BCS ISPF Dialog Management Facility via COBOL


To successfully dialog (a conversation between TSO’s (time sharing option) ISPF (Integrated Structured Programming Facility) and the end user) IBM offers many possible solutions to accomplish this.
Today we will examining using dialog management facility via COBOL (Common Business Oriented Language). As previously stated there are many avenues to accomplish creating dialogs. The lifeblood of this exercise is to employ the COBOL call to the ISPEXEC facility. Because we need to make tools usable we concentrate our efforts on flexible solutions that are reusable.
The implementation of ISPEXEC we will use today requires the user to supply the length of the command buffer and the command buffer which contains the instruction for the dialog’s management.
I do not believe in head down coding so I attempt to automate processes to eliminate hard coding source and wordy / lengthy programs.
I decided to pass a chunk of space (500 characters) to the COBOL program and let COBOL figure out the actual length, move the data to the command buffer and then invoke the ISPEXEC call to dialog management.
Below is a COBOL sub program that does exactly that.
[codesyntax lang=”cobol”]

000100 IDENTIFICATION DIVISION.                                         00010000
000200 PROGRAM-ID.    ABS00001.                                         00020000
000300 AUTHOR.        ARCH BROOKS.                                      00030000
000400 INSTALLATION   BROOKS COMPUTING SYSTEMS, LLC.                    00040000
000500 DATE-WRITTEN.  09/16/2014.                                       00050000
000600 DATE-COMPILED. 09/16/2014.                                       00060000
000700 ENVIRONMENT DIVISION.                                            00070000
000800 CONFIGURATION SECTION.                                           00080000
000900 SOURCE-COMPUTER. IBM-Z-OS.                                       00090000
001000 OBJECT-COMPUTER. IBM-Z-OS.                                       00100000
001100 DATA DIVISION.                                                   00110000
001200 WORKING-STORAGE SECTION.                                         00120000
001210 77  CINDEX PIC 999.                                              00121000
001300 01  PARM-AREA.                                                   00130000
001400   05  PARM-SIZE PIC S9(5).                                       00140000
001500   05  PARMB PIC X OCCURS 1 TO 500 TIMES DEPENDING ON PARM-SIZE.  00150000
001600 LINKAGE SECTION.                                                 00160000
001700 01   COMD PIC X(500).                                            00170000
001710 01   CMDBB-AREA REDEFINES COMD.                                  00171000
001720      05  COMBB  PIC X OCCURS 500 TIMES.                          00172000
001800 PROCEDURE DIVISION USING COMD.                                   00180000
001900     PERFORM 0010-CALC-SIZE.                                      00190000
002000     GOBACK.                                                      00200000
002100 0010-CALC-SIZE.                                                  00210000
002200     COMPUTE PARM-SIZE = LENGTH OF COMD.                          00220000
002201     PERFORM 0020-MOVE-COMMAND.                                   00220100
002210 0020-MOVE-COMMAND.                                               00221000
002221     PERFORM 0030-MOVE-CMDB VARYING CINDEX FROM 1 BY 1            00222100
002222       UNTIL CINDEX > PARM-SIZE.                                  00222200
002223 0030-MOVE-CMDB.                                                  00222300
002230     MOVE PARMB (CINDEX) TO COMBB (CINDEX).                       00223000
002240 0040-INVOKE-ISPLINK.                                             00224000
002250     CALL 'ISPEXEC' USING PARM-SIZE, CMDBB-AREA.                  00225001

[/codesyntax]
The object from the resulting compile process is stored on a PDS (partitioned data set) and will be used subsequently as input to a linkage editor which will make the program executable by the computer. This level of modular programming allows us to isolate automated functions and call them on demand when their utilization is required.
I am also including the compiled listing of this routine to soothe any minds that may question the viability of the offered source code.
[codesyntax lang=”cobol”]

1PP 5655-S71 IBM Enterprise COBOL for z/OS  4.1.0                         Date 09/16/2014  Time 10:18:29   Page     1
0Invocation parameters:
  VBREF
0Options in effect:
  NOADATA
    ADV
    QUOTE
    ARITH(COMPAT)
  NOAWO
    BUFSIZE(4096)
  NOCICS
    CODEPAGE(1140)
  NOCOMPILE(S)
  NOCURRENCY
    DATA(31)
  NODATEPROC
    DBCS
  NODECK
  NODIAGTRUNC
  NODLL
  NODUMP
  NODYNAM
  NOEXIT
  NOEXPORTALL
  NOFASTSRT
    FLAG(I,I)
  NOFLAGSTD
    INTDATE(ANSI)
    LANGUAGE(EN)
  NOLIB
    LINECOUNT(60)
  NOLIST
  NOMAP
  NOMDECK
  NONAME
    NSYMBOL(NATIONAL)
  NONUMBER
    NUMPROC(NOPFD)
    OBJECT
  NOOFFSET
  NOOPTIMIZE
    OUTDD(SYSOUT)
    PGMNAME(COMPAT)
    RENT
    RMODE(AUTO)
    SEQUENCE
    SIZE(MAX)
    SOURCE
    SPACE(1)
  NOSQL
    SQLCCSID
  NOSSRANGE
  NOTERM
  NOTEST
  NOTHREAD
    TRUNC(STD)
    VBREF
  NOWORD
1PP 5655-S71 IBM Enterprise COBOL for z/OS  4.1.0                         Date 09/16/2014  Time 10:18:29   Page     2
0   XMLPARSE(XMLSS)
    XREF(FULL)
    YEARWINDOW(1900)
    ZWB
1PP 5655-S71 IBM Enterprise COBOL for z/OS  4.1.0               ABS00001  Date 09/16/2014  Time 10:18:29   Page     3
   LineID  PL SL  ----+-*A-1-B--+----2----+----3----+----4----+----5----+----6----+----7-|--+----8 Map and Cross Reference
0  000001         000100 IDENTIFICATION DIVISION.                                         00010000
   000002         000200 PROGRAM-ID.    ABS00001.                                         00020000
   000003         000300 AUTHOR.        ARCH BROOKS.                                      00030000
   000004         000400 INSTALLATION   BROOKS COMPUTING SYSTEMS, LLC.                    00040000
   000005         000500 DATE-WRITTEN.  09/16/2014.                                       00050000
   000006         000600 DATE-COMPILED. 09/16/14.                                         00060000
   000007         000700 ENVIRONMENT DIVISION.                                            00070000
   000008         000800 CONFIGURATION SECTION.                                           00080000
   000009         000900 SOURCE-COMPUTER. IBM-Z-OS.                                       00090000
   000010         001000 OBJECT-COMPUTER. IBM-Z-OS.                                       00100000
   000011         001100 DATA DIVISION.                                                   00110000
   000012         001200 WORKING-STORAGE SECTION.                                         00120000
   000013         001210 77  CINDEX PIC 999.                                              00121000
   000014         001300 01  PARM-AREA.                                                   00130000
   000015         001400   05  PARM-SIZE PIC S9(5).                                       00140000
   000016         001500   05  PARMB PIC X OCCURS 1 TO 500 TIMES DEPENDING ON PARM-SIZE.  00150000 15
   000017         001600 LINKAGE SECTION.                                                 00160000
   000018         001700 01   COMD PIC X(500).                                            00170000
   000019         001710 01   CMDBB-AREA REDEFINES COMD.                                  00171000 18
   000020         001720      05  COMBB  PIC X OCCURS 500 TIMES.                          00172000
   000021         001800 PROCEDURE DIVISION USING COMD.                                   00180000 18
   000022         001900     PERFORM 0010-CALC-SIZE.                                      00190000 24
   000023         002000     GOBACK.                                                      00200000
   000024         002100 0010-CALC-SIZE.                                                  00210000
   000025         002200     COMPUTE PARM-SIZE = LENGTH OF COMD.                          00220000 15 IMP 18
   000026         002201     PERFORM 0020-MOVE-COMMAND.                                   00220100 27
   000027         002210 0020-MOVE-COMMAND.                                               00221000
   000028         002221     PERFORM 0030-MOVE-CMDB VARYING CINDEX FROM 1 BY 1            00222100 30 13
   000029         002222       UNTIL CINDEX > PARM-SIZE.                                  00222200 13 15
   000030         002223 0030-MOVE-CMDB.                                                  00222300
   000031         002230     MOVE PARMB (CINDEX) TO COMBB (CINDEX).                       00223000 16 13 20 13
   000032         002240 0040-INVOKE-ISPLINK.                                             00224000
   000033         002250     CALL 'ISPEXEC' USING PARM-SIZE, CMDBB-AREA.                  00225001 EXT 15 19
1PP 5655-S71 IBM Enterprise COBOL for z/OS  4.1.0               ABS00001  Date 09/16/2014  Time 10:18:29   Page     4
0 Count   Cross-reference of verbs        References
 1        CALL . . . . . . . . . . . . .  33
 1        COMPUTE. . . . . . . . . . . .  25
 1        GOBACK . . . . . . . . . . . .  23
 1        MOVE . . . . . . . . . . . . .  31
 3        PERFORM. . . . . . . . . . . .  22 26 28
1PP 5655-S71 IBM Enterprise COBOL for z/OS  4.1.0               ABS00001  Date 09/16/2014  Time 10:18:29   Page     5
0An "M" preceding a data-name reference indicates that the data-name is modified by this reference.
  Defined   Cross-reference of data names   References
       13   CINDEX . . . . . . . . . . . .  M28 29 31 31
       19   CMDBB-AREA . . . . . . . . . .  33
       20   COMBB. . . . . . . . . . . . .  M31
       18   COMD . . . . . . . . . . . . .  19 21 25
       14   PARM-AREA
       15   PARM-SIZE. . . . . . . . . . .  16 M25 29 33
       16   PARMB. . . . . . . . . . . . .  31
1PP 5655-S71 IBM Enterprise COBOL for z/OS  4.1.0               ABS00001  Date 09/16/2014  Time 10:18:29   Page     6
0Context usage is indicated by the letter preceding a procedure-name reference.
 These letters and their meanings are:
     A = ALTER (procedure-name)
     D = GO TO (procedure-name) DEPENDING ON
     E = End of range of (PERFORM) through (procedure-name)
     G = GO TO (procedure-name)
     P = PERFORM (procedure-name)
     T = (ALTER) TO PROCEED TO (procedure-name)
     U = USE FOR DEBUGGING (procedure-name)
  Defined   Cross-reference of procedures   References
       24   0010-CALC-SIZE . . . . . . . .  P22
       27   0020-MOVE-COMMAND. . . . . . .  P26
       30   0030-MOVE-CMDB . . . . . . . .  P28
       32   0040-INVOKE-ISPLINK
1PP 5655-S71 IBM Enterprise COBOL for z/OS  4.1.0               ABS00001  Date 09/16/2014  Time 10:18:29   Page     7
0 Defined   Cross-reference of programs     References
        2   ABS00001
 EXTERNAL   ISPEXEC. . . . . . . . . . . .  33
-* Statistics for COBOL program ABS00001:
 *    Source records = 33
 *    Data Division statements = 7
 *    Procedure Division statements = 7
0End of compilation 1,  program ABS00001,  no statements flagged.
0Return code 0

[/codesyntax]
The provided compiler output proves there are no compile errors in the COBOL source code program.
Mr. Arch Brooks, Software Engineer, Brooks Computing Systems, LLC authored this article.

Leave a Reply

Your email address will not be published. Required fields are marked *