Problem:
Use PANELS2 functions or Class library reference's methods.
In the code pasted below, the Entry field's handle is set in the data EFhandle of the data-block through the use of the Dialog system function MOVE-OBJECT-HANDLE
The MOVE-OBJECT-HANDLE function lets you save the handle of an object in a numeric data item in the Data Block. This ensures the same objects are being referenced by both the Panels V2 and the Dialog System parts of your application. As an example:
MOVE-OBJECT-HANDLE RENAME-PB PB-HAND
MOVE-OBJECT-HANDLE RENAME-WIN WIND-HAND
Resolution:
class-control.
EntryField is class "txtentry".
DATA DIVISION.
WORKING-STORAGE SECTION.
78 dialog-system VALUE "DSGRUN".
01 Display-Error.
03 Display-Error-No PIC 9(4) comp-5.
03 Display-Details-1 PIC 9(4) comp-5.
03 Display-Details-2 PIC 9(4) comp-5.
COPY "DS-CNTRL.MF".
COPY "DSEFreadonly.CPB".
copy "pan2link.cpy". *> because PANELS2
COPY "dssysinf.cpy". *> because PANELS2
COPY "pan2err.cpy". *> because PANELS2
01 EFObjHandle object reference.
01 lnkSystemHandle PIC 9(9) COMP-5.
01 lnkstring pic x(30).
PROCEDURE DIVISION.
*---------------------------------------------------------------*
Main-Process SECTION.
PERFORM Program-Initialize
PERFORM Program-Body UNTIL EXIT-FLAG-TRUE
PERFORM Program-Terminate.
*---------------------------------------------------------------*
Program-Initialize SECTION.
INITIALIZE Ds-Control-Block
INITIALIZE Data-block
MOVE Data-block-version-no
TO Ds-Data-Block-Version-No
MOVE Version-no TO Ds-Version-No
MOVE Ds-New-Set TO Ds-Control
MOVE "DSEFreadonly" TO Ds-Set-Name.
*---------------------------------------------------------------*
Program-Body SECTION.
PERFORM Call-Dialog-System
evaluate exit-flag
when 2
*> set entry-field readonly *> PANELS2
move efhandle to P2-Descendant
move EF-Read-Only to P2G-Entry-Field-Flags
move Pf-Change-Entry-Field-Style
to p2-function
call "PANELS2" using P2-Parameter-Block
P2G-Entry-Field-Record
end-call
if P2-Status = P2-NO-ERROR
continue
else
display "Panels2 error on " Pf-Change-Entry-Field-Style
"/" P2-Status
end-if
move Pf-Set-Entry-Field-Text to p2-function
move efhandle to P2-Descendant
move "ReadOnly" to lnkstring
call "PANELS2" using P2-Parameter-Block
P2G-Entry-Field-Record
lnkstring
when 3 *> PANELS2
*> set entry-field NOT readonly
move efhandle to P2-Descendant
subtract EF-Read-Only from P2G-Entry-Field-Flags
move Pf-Change-Entry-Field-Style
to p2-function
call "PANELS2" using P2-Parameter-Block
P2G-Entry-Field-Record
end-call
if P2-Status = P2-NO-ERROR
continue
else
display "Panels2 error on " Pf-Change-Entry-Field-Style
"/" P2-Status
end-if
move Pf-Set-Entry-Field-Text to p2-function
move efhandle to P2-Descendant
move "Not ReadOnly" to lnkstring
call "PANELS2" using P2-Parameter-Block
P2G-Entry-Field-Record
lnkstring
when 4
*> set entry-field readonly *> class library
move efhandle to lnkSystemHandle
invoke EntryField "fromHandle" USING lnkSystemHandle
returning EFObjHandle
invoke EFObjHandle "ReadOnly"
invoke EFObjHandle "Disable"
move "ReadOnly" to lnkstring
invoke EFObjHandle "SetTextZ" using lnkstring
invoke EFObjHandle "Update"
when 5
*> set entry-field NOT readonly *> class library
move efhandle to lnkSystemHandle
invoke EntryField "fromHandle" USING lnkSystemHandle
returning EFObjHandle
invoke EFObjHandle "NotReadOnly"
invoke EFObjHandle "Enable"
move "Not ReadOnly" to lnkstring
invoke EFObjHandle "SetTextZ" using lnkstring
invoke EFObjHandle "Update"
END-EVALUATE.
*---------------------------------------------------------------*
Program-Terminate SECTION.
STOP RUN
.
*---------------------------------------------------------------*
Call-Dialog-System SECTION.
CALL dialog-system USING Ds-Control-Block,
Data-Block
DS-Event-Block *> because PANELS2
if p2-mf-reserved = 0
move ds-session-id to p2-mf-reserved *> because PANELS2
*> New call - initialize the class library
move Pf-Load-Class-Library to P2-Function
call "PANELS2" using P2-Parameter-Block
end-if
IF NOT Ds-No-Error
MOVE Ds-System-Error TO Display-error
DISPLAY "DS ERROR NO: " Display-error-no
DISPLAY "Error Details(1) : " Display-Details-1
DISPLAY "Error Details(2) : " Display-Details-2
PERFORM Program-Terminate
END-IF
.