CEE3GRO—Get offset of condition

The CEE3GRO service returns the offset within a failing routine of the most recent condition. If there are nested conditions, the most recently signaled condition is returned.
Read syntax diagramSkip visual syntax diagram
Syntax

>>-CEE3GRO--(--cond_offset--,--fc--)---------------------------><

cond_offset (output)
An INT4 data type that, upon completion of this service, contains the offset within a failing routine of the most recent condition.
fc (output, optional)
A 12-byte feedback code, optional in some languages, that indicates the result of this service. If you choose to omit this parameter, refer to Invoking callable services for the appropriate syntax to indicate that the feedback code was omitted.

The following symbolic conditions can result from this service:

Code Severity Message number Message text
CEE000 0 The service completed successfully.
CEE35S 1 3260 No condition was active when a call to a condition management routine was made.

Examples

  1. Following is an example of CEE3GRO called by COBOL.
    CBL  LIB,QUOTE,NOOPT
          *Module/File Name: IGZT3GRO
          ************************************************
          **                                            **
          ** DRV3GRO - Register a condition handler     **
          **           that calls CEE3GRO to determine  **
          **           the offset in the program that   **
          **           incurred the condition.          **
          **                                            **
          ************************************************
           IDENTIFICATION DIVISION.
           PROGRAM-ID.  DRV3GRO.
    
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           01  ROUTINE      PROCEDURE-POINTER.
           01  DENOMINATOR  PIC S9(9) BINARY.
           01  NUMERATOR    PIC S9(9) BINARY.
           01  RATIO        PIC S9(9) BINARY.
           01  TOKEN        PIC S9(9) BINARY VALUE 0.
           01  FC.
    
           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.
    
           PROCEDURE DIVISION.       REGISTER-HANDLER.
          *************************************************
          ** Register handler
          *************************************************
               SET ROUTINE TO ENTRY "CBL3GRO".
               CALL "CEEHDLR" USING ROUTINE, TOKEN, FC.
               IF NOT CEE000 of FC THEN
                  DISPLAY "CEEHDLR failed with msg "
                          Msg-No of FC UPON CONSOLE
                  STOP RUN
               END-IF.    RAISE-CONDITION.
          *************************************************
          ** Cause a zero-divide condition
          *************************************************
               MOVE 0 TO DENOMINATOR.
               MOVE 1 TO NUMERATOR.
               DIVIDE NUMERATOR BY DENOMINATOR
                  GIVING RATIO.
    
           UNREGISTER-HANDLER.
          *************************************************
          ** Unregister handler
          *************************************************
               CALL "CEEHDLU" USING ROUTINE, FC.
               IF NOT CEE000 of FC THEN
                  DISPLAY "CEEHDLU failed with msg "
                          Msg-No of FC UPON CONSOLE
                  STOP RUN
               END-IF.
    
               STOP RUN.
           END PROGRAM DRV3GRO.
    
          ************************************************
          **                                            **
          ** CBL3GRO - Call CEE3GRO to get the offset   **
          **           in the routine that incurred     **
          **           the condition.                   **
          **                                            **
          ************************************************
    
           IDENTIFICATION DIVISION.
           PROGRAM-ID.  CBL3GRO.
    
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           01  ROFFSET  PIC S9(9) BINARY.
           01  FC.
               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.      
     LINKAGE SECTION.
           01  TOKEN        PIC S9(9) BINARY.
           01  RESULT       PIC S9(9) BINARY.
               88  RESUME   VALUE 10.
           01  CURCOND.
               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  NEWCOND.
               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.
    
           PROCEDURE DIVISION USING CURCOND, TOKEN,
                                    RESULT, NEWCOND.
           PARA-CBL3GRO.
               CALL "CEE3GRO" USING ROFFSET, FC.
               IF CEE000 of FC THEN
                  DISPLAY "Offset in routine which "
                          "incurred the condition is:  "
                          ROFFSET
               ELSE
                  DISPLAY "CEE3GRO failed with msg "
                          Msg-No of FC UPON CONSOLE
               END-IF.
    
           PARA-HANDLER.
          *************************************************
          **  In user handler - resume execution
          *************************************************
               SET RESUME TO TRUE.
    
               GOBACK.
           END PROGRAM CBL3GRO.
  2. Following is an example of CEE3GRO called by PL/I.
    *Process lc(101),opt(0),s,map,list,stmt,a(f),ag;
    *Process macro;
     DRV3GRO: Proc Options(Main);
    
       /*Module/File Name: IBM3GRO                       */
       /***************************************************
        **                                                *
        ** DRV3GRO - Register a condition handler that    *
        **           calls CEE3GRO to determine           *
        **           the offset in the routine that       *
        **           incurred the condition.              *
        **                                                *
        **************************************************/
    
        %include CEEIBMCT;
        %include CEEIBMAW;
        declare 01 FBCODE    feedback;
        declare DENOMINATOR  real fixed binary(31,0);
        declare NUMERATOR    real fixed binary(31,0);
        declare RATIO        real fixed binary(31,0);
        declare PLI3GRO      external entry;
        declare U_PTR        pointer;
        declare 01 U_DATA,
                  03 U_CNTL  fixed binary(31,0),
                  03 U_TOK   pointer;
    
        U_PTR = addr(U_DATA);
        U_CNTL = 0;
    
        /* Set Resume Point               */
    
        Display('Setting resume point via CEE3SRP');
        Call CEE3SRP(U_TOK,FBCODE);
        Display('After call to CEE3SRP ... Resume point');
        If U_CNTL = 0
          Do;
            Display('First time through...');
    
            /* Register User Handler  */
    
            Display('Registering user handler');
            Call CEEHDLR(PLI3GRO, U_PTR, FBCODE);
            If FBCHECK(FBCODE, CEE000) then
              Do;
                /* Cause a zero-divide condition  */
                DENOMINATOR = 0;
                NUMERATOR = 1;
                RATIO = NUMERATOR/DENOMINATOR;
              End;
            Else
              Do;
                Display('CEEHDLR failec with msg');
                Display(MsgNo);
              End;
          End;
        Else
          Display('2nd time...User can do whatever');
    
        /* Unregister handler  */
    
        Call CEEHDLU(PLI3GRO, FBCODE);
        If FBCHECK (FBCODE, CEE000) Then
          Display('Main: unregistered PLI3GRO);
        Else
          Do;
            Display('CEEHDLU failed with msg ');
            Display(MsgNo);
          End;
     End DRV3GRO;*Process lc(101),opt(0),s,map,list,stmt,a(f),ag;
    *Process macro;
     PLI3GRO: Proc (PTR1,PTR2,PTR3,PTR4);
       /***************************************************
        **                                                *
        ** PLI3GRO - Call CEE3GRO to get the offset in    *
        **           the routine that incurred the        *
        **           condition.                           *
        **                                                *
        **************************************************/
      
        %include CEEIBMCT;
        %include CEEIBMAW;
        declare (PTR1,PTR2,PTR3,PTR4) pointer;
        declare 01 CURCOND based(PTR1) feedback;
        declare TOKEN      pointer based(PTR2);
        declare RESULT     fixed binary(31,0) based(PTR3);
        declare 01 NEWCOND based(PTR4) feedback;
        declare ROFFSET    real fixed binary(31,0);
        declare 01 FBCODE  feedback;
        declare 01 U_DATA  based(TOKEN),
                 03 U_CNTL fixed binary(31,0),
                 03 U_TOK  pointer;
    
             Call CEE3GRO(ROFFSET,FBCODE);
             If fbcheck (fbcode, cee000) Then
               Do;
                 Display('Routine offset which incurred');
                 Display('the condition is: ');
                 Display(ROFFSET);
               End;
             Else
               Do;
                 Display('CEE3GRO failed with msg ');
                 Display(FBCODE.MsgNo);
               End;
    
       /***************************************************
        ** In user handler - resume execution             *
        **************************************************/
    
             RESULT = 10;
             Call CEEMRCE(U_TOK,FBCODE);
             U_CNTL = 1;
             Return;
     End PLI3GRO;