Using EXEC CICS LINK passing storage buffers

When the z/OS CICS Execution Option is called by an EXEC CICS LINK, it is often because you want to pass to the CICS Execution Option the address of one or more storage buffers containing input data or the address of one or more storage buffers that will contain mapped output data or both address types.

Suppose that you want to call the CICS Execution Option from a z/OS CICS COBOL program using an EXEC CICS LINK and execute a map named MAPA. This map has one input and one output, both of which exist as storage buffers. To do this, the COMMAREA passed to the CICS Execution Option should be defined as:


   01 DTX-LINK-BLOCK-B.
      05 MRLB-VERSION                              PIC X(04) VALUE 'B002'.
      05 MRLB-PARM-COUNT                           PIC 9(08) COMP VALUE 0.
      05 MRLB-PARM-LIST-ADDRESS                        POINTER VALUE NULL.
      05 MRLB-RETURN-CODE                          PIC 9(04) COMP VALUE 0.
         88 MRLB-NORMAL-RETURN                            VALUE 0.
      05 MRLB-RETURN-MESSAGE                       PIC X(80) VALUE SPACE.
      05 MRLB-MAPPING-RETURN-CODE                  PIC 9(04) COMP VALUE 0.
         88 MRLB-NORMAL-MAP-RETURN                        VALUE 0.

Next, code a working-storage area similar to the following example to hold the command line. The command line has card overrides for input 1 and output 1 indicates that the source and target exist as storage buffers.


   01 MAP-COMMAND-LINE
      05 MAP-COMMAND-STRING   PIC X(16) VALUE 'MAPA -I1@B -O1@B'.
      05 FILLER               PIC X(01) VALUE LOW-VALUE.

MRLB-PARM-LIST-ADDRESS in DTX-LINK-BLOCK-B should contain the address of a parameter list such as the following example. The parameters need not be in this exact order but the command line must be the first parameter in the list.


   01 PL00-PARM-LIST.
      05  PL01-MAP-COMMAND            POINTER.
      05  PL02-I1-BUFFER-PARM         POINTER.
      05  PL03-O1-BUFFER-PARM         POINTER.

PL01-MAP-COMMAND should contain the address of the null-terminated Command Line, MAP-COMMAND-LINE, defined above. PL02-I1-BUFFER-PARM should contain the address of the following working storage area:


   01    DTX-DATA-BUFFER.
         05  MRDB-DATA-LENGTH                         PIC S9(8) COMP.
         05  MRDB-DATA-ADDRESS                                 POINTER.
         05  MRDB-DATA-NAME-AREA                      PIC X(04).
         05  FILLER REDEFINES MRDB-DATA-NAME-AREA.
             10  MRDB-DATA-NAME-L2                    PIC X(02).
             10  MRDB-NULL-TERMINATOR-L2              PIC X(01).
             10  FILLER                               PIC X(01).
         05  FILLER REDEFINES MRDB-DATA-NAME-AREA.
             10  MRDB-DATA-NAME-L3                    PIC X(03).
             10  MRDB-NULL-TERMINATOR-L3              PIC X(01).

MRDB-DATA-LENGTH should contain the actual length of the data in the buffer for input 1. MRDB-DATA-ADDRESS should contain the address of the buffer for input 1. MRDB-DATA-NAME-AREA should contain the null-terminated string "I1", indicating that this buffer is to be used as input 1.

PL02-O1-BUFFER-PARM should contain the address of an identical working storage area initialized as follows: MRDB-DATA-LENGTH should contain the full size of the buffer allocated for output 1. MRDB-DATA-ADDRESS should contain the address of the output buffer. MRDB-DATA-NAME-AREA should contain the null-terminated string "O1", indicating that this buffer will hold the mapped data for output 1.

MAPLB-PARM-COUNT should be set to 3 (1 for the command line + 1 for the input buffer + 1 for the output buffer). If more or fewer parameters are to be passed, make sure that you adjust the value of MAPLB-PARM-COUNT accordingly. See the DTXSCTST sample program.