3.2 Definition of the COBOL Programs

To be able to write a COBOL program for this defined surface, you have to know the following:

Each of these points are explained in the following chapters.

3.2.1 Mapping the Dialog Data Types

Based on the dialog description the data types used there can be mapped onto the data types usable in COBOL. This dialog mapping on COBOL is unambiguous; the next incomplete table provides some information:

Dialog Data Type

COBOL Data Type

object

PIC 9(9) binary.

integer

PIC 9(9) binary.

string[??]

PIC X(??).

boolean

PIC 9(4) binary.

3.2.2 Central Data Structures

In the COBOL interface of the Dialog Manager there are two central data structures via which the communication between application and the Dialog Manager is established.

The most important data structure is called DM-StdArgs, which the application has to transfer to every function called by the COBOL interface. In this structure the Dialog Manager informs the application whether any errors have occurred on calling the function. Furthermore, the application can inform the Dialog Manager about options which shall be considered during the realization of individual functions. The fields for the string handling DM-truncspaces, DM-getsep and DM-setsep should be only set before calling the initialization function, thus should only be set globally; in other words, it should not be changed during the course of the program. See also chapter “Handling of String Parameters”.

The DM-StdArgs structure thus looks as follows:

02 DM-StdArgs.
03 DM-version-type               pic X value "A".
03 DM-major-version              pic 9(4) binary value 6.
03 DM-minor-version              pic 9(4) binary value 3.
03 DM-patch-level                pic 9(4) binary value 2.
03 DM-patch-sublevel             pic 9(4) binary value 0.
03 DM-version-string             pic X(12) value "A.06.03.b".
03 DM-version                    pic 9(4) binary value 603.
03 DM-protocol-version           pic 9(4) binary value 1.
   03 DM-status                  pic 9(9) binary value 0.
   03 DM-options                 pic 9(9) binary value 0.
   03 DM-rescode                 pic 9(9) binary value 0.
   03 DM-setsep-S.
      04 DM-setsep               pic X value "@".
      04 filler                  pic X value low-value.
   03 DM-getsep-S.
      04 DM-getsep               pic X value space.
      04 filler                  pic X value low-value.
   03 DM-truncspaces             pic 9(4) binary value 1.
   03 DM-usercodepage-S.
      04 DM-usercodepage         pic X(32) value spaces.
      04 filler                  pic X(32) value low-values.

The second important structure is the DM-Value structure, for in this structure the values are transferred from the COBOL program to the Dialog Manager. This structure contains the object, the attribute and the values an attribute can adopt. In the example this structure is needed to fill the tablefield and it will only be defined there.

3.2.3 Main Program

Programs which shall work with the Dialog Manager need special main programs. These are equal in principle and can therefore be copied from the provided examples.

On constructing the main program you have to decide, however, if you want to develop a local application or a server in a distributed environment. For a local application you have to provide for a function called COBOLMAIN, for a distributed application you have to provide for two functions called COBOLAPPINIT and COBOLAPPFINISH.

These main programs have to use in their WORKING STORAGE section the copy path "IDMcobws.cob" supplied by the Dialog Manager in order to be able to access the DM definitions.

3.2.3.1 Local Applications

The structure of the function COBOLMAIN here looks as follows:

Example

    identification division.

    programid. CobolMAIN.

 

    data division.

    workingstorage section.

    *This is the copy path which provides for the possibility

    *that the values defined by the Dialog Manager can be

    *accessed.

    copy "IDMcobws.cob".

 

    *Definition of a variable to save the dialog ID.

    77    Dmdialogid    pic 9(9) binary value 0.

    *Variable for intermediate data storage of the current

    *function

    *By this variable the error output will be facilitated.

    77    Funcname        pic X(30) value spaces.

 

    linkage section.

    *Definition of the parameters which are passed on to

    *the main program.

    01    exitstatus pic 9(4) binary.

 

    procedure division using exitstatus.

    startup section.

 

    *Initialization of the Dialog Manager

    initializeIDM.

    *Here the separator can be set

    *by which the strings in COBOL can be finished.

      move "@" to DMsetsep.

      call "DMcob_Initialize" using DMStdArgs

            DMCommonData.

      perform errorcheck.

 

    *Loading the dialog belonging to the application

    loaddialog.

      call "DMcob_LoadDialog" using DMStdArgs DMdialogid

             by content "table.dlg@".

      perform errorcheck.

 

    *Binding the functions by means of records as parameters.

    bindrecords.

      call "CobRecMInitCobolBeispiel" using DMStdArgs

                 DMdialogid

              DMStdArgs.

    *Binding the functions without records as parameters.

      call "BindFuncs" using DMdialogID DMStdArgs.

 

    *Starting the dialog

    startdialog.

      call "DMcob_StartDialog" using DMStdArgs DMdialogid.

      perform errorcheck.

 

    *Starting the processing in the dialog

    eventloop.

      call "DMcob_EventLoop" using DMStdArgs.

      perform errorcheck.

 

    *Finishing the application

    dialogdone.

      display "Application finishes successfully.".

      goback.

 

    *Query for errors

    errorcheck.

      if DMStatus

        display "Error occurred in " funcname upon sysout

        display "Application terminates due to error."

        move 1 to exitstatus

        goback.

3.2.3.2 Distributed Applications

For distributed applications two COBOL functions have to be supplied, which can initialize or finish the application. The initialization function is called CobolAppInit, the end function CobolAppFinish.

The structure of the function CobolAppInit looks as follows:

In the function CobolAppInit those actions have to be carried out which bring about a controlled termination of the application. Calls to the Dialog Manager are not necessary here, the server application will automatically be terminated after the function return.

Example

    identification division.

    programid. COBOLAPPINIT.

 

    data division.

    workingstorage section.

    * Using the copy path supplied by the Dialog Manager

    copy "IDMcobws.cob".

 

    linkage section.

    * Declaration of the function parameters

    * In the Exit state the result is returned,

    * in DMapplid the application ID and in the

    * DMdialogID the dialog ID is passed on.

    01    Exitstatus    pic 9(4) binary.

    77    Dmapplid    pic 9(9) binary.

    77    Dmdialogid    pic 9(9) binary.

 

    procedure division using exitstatus dmapplid

        DMdialogid.

    startup section.

 

    * Initialization of the COBOL interface

    initialize-IDM.

      call "DMcob_Initialize" using DM-StdArgs

        DM-Common-Data.

      PERFORM ERROR-CHECK.

 

    * Dynamic binding of the COBOL functions

    * after the record functions have been bound.

    BIND-FUNCTIONS.

      call "CobRecMInitCobolBeispiel" using DM-StdArgs

                  DM-appl-id

                  by content 0.

      call "DMufcob_BindThruLoader" using DM-StdArgs

                  DM-appl-id.

 

    * Setting the return value.

      MOVE DM-SUCCESS TO EXIT-STATUS.

      GOBACK.

3.2.4 Auxiliary Means for the COBOL Programming

To avoid having to input twice the definitions in the dialog for parameters of the COBOL functions, the simulator of the Dialog Manager can generate a necessary copy path from a dialog file. This is done by the start option

+writetrampolin <Basis-Name>

In doing so, the basis name of a file is indicated, to which the endings ".c", ".cob" and ".cpy" is attached to generate the files needed for the call of the COBOL functions.

For the example the command line looks as follows:

idm +writetrampolin tablec table.dlg

By this call the following files are created:

The generated C and COBOL files have to be translated and linked to the application. The CPY file should be used to be able to access the definitions of the transfer structure in the dialog.

This file looks as follows in the example:

01 RecAddress.

   05 NName      pic X(25).

   05 FirstName  pic X(15).

   05 City       pic X(25).

   05 Street     pic X(30).

   05 Country    pic 9(9) binary.

3.2.5 Functions for the Tablefield

Functions which can fill or query the contents of objects with list characters are an exception with regard to the layer model, for these functions can only be written with extensive knowledge of the dialog. This is necessary so that the functions can operate effectively. The tablefield has to be filled by means of so-called temporary areas. These temporary areas in the Dialog Manager are created, then filled before the application and finally allocated to an object. In doing so, the permanent flicker of the tablefield during filling can be avoided in local applications; for distributed applications a strong increase in performance compared to the single allocation can be achieved. The procedure consists of the following steps:

The values are read out analogous to filling the object:

3.2.5.1 Function FILLTAB

This function takes on the filling of the tablefield. The tablefield ID and the number of elements to be filled are transferred to this function.

Usually the definition of the module is made first (it should have the same name as the function in the dialog).

*SET OSVS

    IDENTIFICATION DIVISION.

    PROGRAM-ID. FILLTAB.

    AUTHOR. "ISA-DEMO".

 

    ENVIRONMENT DIVISION.

    INPUT-OUTPUT SECTION.

    DATA DIVISION.

    FILE SECTION.

 

    WORKING-STORAGE SECTION.

    01  STR-TAB.

    05 STRFIELD PIC X OCCURS 80.

    01  INT-TAB.

    05 INTFIELD PIC 9 OCCURS 5.

 

    77  COUNTER PIC 9(4) VALUE 0.

    77  BASE PIC 9(4) VALUE 0.

    77  DM-POINTER  PIC 9(4) BINARY VALUE 0.

    77  ICOUNT  PIC 9(4) BINARY VALUE 0.

    77  IDUMMY  PIC 9(4) VALUE 0.

 

    77  I    PIC 99 VALUE ZERO.

    77  J    PIC 99 VALUE ZERO.

    77  KL      PIC 9(4) VALUE ZERO.

    77  DLG-NAME PIC X(80) value "Name ".

    77  DLG-VORNAME PIC X(80) value "First Name ".

    77  DLG-WOHNORT PIC X(80) value "Place of Residence ".

In the linkage section a copy is made on the file supplied by the DM IDMcobls.cob, so that the definitions in the COBOL program can be accessed.

    LINKAGE SECTION.

    *By this copy path the definitions in the

    *Dialog Manager

    *are available in this COBOL module.

    COPY "IDMcobls.cob".

    *In this parameter the number of rows is transferred

    *which are to be initially filled.

    77  DLG-CNT PIC 9(9) binary.

    *In this variable the table is transferred

    *which shall be filled.

    77  DLG-OBJECT PIC 9(9) binary.

On defining the procedure division it shall be considered that this division has one parameter more than defined in the dialog. The first parameter of a COBOL function called by the DM is always the DM-Common-Data and these will not be defined in the dialog.

    *This COBOL function creates a temporary memory area in

    *the Dialog Manager and allocates this area to a

    *tablefield.

 

    PROCEDURE DIVISION USING DM-COMMON-DATA

        DLG-OBJECT DLG-CNT.

    ORGANIZE-IN SECTION.

      MOVE 0 TO BASE.

      MOVE DLG-CNT TO ICOUNT.

    *Initialization of a memory area in the DM

In this function a temporary area will be created, filled and then allocated to a tablefield.

      CALL "DMcob_InitVector" USING DM-StdArgs DM-POINTER

        DT-String

        ICOUNT.

    *Initialization of the DM-Value structure

      MOVE DT-STRING TO DM-DATATYPE.

    *Filling the temporary area which shall then

    *be displayed in the table.

    PREPARE-DATA SECTION.

    *Setting the individual contents

      MOVE 0 TO COUNTER.

      MOVE 0 TO KL.

 

      PERFORM VARYING COUNTER FROM 1 BY 1

        UNTIL COUNTER > ICOUNT

            ADD 1 TO KL

        MOVE KL TO DM-INDEX

        MOVE DLG-NAME TO STR-TAB

    *First the name is set.

            COMPUTE IDUMMY = COUNTER + BASE

        MOVE IDUMMY TO INT-TAB

        MOVE 5 TO J

        MOVE SPACE TO STRFIELD(J)

        ADD 1 TO J

        PERFORM VARYING I FROM 1 BY 1 UNTIL I > 5

            MOVE INTFIELD(I) TO STRFIELD(J)

            ADD 1 TO J

        END-PERFORM

 

        MOVE STR-TAB TO DM-VALUE-STRING

        CALL "DMcob_SetVectorValue" USING DM-STDARGS

            DM-VALUE

            DM-POINTER

 

    *After that the first name is set.

            ADD 1 TO KL

        MOVE KL TO DM-INDEX

        MOVE DLG-VORNAME TO STR-TAB

    *Editing of a modified string for the display

        COMPUTE IDUMMY = COUNTER + BASE

        MOVE IDUMMY TO INT-TAB

        MOVE 8 TO J

        MOVE SPACE TO STRFIELD(J)

        ADD 1 TO J

        PERFORM VARYING I FROM 1 BY 1 UNTIL I > 5

            MOVE INTFIELD(I) TO STRFIELD(J)

            ADD 1 TO J

        END-PERFORM

 

    *Finally the city is set.

        MOVE STR-TAB TO DM-VALUE-STRING

        CALL "DMcob_SetVectorValue" USING DM-STDARGS

            DM-VALUE

            DM-POINTER

 

        ADD 1 TO KL

        MOVE KL TO DM-INDEX

        MOVE DLG-WOHNORT TO STR-TAB

    *Computing a modified string for the display

        COMPUTE IDUMMY = COUNTER + BASE

        MOVE IDUMMY TO INT-TAB

        MOVE 4 TO J

        MOVE SPACE TO STRFIELD(J)

        ADD 1 TO J

        PERFORM VARYING I FROM 1 BY 1 UNTIL I > 5

            MOVE INTFIELD(I) TO STRFIELD(J)

            ADD 1 TO J

        END-PERFORM

 

        MOVE STR-TAB TO DM-VALUE-STRING

        CALL "DMcob_SetVectorValue" USING DM-STDARGS

            DM-VALUE

            DM-POINTER

    *End of loop to compute the data.

      END-PERFORM.

 

    *Transferring the saved values to the display

      MOVE DLG-OBJECT TO DM-OBJECT.

      MOVE AT-FIELD TO DM-ATTRIBUTE.

      MOVE 2 TO DM-INDEXCOUNT.

      MOVE 1 TO DM-index.

      MOVE 1 TO DM-second.

    *The entire table contents shall be replaced by the

    *contents of the temporary area.

    *Therefore the last three parameters have the value 0.

      CALL "DMcob_SetVector" USING DM-StdArgs DM-Value

            DM-POINTER

            by content 0

            by content 0

            by content 0.

Finally this area will be released in the Dialog Manager.

    *Freeing the memory area

 

      CALL "DMcob_FreeVector" USING DM-StdArgs DM-POINTER.

      GOBACK.

3.2.5.2 Function TABFUNC

By means of this function the reloading of the tablefield will be achieved. Whenever the user scrolls in an area which has not been filled yet, the Dialog Manger calls this function.

The parameters are uniquely defined and therefore cannot be changed. These reloading functions get as a parameter a structure DM-Content-Data in which the necessary information is saved.

01  DM-Content-Data

    02    DM-CO-OBJECT     pic 9(9) binary.

    02    DM-CO-REASON     pic 9(4) binary.

    02    DM-CO-VISFIRST   pic 9(4) binary.

    02    DM-CO-VISLAST    pic 9(4) binary.

    02    DM-CO-LOADFIRST  pic 9(4) binary.

    02    DM-CO-LOADLAST   pic 9(4) binary.

    02    DM-CO-COUNT      pic 9(4) binary.

    02    DM-CO-HEADER     pic 9(4) binary.

In the DM-Co-Object the ID of the tablefield is transferred. The fields DM-Co-Visfirst and DM-Co-Vislast contain the first and last visible line, the fields DM-Co-Loadfirst and DM-Co-Loadlast contain the first and last line to be loaded. But these are only minimal values, the application may at any time load more than the indicated lines.

    IDENTIFICATION DIVISION.

    PROGRAM-ID. TABFUNC.

    AUTHOR. "ISA-DEMO".

 

    ENVIRONMENT DIVISION.

    INPUT-OUTPUT SECTION.

    DATA DIVISION.

    FILE SECTION.

 

    WORKING-STORAGE SECTION.

    01  STR-TAB.

    05 STRFIELD PIC X OCCURS 80.

    01  INT-TAB.

    05 INTFIELD PIC 9 OCCURS 5.

    77  COUNTER PIC 9(4) VALUE 0.

    77  BASE PIC 9(4) VALUE 0.

    77  DM-POINTER  PIC 9(4) BINARY VALUE 0.

    77  ICOUNT  PIC 9(4) BINARY VALUE 0.

    77  IROW    PIC 9(4) BINARY VALUE 0.

    77  ICOL    PIC 9(4) BINARY VALUE 3.

    77  IDUMMY  PIC 9(4) VALUE 0.

 

    77  I    PIC 99 VALUE ZERO.

    77  J    PIC 99 VALUE ZERO.

    77  KL      PIC 9(4) VALUE ZERO.

    77  DLG-NAME PIC X(80) value "Name ".

    77  DLG-VORNAME PIC X(80) value "Vorname ".

    77  DLG-WOHNORT PIC X(80) value "Ort  ".

    77  DLG-COUNT PIC 9(9) BINARY value 0.

In order to access the DM-Content-Data structure, the file IDMcoboc.cob per COPY must be drawn. Otherwise this function works the same way as the function FILLTAB.

    LINKAGE SECTION.

    COPY "IDMcobls.cob".

    COPY "IDMcoboc.cob".

 

    *This COBOL function creates a temporary memory area

    *in the Dialog Manager and allocates this area to a     *tablefield.

 

    PROCEDURE DIVISION USING DM-COMMON-DATA DM-Content-Data.

    ORGANIZE-IN SECTION.

 

      COMPUTE ICOUNT =  DM-co-loadlast - DM-co-loadfirst.

      COMPUTE ICOUNT = ICOUNT + 1.

      COMPUTE ICOUNT = ICOUNT * 3.

      COMPUTE BASE = DM-co-loadfirst * 3.

      MOVE ICOUNT TO DLG-COUNT.

      MOVE DM-CO-OBJECT TO DM-OBJECT.

      MOVE DT-string TO DM-DATATYPE.

      MOVE DM-co-loadfirst TO BASE.

    *Initialization of a memory area in the DM

      CALL "DMcob_InitVector" USING DM-StdArgs DM-POINTER

        DT-String

        ICOUNT.

    *Initialization of the DM-Value structure

      MOVE DT-STRING TO DM-DATATYPE.

      PERFORM FILLDATA.

 

    *Transferring the saved values to the display

      MOVE DM-CO-OBJECT TO DM-OBJECT.

      MOVE AT-FIELD TO DM-ATTRIBUTE.

      MOVE 2 TO DM-INDEXCOUNT.

      COMPUTE DM-INDEX =  DM-co-loadfirst - 1.

      MOVE 1 TO DM-second.

      CALL "DMcob_SetVector" USING DM-StdArgs DM-Value

            DM-POINTER by content 0

            by reference DM-co-loadlast ICOL.

    

    *Freeing the memory area

      CALL "DMcob_FreeVector" USING DM-StdArgs DM-POINTER.

      GOBACK.

 

    FILLDATA.

    *Setting the individual contents

      MOVE 0 TO COUNTER.

      MOVE 0 TO KL.

        MOVE 256 TO DM-INDEXCOUNT.

      PERFORM VARYING COUNTER FROM 1 BY 1

        UNTIL KL > ICOUNT

        ADD 1 TO KL

        MOVE KL TO DM-INDEX

        MOVE DLG-NAME TO STR-TAB

    *Computing a modified string for the display

        COMPUTE IDUMMY = COUNTER + BASE

        MOVE IDUMMY TO INT-TAB

        MOVE 5 TO J

        MOVE SPACE TO STRFIELD(J)

        ADD 1 TO J

        PERFORM VARYING I FROM 1 BY 1 UNTIL I > 5

            MOVE INTFIELD(I) TO STRFIELD(J)

            ADD 1 TO J

        END-PERFORM

 

        MOVE STR-TAB TO DM-VALUE-STRING

        CALL "DMcob_SetVectorValue" USING DM-STDARGS

            DM-VALUE DM-POINTER

 

        ADD 1 TO KL

        MOVE KL TO DM-INDEX

        MOVE DLG-VORNAME TO STR-TAB

    *Computing a modified string for the display

        COMPUTE IDUMMY = COUNTER + BASE

        MOVE IDUMMY TO INT-TAB

        MOVE 8 TO J

        MOVE SPACE TO STRFIELD(J)

        ADD 1 TO J

        PERFORM VARYING I FROM 1 BY 1 UNTIL I > 5

            MOVE INTFIELD(I) TO STRFIELD(J)

            ADD 1 TO J

        END-PERFORM

 

        MOVE STR-TAB TO DM-VALUE-STRING

        CALL "DMcob_SetVectorValue" USING DM-STDARGS

            DM-VALUE DM-POINTER

        ADD 1 TO KL

        MOVE KL TO DM-INDEX

        MOVE DLG-WOHNORT TO STR-TAB

    *Computing a modified string for the display

        COMPUTE IDUMMY = COUNTER + BASE

        MOVE IDUMMY TO INT-TAB

        MOVE 4 TO J

        MOVE SPACE TO STRFIELD(J)

        ADD 1 TO J

        PERFORM VARYING I FROM 1 BY 1 UNTIL I > 5

            MOVE INTFIELD(I) TO STRFIELD(J)

            ADD 1 TO J

        END-PERFORM

        MOVE STR-TAB TO DM-VALUE-STRING

        CALL "DMcob_SetVectorValue" USING DM-STDARGS

            DM-VALUE DM-POINTER

      END-PERFORM.

3.2.6 Functions with Records as Parameters

In contrast to the functions for the tablefield, the subsequent functions can do without the information about the dialog, which is even much better. These functions are therefore written in standard COBOL without any call to the Dialog Manager. Only the copy paths show that these are functions which are called by the Dialog Manager.

3.2.6.1 Function GETADDR

This function shall bring the rest of the record to the surface on a given name. In order to access the dialog definition, a copy will be added to the file tablec.cpy generated by the Dialog Manager.

IDENTIFICATION DIVISION.

    PROGRAM-ID. GETADDR.

    AUTHOR. "ISA-DEMO".

    DATA DIVISION.

    WORKING-STORAGE SECTION.

    LINKAGE SECTION.

 

    COPY "IDMcobls.cob".

    *The following copy belongs to this application. It was

    *generated by the DM from the dialgo and should be used

    *in the COBOL modules where the corresponding structures

    *shall be accessed.

    COPY "tablec.cpy".

 

    PROCEDURE DIVISION USING DM-COMMON-DATA RECADDRESS.

 

    SEC-RECADDRESS SECTION.

    *Normally the values for the individual entries should be

    *fetched from the database. This is not necessary here.

    *Instead dummy values are allocated to the corresponding

    *structure elements.

        MOVE "NAME" TO NNAME.

        MOVE "FIRST NAME" TO FIRSTNAME.

        MOVE "STREET" TO STREET.

        MOVE 3 TO COUNTRY.

        GOBACK.

3.2.6.2 Function PUTADDR

This function shall save the data changed by the user. In order to access the dialog definitions, a copy is added to the file tablec.cpy generated by the Dialog Manager.

IDENTIFICATION DIVISION.

    PROGRAM-ID. PUTADDR.

    AUTHOR. "ISA-DEMO".

 

    DATA DIVISION.

 

    WORKING-STORAGE SECTION.

 

    LINKAGE SECTION.

 

    COPY "IDMcobls.cob".

    *The following copy belongs to this application. It was

    *generated by the DM from the dialog and should be used

    *in the COBOL modules where the corresponding structures

    *can be accessed.

    COPY "tablec.cpy".

 

    PROCEDURE DIVISION USING DM-COMMON-DATA RECADDRESS.

 

    SEC-RECADDRESS SECTION.

 

    *Normally the values for the individual entries should be

    *fetched from the database. This is not necessary here.

    *Instead dummy values are allocated to the corresponding

    *structure elements.

        MOVE "      " TO STREET.

        MOVE 0 TO COUNTRY.

        GOBACK.