Specifying the UIB (CICS online programs only)

The interface between your CICS® online program and DL/I passes additional information to your program in a user interface block (UIB). The UIB contains the address of the PCB list and any return codes your program must examine before checking the status code in the DB PCB.

When you issue the PCB call to obtain a PSB for your program, a UIB is created for your program. As with any area outside your program, you must include a definition of the UIB and establish addressability to it. CICS provides a definition of the UIB for all programming languages:

  • In COBOL programs, use the COPY DLIUIB statement.
  • In PL/I programs, use a %INCLUDE DLIUIB statement.
  • In assembler language programs, use the DLIUIB macro.

Three fields in the UIB are important to your program: UIBPCBAL, UIBFCTR, and UIBDLTR. UIBPCBAL contains the address of the PCB address list. Through it you can obtain the address of the PCB you want to use. Your program must check the return code in UIBFCTR (and possibly UIBDLTR) before checking the status code in the DB PCB. If the contents of UIBFCTR and UIBDLTR are not null, the content of the status code field in the DB PCB is not meaningful. The return codes are described in the topic "CICS-DL/I user interface block return codes" in IMS Version 15.4 Messages and Codes, Volume 4: IMSComponent Codes.

Immediately after the statement that defines the UIB in your program, you must define the PCB address list and the PCB mask.

The following code example shows how to use the COPY DLIUIB statement in a VS COBOL II program:

Defining the UIB, PCB address list, and the PCB mask for VS COBOL II

LINKAGE SECTION.
 
    COPY DLIUIB.
01  OVERLAY-DLIUIB REDEFINES DLIUIB.
    02  PCBADDR USAGE IS POINTER.
    02  FILLER PIC XX.
 
01  PCB-ADDRESSES.
    02  PCB-ADDRESS-LIST
            USAGE IS POINTER OCCURS 10 TIMES.
01  PCB1.
    02  PCB1-DBD-NAME PIC X(8).
    02  PCB1-SEG-LEVEL PIC XX.
        .
        .
        .

The COBOL COPY DLIUIB copybook

01  DLIUIB.
*                                   Address of the PCB addr list
    02  UIBPCBAL PIC S9(8) COMP.
*                                   DL/I return codes
    02  UIBRCODE.
*                                   Return codes
        03  UIBFCTR  PIC X.
            88  FCNORESP     VALUE ' '.
            88  FCNOTOPEN    VALUE ' '.
            88  FCINVREQ     VALUE ' '.
            88  FCINVPCB     VALUE ' '.
*                                   Additional information
        03  UIBDLTR  PIC X.
            88  DLPSBNF      VALUE ' '.
            88  DLTASKNA     VALUE ' '.
            88  DLPSBSCH     VALUE ' '.
            88  DLLANGCON    VALUE ' '.
            88  DLPSBFAIL    VALUE ' '.
            88  DLPSBNA      VALUE ' '.
            88  DLTERMNS     VALUE ' '.
            88  DLFUNCNS     VALUE ' '.
            88  DLINA        VALUE ' '.

The values placed in level 88 entries are not printable. They are described in the topic "CICS-DL/I User Interface Block Return Codes" in IMS Version 15.4 Messages and Codes, Volume 4: IMSComponent Codes. The meanings of the field names and their hexadecimal values are shown below:

FCNORESP
Normal response Value X'00'
FCNOTOPEN
Not open Value X'0C'
FCINVREQ
Invalid request Value X'08'
FCINVPCB
Invalid PCB Value X'10'
DLPSBNF
PSB not found Value X'01'
DLTASKNA
Task not authorized Value X'02'
DLPSBSCH
PSB already scheduled Value X'03'
DLLANGCON
Language conflict Value X'04'
DLPSBFAIL
PSB initialization failed Value X'05'
DLPSBNA
PSB not authorized Value X'06'
DLTERMNS
Termination not successful Value X'07'
DLFUNCNS
Function unscheduled Value X'08'
DLINA
DL/I not active Value X'FF'

The following code example shows how to define the UIB, PCB address list, and PCB mask for PL/I.

Defining the UIB, PCB address list, and the PCB mask for PL/I

DCL UIBPTR PTR;                     /* POINTER TO UIB              */
DCL 1 DLIUIB UNALIGNED BASED(UIBPTR),
                                    /* EXTENDED CALL USER INTFC BLK*/
  2 UIBPCBAL PTR,                   /* PCB ADDRESS LIST            */
  2 UIBRCODE,                       /* DL/I RETURN CODES           */
    3 UIBFCTR BIT(8) ALIGNED,       /* RETURN CODES                */
    3 UIBDLTR BIT(8) ALIGNED;       /* ADDITIONAL INFORMATION      */

The following code example shows how to define the UIB, PCB address list, and PCB mask for assembler language.

Defining the UIB, PCB address list, and the PCB mask for assembler language

DLIUIB   DSECT
UIB      DS    0F                  EXTENDED CALL USER INTFC BLK
UIBPCBAL DS    A                   PCB ADDRESS LIST
UIBRCODE DS    0XL2                DL/I RETURN CODES
UIBFCTR  DS    X                   RETURN CODE
UIBDLTR  DS    X                   ADDITIONAL INFORMATION
         DS    2X                  RESERVED
         DS    0F                  LENGTH IS FULLWORD MULTIPLE
UIBLEN   EQU   *-UIB               LENGTH OF UIB