Example of EXCI CALLs with null parameters

If you omit an optional parameter, such as userid on a DPL_Request, you must ensure that the parameter list is built with a null address for the missing parameter.

The example that follows illustrates how to issue an EXCI DPL_Request with the userid and uowid parameters omitted in a COBOL program.

DPL CALL without userid and uowid (COBOL): In this example, the DPL parameters used on the call are defined in the WORKING-STORAGE SECTION, as follows:
DPL parameter COBOL variable Field definition
version_number 01 VERSION-1 PIC S9(8) COMP VALUE 1.
return_area 01 EXCI-RETURN-CODE. (structure)
user_token 01 USER-TOKEN PIC S9(8) COMP VALUE ZERO.
call_type 03 DPL-REQUEST PIC S9(8) COMP VALUE 6.
pipe_token 01 PIPE-TOKEN PIC S9(8) COMP VALUE ZERO.
     
pgmname 01 TARGET-PROGRAM PIC X(8) VALUE "DFHœAXCS".
commarea 01 COMMAREA. (structure)
commarea_len 01 COMM-LENGTH PIC S9(8) COMP VALUE 98.
data_len 01 DATA-LENGTH PIC S9(8) COMP VALUE 18.
transid 01 TARGET-TRANSID PIC X(4) VALUE "EXCI".
     
dpl_retarea 01 EXCI-DPL-RETAREA. (structure)
dpl_opts 01 SYNCONRETURN PIC X VALUE X'80'.

The variable used for the null address is defined in the LINKAGE SECTION:

       LINKAGE SECTION.
         01  NULL-PTR         USAGE IS POINTER.

Using the data names specified in the WORKING-STORAGE SECTION, and the NULL-PTR name as described in the LINKAGE SECTION, the following invocation of the DPL function omits the uowid and the userid parameters, and replaces them in the parameter list with the NULL-PTR variable:
       DPL-SECTION.
      *
           SET ADDRESS OF NULL-PTR TO NULLS.
      *
           CALL 'DFHXCIS' USING  VERSION-1   EXCI-RETURN-CODE  USER-TOKEN
                               DPL-REQUEST    PIPE-TOKEN   TARGET-PROGRAM
                               COMMAREA       COMM-LENGTH  DATA-LENGTH
                               TARGET-TRANSID NULL-PTR     NULL-PTR
                               EXCI-DPL-RETAREA    SYNCONRETURN.
This example is taken from the CICS-supplied sample external CICS® interface program, DFH0CXCC, which is supplied in CICSTS53.CICS.SDFHSAMP. For an example of how to omit the same parameters from the DPL call in the other supported languages, see the following sample programs:
DFH$AXCC
The assembler sample
DFH$PXCC
The PL/I sample
DFH$DXCC
The C sample.