Skip to main content

How to dynamically set a BORDER on a Dialog System DISPLAY FIELD entry field ?

  • February 15, 2013
  • 0 replies
  • 0 views

Problem:

use Class library reference's methods, as in the code pasted below.

( Methods: Border, SizeBorder, DoubleBorder                to set     a Border )

( Methods: NoBorder, NoSizeBorder, NoDoubleBorder  to unset a Border )

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"

           StaticText is class "label".

       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 "DSEFborder.CPB".

       copy "pan2link.cpy".               *> because PANELS2

       COPY "dssysinf.cpy".               *> because PANELS2

       COPY "pan2err.cpy".                *> because PANELS2

       01 lnkstring                       pic x(20).

       01 EFObjHandle                     object reference.

       01 lnkSystemHandle                 PIC 9(9) COMP-5.

       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 "DSEFborder" TO Ds-Set-Name.

      *---------------------------------------------------------------*

       Program-Body SECTION.

          PERFORM Call-Dialog-System

          evaluate exit-flag

          when 3    *> Class Library reference

          when 4

          when 5

          when 6

          when 7

          when 8

            move efhandle to lnkSystemHandle

            invoke EntryField "fromHandle" USING lnkSystemHandle

                                          returning EFObjHandle

            end-invoke

            *>invoke EFObjHandle "isTypeOf" using EntryField

            *>                              returning lnkbool

            *>end-invoke

            *>if lnkbool = 1 display "EF1 class  txtentry " end-if

            *>invoke EFObjHandle "isTypeOf" using StaticText

            *>                              returning lnkbool

            *>end-invoke

            *>if lnkbool = 1 display "EF1 class  label    " end-if

            invoke EFObjHandle "fittext"

            evaluate exit-flag

               when 3  invoke EFObjHandle "border"               end-invoke

               when 4  invoke EFObjHandle "DoubleBorder"   end-invoke

               when 5  invoke EFObjHandle "NoBorder"         end-invoke

               when 6  invoke EFObjHandle "NoDoubleBorder" end-invoke

               when 7  invoke EFObjHandle "SizeBorder"       end-invoke

               when 8  invoke EFObjHandle "NoSizeBorder"   end-invoke

            end-evaluate

          end-evaluate.

      *---------------------------------------------------------------*

       Program-Terminate SECTION.

          STOP RUN

          .

      *---------------------------------------------------------------*

       Call-Dialog-System SECTION.

          CALL dialog-system USING Ds-Control-Block,

                                   Data-Block

                                   DS-Event-Block

          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

          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.

Old KB# 6577

0 replies

Be the first to reply!