Example illustrating retrieval of q_data

The following example shows how the abend code can be retrieved from q_data by invoking the CEEGQDT callable service within a CEEHDLR-established condition handler written in COBOL. For an example of a working program that includes the following code, see member IGZTCHDL in library CEE.SCEESAMP.
   ID DIVISION.
    PROGRAM-ID. GETQDATA.
   ENVIRONMENT DIVISION.
   DATA DIVISION.
    WORKING-STORAGE SECTION.

  ***************************************************************
  *  Data items for retrieving q_data, including the            *
  *  q_data_token, q_data pointers, and the q_data itself.      *
  *  Q-DATA-TOKEN is a pointer to a list of pointers that point *
  *  to the q_data.                                             *
  ***************************************************************
    77  Q-DATA-TOKEN   USAGE POINTER.

    LINKAGE SECTION.
  ***************************************************************
  *  Mapping for the 12-byte Language Environment feedback      *
  *  code, which holds information about the condition that     *
  *  caused this condition handler to get control.  It is       *
  *  passed from the Language Environment condition manager.    *
  ***************************************************************
    01  CURRENT-CONDITION.
      05  FIRST-8-BYTES.
          COPY CEEIGZCT.
          COPY IGZIGZCT.
          10  C-SEVERITY PIC 9(4) USAGE BINARY.
          10  C-MSGNO    PIC 9(4) USAGE BINARY.
          10  C-FC-OTHER PIC X.
          10  C-FAC-ID   PIC X(3).
      05  C-I-S-INFO PIC 9(9) USAGE BINARY.

  ***************************************************************
  *  TOKEN is the 4-byte token passed from the condition        *
  *  manager.  It can contain data from the program that        *
  *  registered this condition handler.                         *
  ***************************************************************
    01  TOKEN               PIC X(4).
  ***************************************************************
  *  RESULT-CODE is passed back to the Language Environment     *
  *  condition manager to indicate what it should do            *
  *  with this condition:  resume, percolate, or promote.       *
  ***************************************************************
    01  RESULT-CODE         PIC S9(9) USAGE BINARY.
      88 RESUME             VALUE 10.
      88 PERCOLATE          VALUE 20.
      88 PROMOTE            VALUE 30.
      88 PROMOTE-SF         VALUE 31.
  ***************************************************************
  *  NEW-CONDITION is the 12-byte feedback code for the new     *
  *  condition that must be specified for RESULT-CODE values of *
  *  30, 31, or 32, indicating that a new condition is to be    *
  *  promoted.                                                  *
  ***************************************************************
    01  NEW-CONDITION       PIC X(12).


   ***************************************************************
  *  Data items for retrieving q_data, including the            *
  *  q_data_token, q_data pointers, and the q_data itself,      *
  *  which consists of a parm count, an abend code, and a       *
  *  reason code.                                               *
  ***************************************************************
    01  Q-DATA-PTRS    USAGE POINTER.
      05  Q-DATA-PARM-COUNT-PTR.
      05  Q-DATA-ABEND-CODE-PTR.
      05  Q-DATA-REASON-CODE-PTR.
    01  PARM-COUNT          PIC S9(9) USAGE BINARY.
    01  ABEND-CODE          PIC S9(9) USAGE BINARY.
    01  REASON-CODE         PIC S9(9) USAGE BINARY.


    PROCEDURE DIVISION USING CURRENT-CONDITION TOKEN RESULT-CODE
                             NEW-CONDITION.

        EVALUATE TRUE
  *****************************************************************
  *       When Language Environment fields a system or user       *
  *       abend, condition CEE35I (corresponding to message       *
  *       number 3250) is raised.  The following code uses        *
  *       callable service CEEGQDT to get the q_data and examine  *
  *       the abend code.                                         *
  *****************************************************************
          WHEN CEE35I OF CURRENT-CONDITION
            PERFORM
  *****************************************************************
  *           Get q_data for the condition we are handling.       *
  *****************************************************************
              CALL "CEEGQDT" USING CURRENT-CONDITION
                                 Q-DATA-TOKEN FC
              IF SEVERITY > 0 THEN
                 DISPLAY "CALL to CEEGQDT failed with "
                         "Severity = " SEVERITY
                 DISPLAY "                and message "
                         "number   = " MSGNO
                 GOBACK
              END-IF
  *****************************************************************
  *           Set up pointers to get ABEND-CODE.                  *
  *****************************************************************
              SET ADDRESS OF Q-DATA-PTRS TO Q-DATA-TOKEN
              SET ADDRESS OF ABEND-CODE TO Q-DATA-ABEND-CODE-PTR
  *****************************************************************
  *           Select handler code based on ABEND-CODE.            *
  *****************************************************************
              EVALUATE ABEND-CODE
                 WHEN 777
                   DISPLAY "Severe Error!  Condition Handling "
                           "should not get control for IMS Abends"
                   SET PERCOLATE TO TRUE
                 WHEN OTHER
                   CONTINUE
              END-EVALUATE
            END-PERFORM

  *****************************************************************
  *       Handle all other conditions here.                       *
  *****************************************************************
          WHEN OTHER
            CONTINUE

        END-EVALUATE

     END-PROGRAM GETQDATA.