COBOL

In Figure 1, the symbolic feedback code file CEEIGZCT is accessed and a call is made to CEESDEXP (exponential base e). The first 8 bytes of the feedback code returned are tested against the symbolic feedback code CEE1UR to ensure that the input parameter is within the valid range for CEESDEXP. The symbolic feedback code table for CEESDEXP is listed in z/OS Language Environment Programming Reference. A message is displayed if the input parameter is out of range.

Figure 1. COBOL example testing for CEESDEXP symbolic feedback code CEE1UR
CBL LIB,QUOTE
      *************************************************
      *                                               *
      *  IBM Language Environment                     *
      *                                               *
      *  Licensed Materials - Property of IBM         *
      *                                               *
      *  5645-001 5688-198                            *
      *  (C) Copyright IBM Corp. 1991, 1997           *
      *  All Rights Reserved                          *
      *                                               *
      *  US Government Users Restricted Rights - Use, *
      *  duplication or disclosure restricted by GSA  *
      *  ADP Schedule Contract with IBM Corp.         *
      *                                               *
      *************************************************
      *Module/File Name: IGZTSFC
      *************************************************
      *                                               *
      * CTDEMO -  This routine assigns values to a    *
      *           condition token.                    *
      *                                               *
      *************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. CTDEMO.

       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 FBC.
           02  Condition-Token-Value.
           COPY  CEEIGZCT.
               03  Case-1-Condition-ID.
                   04  Severity    PIC S9(4) BINARY.
                   04  Msg-No      PIC S9(4) BINARY.
               03  Case-2-Condition-ID
                         REDEFINES Case-1-Condition-ID.
                   04  Class-Code  PIC S9(4) BINARY.
                   04  Cause-Code  PIC S9(4) BINARY.
               03  Case-Sev-Ctl    PIC X.
               03  Facility-ID     PIC XXX.
           02  I-S-Info            PIC S9(9) BINARY.
       01 X COMP-2 VALUE +2.0E+02.
       01 Y COMP-2.
       PROCEDURE DIVISION.
           CALL "CEESDEXP" USING X FBC Y.
           IF CEE1UR of FBC THEN
               DISPLAY "Argument X out of range"
                       " for CEEDEXP"
           END-IF

           GOBACK.

It is important that symbolic feedback codes be compared with only the first 8 bytes of the 12-byte condition token. To this end, you must code the COPY statements for the symbolic feedback code declarations in the right place within the condition token declaration.

In Figure 1, for example, symbolic feedback code CEE1UR is compared to the first 8 bytes of condition token FBC because of the correct placement of the COPY statements.

It is wrong to place the COPY statements before the declaration of Condition-Token-Value as shown in Figure 2, because the 8-byte symbolic feedback code blank-padded (X'40') to a length of 12 bytes would be compared to the full 12-byte condition token. The comparison would always fail, because the blanks would not match the ISI data in the last 4 bytes of the condition token.

Figure 2. Wrong placement of COBOL COPY statements for testing feedback code
       01 FBC
           COPY CEEIGZCT.                    <-----+  Incorrect
           COPY IGZIGZCT.                    <-----+  Incorrect
           02  Condition-Token-Value
               03  Case-1-Condition-ID.
                   04  Severity    PIC S9(4) BINARY.
                   04  Msg-No      PIC S9(4) BINARY.
               03  Case-2-Condition-ID
                         REDEFINES Case-1-Condition-ID.
                   04  Class-Code  PIC S9(4) BINARY.
                   04  Cause-Code  PIC S9(4) BINARY.
               03  Case-Sev-Ctl    PIC X.
               03  Facility-ID     PIC XXX.
           02  I-S-Info            PIC S9(9) BINARY.
⋮