CEEMRCE—Move resume cursor explicit

The CEEMRCE service resumes execution of a user routine at the location established by CEE3SRP. CEEMRCE is called from a user condition handler and works only in conjunction with the CEE3SRP service.
Read syntax diagramSkip visual syntax diagram CEEMRCE ( resume_token , fc )
resume_token (input)
An INT4 data type that contains a token, returned from the CEE3SRP service, representing the resume point in the user routine.
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 table lists the symbolic conditions that might result from this service.

Code Severity Message number Message text
CEE000 0 The service completed successfully.
CEE07V 2 0255 The first parameter passed to CEEMRCE was an unrecognized label.

Usage notes

  1. Exit DSA routines are invoked as the resume cursor is moved back across stack frames.
  2. When a resume is requested, the state of the machine indicated in the machine state block is established prior to entry at the resume point.

For more information

Examples

  1. Start of changeIn this example, CEEMRCE is called by a single COBOL program.

    PGM1 registers a condition handler (UCH1) using CEEHDLR and sets a resume point using CEE3SRP. When a condition occurs (in this example, ANSWER = 1 / 0), UCH1 gets a control to handle the condition and resumes the program execution to the resume point in PGM1.

    To try the following example, compile PGM1 and UCH1 and statically link them together to generate a program object (load module) named PGM1. Then run PGM1.

    Module/File Name: PGM1
    
           CBL NODYNAM
           IDENTIFICATION DIVISION.
           PROGRAM-ID. PGM1.
          *Module/File Name: PGM1
          *------------------------------------------*
          * Sample program using CEE3SRP and CEEMRCE.*
          * PGM1 registers user-written condition    *
          * handler UCH1 using CEEHDLR.  It          *
          * sets a resume point using CEE3SRP.       *
          *------------------------------------------*
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           01  RECOVERY-AREA EXTERNAL.
               05  RECOVERY-POINT            POINTER.
               05  ERROR-INDICATOR           PIC X(01).
           01 UCH-ROUTINE      PROCEDURE-POINTER.
           01  FIELDS.
               05  FIRST-TIME-SW    PIC X(03) VALUE ' ON'.
                   88 FIRST-TIME-88           VALUE ' ON'.
               05  ANSWER    PIC S9(01) COMP-3 VALUE 0.
               05  TOKEN     PIC S9(09) BINARY.
               05  FC.
                   10  CASE-1.
                       15  SEVERITY PIC S9(04) BINARY.
                       15  MSG-NO   PIC S9(04) BINARY.
                   10  SEV-CTL      PIC  X(01).
                   10  FACILITY-ID  PIC  X(03).
                   10  I-S-INFO     PIC S9(09) BINARY.
    
           PROCEDURE DIVISION.
               DISPLAY "PGM1: === BEGINS ==="
               SET UCH-ROUTINE TO ENTRY 'UCH1'.
          *------------------------------------------*
          *    Register the condition handler, UCH1. *
          *------------------------------------------*
               CALL 'CEEHDLR' USING UCH-ROUTINE, TOKEN, FC.
               IF CASE-1 NOT = LOW-VALUE
                   DISPLAY "PGM1: ERROR: CALL CEEHDLR FAILED"
                   GOBACK.
               DISPLAY "PGM1: === CALL COMPUTE-LOOP 2 TIMES ==="
               DISPLAY " "
               PERFORM COMPUTE-LOOP 2 TIMES.
               SET RECOVERY-POINT TO NULL.
               DISPLAY "PGM1: === ENDS ==="
               GOBACK.
    
            COMPUTE-LOOP.
               DISPLAY "PGM1: COMPUTE-LOOP BEGINS"
               IF FIRST-TIME-88
                   MOVE 'OFF' TO FIRST-TIME-SW
          *------------------------------------------*
          *        Set up a resume point.            *
          *------------------------------------------*
                   CALL 'CEE3SRP' USING RECOVERY-POINT, FC
                   SERVICE LABEL
                   IF CASE-1 NOT = LOW-VALUE
                       DISPLAY "PGM1: ERROR: CALL CEE3SRP FAILED"
                       GOBACK
                   END-IF
                   DISPLAY "PGM1: RESUME POINT"
               END-IF
    
               IF ERROR-INDICATOR = 'E'
                   MOVE SPACE TO ERROR-INDICATOR
                   MOVE 1 TO ANSWER
               END-IF
    
          * Application code may go here.
               DISPLAY "PGM1: BEFORE DOING 1 / " ANSWER.
               COMPUTE ANSWER = 1 / ANSWER.
               DISPLAY "PGM1: AFTER  DOING 1 / " ANSWER.
    
               DISPLAY "PGM1: COMPUTE-LOOP ENDS"
               DISPLAY " "
               EXIT.
           END PROGRAM PGM1.
    
    Module/File Name: UCH1
    
           CBL NODYNAM APOST
           IDENTIFICATION DIVISION.
           PROGRAM-ID. UCH1.
          *Module/File Name: UCH1
          *------------------------------------------*
          * Sample user condition handler using      *
          * CEEMRCE.  This program sets an error     *
          * flag for the program-in-error to query   *
          * and issues a call to CEEMRCE to return   *
          * control to the statement following the   *
          * call to CEE3SRP.                         *
          *------------------------------------------*
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           01  RECOVERY-AREA EXTERNAL.
               05 RECOVERY-POINT         POINTER.
               05 ERROR-INDICATOR        PIC X(01).
           01  FC.
               10  CASE-1.
                   15  SEVERITY PIC S9(04) BINARY.
                   15  MSG-NO   PIC S9(04) BINARY.
               10  SEV-CTL      PIC  X(01).
               10  FACILITY-ID  PIC  X(03).
               10  I-S-INFO     PIC S9(09) BINARY.
    
           LINKAGE SECTION.
           01  CURRENT-CONDITION         PIC  X(12).
           01  TOKEN                     PIC  X(04).
           01  RESULT-CODE             PIC S9(09) BINARY.
               88  RESUME                 VALUE +10.
               88  PERCOLATE              VALUE +20.
               88  PERC-SF                VALUE +21.
               88  PROMOTE                VALUE +30.
               88  PROMOTE-SF             VALUE +31.
           01  NEW-CONDITION             PIC  X(12).
    
           PROCEDURE DIVISION  USING CURRENT-CONDITION,
                                     TOKEN,
                                     RESULT-CODE,
                                     NEW-CONDITION.
               DISPLAY "      > UCH1: RECOVERY BEGINS"
               DISPLAY "      > UCH1: MOVE E TO ERROR-INDICATOR"
               MOVE 'E' TO ERROR-INDICATOR.
          *------------------------------------------*
          *    Call CEEMRCE to return control to the *
          *    last resume point.                    *
          *------------------------------------------*
               CALL 'CEEMRCE' USING RECOVERY-POINT, FC.
               IF CASE-1 NOT = LOW-VALUE
                   DISPLAY "      > UCH1: ERROR: CALL CEEMRCE FAILED"
                   GOBACK.
               MOVE +10 TO RESULT-CODE.
               DISPLAY "      > UCH1: GO BACK TO RESUME POINT"
               GOBACK.
           END PROGRAM UCH1.
    
    Actual program output
    PGM1: === BEGINS ===
    PGM1: === CALL COMPUTE-LOOP 2 TIMES ===
    
    PGM1: COMPUTE-LOOP BEGINS
    PGM1: RESUME POINT
    PGM1: BEFORE DOING 1 / 0
          > UCH1: RECOVERY BEGINS
          > UCH1: MOVE E TO ERROR-INDICATOR
          > UCH1: GO BACK TO RESUME POINT
    PGM1: RESUME POINT
    PGM1: BEFORE DOING 1 / 1
    PGM1: AFTER  DOING 1 / 1
    PGM1: COMPUTE-LOOP ENDS
    
    PGM1: COMPUTE-LOOP BEGINS
    PGM1: BEFORE DOING 1 / 1
    PGM1: AFTER  DOING 1 / 1
    PGM1: COMPUTE-LOOP ENDS
    
    PGM1: === ENDS ===
    
    End of change
  2. Start of changeIn this example, CEEMRCE is called by multiple COBOL programs.

    Using the same UCH1 in the previous example, PGM2 does the same as PGM1 but additionally calls PGM3 where a new resume point is set and a condition occurs. This example shows that multiple resume points can be dynamically set during execution although only one resume point can be active.

    To try the following example, compile PGM2 and UCH1 and statically link them together to generate a program object (load module) named PGM2. Compile and link PGM3 to generate a program object named PGM3. Make sure that PGM3 is accessible by PGM2 and then run PGM2.

    Module/File Name: PGM2
    
           CBL NODYNAM
           IDENTIFICATION DIVISION.
           PROGRAM-ID. PGM2.
          *Module/File Name: PGM2
          *------------------------------------------*
          * Sample program using CEE3SRP and CEEMRCE.*
          * PGM2 registers user-written condition    *
          * handler UCH1 using CEEHDLR.  It          *
          * sets a resume point using CEE3SRP. After *
          * incurring a condition and returning      *
          * to PGM2, PGM3 is called.  PGM3 sets up   *
          * new resume point, does a divide-by-zero, *
          * and after resuming in PGM3, resets the   *
          * resume point to PGM2 and does a GOBACK.  *
          *------------------------------------------*
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           01  RECOVERY-AREA EXTERNAL.
               05  RECOVERY-POINT            POINTER.
               05  ERROR-INDICATOR           PIC X(01).
           01 UCH-ROUTINE      PROCEDURE-POINTER.
           01  FIELDS.
               05  FIRST-TIME-SW    PIC X(03) VALUE ' ON'.
                   88 FIRST-TIME-88           VALUE ' ON'.
               05  ANSWER    PIC S9(01) COMP-3 VALUE 0.
               05  PGM3      PIC  X(08) VALUE 'PGM3    '.
               05  TOKEN     PIC S9(09) BINARY.
               05  FC.
                   10  CASE-1.
                       15  SEVERITY PIC S9(04) BINARY.
                       15  MSG-NO   PIC S9(04) BINARY.
                   10  SEV-CTL      PIC  X(01).
                   10  FACILITY-ID  PIC  X(03).
                   10  I-S-INFO     PIC S9(09) BINARY.
    
           PROCEDURE DIVISION.
               DISPLAY "PGM2: === BEGINS ==="
               SET UCH-ROUTINE TO ENTRY 'UCH1'.
          *------------------------------------------*
          *    Register the condition handler, UCH1. *
          *------------------------------------------*
               CALL 'CEEHDLR' USING UCH-ROUTINE, TOKEN, FC.
               IF CASE-1 NOT = LOW-VALUE
                   DISPLAY "PGM2: ERROR: CALL CEEHDLR FAILED"
                   GOBACK.
               DISPLAY "PGM2: === CALL COMPUTE-LOOP 2 TIMES ==="
               DISPLAY " "
               PERFORM COMPUTE-LOOP 2 TIMES.
    
               DISPLAY "PGM2: === CALL PGM3 ==="
               CALL PGM3 USING RECOVERY-AREA.
    
               SET RECOVERY-POINT TO NULL.
               DISPLAY "PGM2: === ENDS ==="
               GOBACK.
    
            COMPUTE-LOOP.
               DISPLAY "PGM2: COMPUTE-LOOP BEGINS"
               IF FIRST-TIME-88
                   MOVE 'OFF' TO FIRST-TIME-SW
          *------------------------------------------*
          *        Set up a resume point.            *
          *------------------------------------------*
                   CALL 'CEE3SRP' USING RECOVERY-POINT, FC
                   SERVICE LABEL
                   IF CASE-1 NOT = LOW-VALUE
                       DISPLAY "PGM2: ERROR: CALL CEE3SRP FAILED"
                       GOBACK
                   END-IF
                   DISPLAY "PGM2: RESUME POINT"
               END-IF
    
               IF ERROR-INDICATOR = 'E'
                   MOVE SPACE TO ERROR-INDICATOR
                   MOVE 1 TO ANSWER
               END-IF
    
          * Application code may go here.
               DISPLAY "PGM2: BEFORE DOING 1 / " ANSWER.
               COMPUTE ANSWER = 1 / ANSWER.
               DISPLAY "PGM2: AFTER  DOING 1 / " ANSWER.
    
               DISPLAY "PGM2: COMPUTE-LOOP ENDS"
               DISPLAY " "
               EXIT.
           END PROGRAM PGM2.
    

    Module / File Name: UCH1

    The code is the same as UCH in the previous example.

    Module/File Name: PGM3
    
           CBL NODYNAM
           IDENTIFICATION DIVISION.
           PROGRAM-ID. PGM3.
          *------------------------------------------*
          * Sample program using CEE3SRP and CEEMRCE.*
          * PGM2 registered UCH1. This program sets a*
          * new resume point, does a divide-by-zero, *
          * and after resuming in PGM3, resets the   *
          * resume point to PGM2 and does a GOBACK.  *
          *------------------------------------------*
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           01  RECOVERY-AREA EXTERNAL.
               05  RECOVERY-POINT            POINTER.
               05  ERROR-INDICATOR           PIC X(01).
           01 UCH-ROUTINE      PROCEDURE-POINTER.
           01  FIELDS.
               05  FIRST-TIME-SW    PIC X(03) VALUE ' ON'.
                   88 FIRST-TIME-88           VALUE ' ON'.
               05  ANSWER    PIC S9(01) COMP-3 VALUE 0.
               05  TOKEN     PIC S9(09) BINARY.
               05  FC.
                   10  CASE-1.
                       15  SEVERITY PIC S9(04) BINARY.
                       15  MSG-NO   PIC S9(04) BINARY.
                   10  SEV-CTL      PIC  X(01).
                   10  FACILITY-ID  PIC  X(03).
                   10  I-S-INFO     PIC S9(09) BINARY.
    
           PROCEDURE DIVISION.
               DISPLAY "  PGM3: ----- BEGINS -------------------------"
               DISPLAY "  PGM3: ----- CALL COMPUTE-LOOP2 2 TIMES -----"
               PERFORM COMPUTE-LOOP2 2 TIMES.
               SET RECOVERY-POINT TO NULL.
               DISPLAY "  PGM3: ----- ENDS ---------------------------"
               GOBACK.
    
           COMPUTE-LOOP2.
               DISPLAY " "
               DISPLAY "  PGM3: COMPUTE-LOOP2 BEGINS"
               IF FIRST-TIME-88
                   MOVE 'OFF' TO FIRST-TIME-SW
          *------------------------------------------*
          * Set new resume point.                    *
          *------------------------------------------*
                   CALL 'CEE3SRP' USING RECOVERY-POINT, FC
                   SERVICE LABEL
                   IF CASE-1 NOT = LOW-VALUE
                       DISPLAY "  PGM3: ERROR: CALL CEE3SRP FAILED"
                       GOBACK
                   END-IF
                   DISPLAY "  PGM3: RESUME POINT"
               END-IF
    
               IF ERROR-INDICATOR = 'E'
                   MOVE SPACE TO ERROR-INDICATOR
                   MOVE 1 TO ANSWER
               END-IF
    
          * Application code may go here.
               DISPLAY "  PGM3: BEFORE DOING 1 / " ANSWER.
               COMPUTE ANSWER = 1 / ANSWER.
               DISPLAY "  PGM3: AFTER  DOING 1 / " ANSWER.
               DISPLAY "  PGM3: COMPUTE-LOOP2 ENDS"
               ExIT.
           END PROGRAM PGM3.
    
    Actual program output
    
    PGM2: === BEGINS ===
    PGM2: === CALL COMPUTE-LOOP 2 TIMES ===
    
    PGM2: COMPUTE-LOOP BEGINS
    PGM2: RESUME POINT
    PGM2: BEFORE DOING 1 / 0
          > UCH1: RECOVERY BEGINS
          > UCH1: MOVE E TO ERROR-INDICATOR
          > UCH1: GO BACK TO RESUME POINT
    PGM2: RESUME POINT
    PGM2: BEFORE DOING 1 / 1
    PGM2: AFTER  DOING 1 / 1
    PGM2: COMPUTE-LOOP ENDS
    
    PGM2: COMPUTE-LOOP BEGINS
    PGM2: BEFORE DOING 1 / 1
    PGM2: AFTER  DOING 1 / 1
    PGM2: COMPUTE-LOOP ENDS
    
    PGM2: === CALL PGM3 ===
      PGM3: ----- BEGINS -------------------------
      PGM3: ----- CALL COMPUTE-LOOP2 2 TIMES -----
    
      PGM3: COMPUTE-LOOP2 BEGINS
      PGM3: RESUME POINT
      PGM3: BEFORE DOING 1 / 0
          > UCH1: RECOVERY BEGINS
          > UCH1: MOVE E TO ERROR-INDICATOR
          > UCH1: GO BACK TO RESUME POINT
      PGM3: RESUME POINT
      PGM3: BEFORE DOING 1 / 1
      PGM3: AFTER  DOING 1 / 1
      PGM3: COMPUTE-LOOP2 ENDS
    
      PGM3: COMPUTE-LOOP2 BEGINS
      PGM3: BEFORE DOING 1 / 1
      PGM3: AFTER  DOING 1 / 1
      PGM3: COMPUTE-LOOP2 ENDS
      PGM3: ----- ENDS ---------------------------
    PGM2: === ENDS ===
    
    End of change
  3. In this example, CEEMRCE is called by a PL/I program.
    
    *Process lc(101),opt(0),s,map,list,stmt,a(f),ag;
    *Process macro;
     DRV3SRP: Proc Options(Main);
    
       /*Module/File Name: IBM3SRP                       */
       /***************************************************
        **                                                *
        ** DRV3SRP - Set an explicit resume point by      *
        **           calling CEE3SRP then registering a   *
        **           condition handler that calls CEEMRCE *
        **           to resume at the explicitly set      *
        **           resume point.                        *
        **                                                *
        **************************************************/
    
        %include CEEIBMCT;
        %include CEEIBMAW;
        declare 01 FBCODE   feedback;  /* Feedback token */
        declare DENOMINATOR fixed binary(31,0);
        declare NUMERATOR   fixed binary(31,0);
        declare RATIO       fixed binary(31,0);
        declare PLI3SRP     external entry;
        declare U_PTR       pointer;
        declare 01 U_DATA,
                  03 U_CNTL fixed binary(31),
                  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 CEE3SRP ... Resume point');
             If U_CNTL = 0 Then
               Do;
                 Display('First time through...');
    
                 Display('Registering user handler');
                 Call CEEHDLR(PLI3SRP, 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 failed with msg ');
                     Display(MsgNo);
                   End;
               End;
             Else
               Display('Second time through...');
    
             /* Unregister handler                 */         
    Call CEEHDLU(PLI3SRP, FBCODE);
             If FBCHECK(FBCODE, CEE000) Then
               Display('Main: unregistered PLI3SRP');
             Else
               Do;
                 Display('CEEHDLU failed with msg ');
                 Display(MsgNo);
               End;
     End DRV3SRP;
    
    *Process lc(101),opt(0),s,map,list,stmt,a(f),ag;
    *Process macro;
     PLI3SRP: Proc (PTR1,PTR2,PTR3,PTR4) Options(byvalue);
       /***************************************************
        **                                                *
        ** PLI3SRP - Call CEEMCRE to resume at the resume *
        **           point explicitly set in user         *
        **           program.                             *
        **                                                *
        **************************************************/
    
        %include CEEIBMCT;
        %include CEEIBMAW;
        declare (PTR1,PTR2,PTR3,PTR4) pointer;
        declare 01 CURCOND  based(PTR1) feedback;
        declare TOKEN       pointer based(PTR2);
        declare RESULT      fixed bin(31,0) based(PTR3);
        declare 01 NEWCOND  based(PTR4) feedback;
        declare 01 U_DATA   based(TOKEN),
                  03 U_CNTL fixed binary(31,0),
                  03 U_TOK  pointer;
        declare 01 FBCODE   feedback;
    
        Display('In user handler');
        RESULT = 10;
        Call CEEMRCE(U_TOK,FBCODE);
        Display(U_CNTL);
        U_CNTL = 1;
        Return;