CEEMRCE—Move resume cursor explicit

The CEEMRCE service resumes execution of a user routine at the location established by CEE3SRP. CEEMRCE is designed to be called from a user condition handler and works only in conjunction with the CEE3SRP service.
Read syntax diagramSkip visual syntax diagram
Syntax

>>-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 symbolic conditions can 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

  • Exit DSA routines are invoked as the resume cursor is moved back across stack frames.
  • 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. An example of CEEMRCE called by COBOL:
           CBL NODYNAM APOST
           IDENTIFICATION DIVISION.
           PROGRAM-ID. PGM2.
          *Module/File Name: IGZTMRCE
          *__________________________________________*
          *                                          *
          * 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(02) COMP-3 VALUE 0.
               05  UCH1      PIC  X(08) VALUE 'UCH1    '.
               05  PGM3      PIC  X(08) VALUE 'PGM3    '.
               05  CEEHDLR   PIC  X(08) VALUE 'CEEHDLR '.
               05  CEE3SRP   PIC  X(08) VALUE 'CEE3SRP '.
               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.
    
               SET UCH-ROUTINE TO ENTRY 'UCH1'.
          *__________________________________________*
          *                                          *
          * Register the condition handler, UCH1.    *
          *__________________________________________*
    
               CALL CEEHDLR USING UCH-ROUTINE, TOKEN, FC.
               IF CASE-1 NOT = LOW-VALUE
                   GOBACK.
               PERFORM COMPUTE-LOOP 3 TIMES.
               CALL PGM3 USING RECOVERY-AREA.
               SET RECOVERY-POINT TO NULL.
               GOBACK.       COMPUTE-LOOP.
               IF FIRST-TIME-88
                   MOVE 'OFF' TO FIRST-TIME-SW
          *__________________________________________*
          *                                          *
          * Set up a new resume point.               *
          *__________________________________________*
    
                   CALL CEE3SRP USING RECOVERY-POINT,
                                      CASE-1
    
                                      SERVICE LABEL 
    
                   IF CASE-1 NOT = LOW-VALUE
                       GOBACK.
    
               IF ERROR-INDICATOR = 'E'
                   MOVE SPACE TO ERROR-INDICATOR
                   MOVE 1 TO ANSWER.
    
          * Application code may go here.
    
               COMPUTE ANSWER = 1 / ANSWER.
    
          * Put application code here.
    
           CBL NODYNAM APOST
           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(02) COMP-3 VALUE 0.
               05  CEEHDLR   PIC  X(08) VALUE 'CEEHDLR '.
               05  CEE3SRP   PIC  X(08) VALUE 'CEE3SRP '.
               05  TOKEN     PIC S9(09) BINARY.
               05  SEV PIC -9(05).
               05  MSG PIC -9(05).
               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.
    
               PERFORM COMPUTE-LOOP 3 TIMES.
               SET RECOVERY-POINT TO NULL.
               GOBACK.
    
           COMPUTE-LOOP.
               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
                       GOBACK.
    
               IF ERROR-INDICATOR = 'E'
                   MOVE SPACE TO ERROR-INDICATOR
                   MOVE 1 TO ANSWER.
    
          * Application code may go here.
    
               COMPUTE ANSWER = 1 / ANSWER.
    
          * Put application code here.
    
           CBL NODYNAM APOST
           IDENTIFICATION DIVISION.
           PROGRAM-ID. 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.
    
           01 CEEMRCE       PIC X(08) VALUE 'CEEMRCE '.
           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.
    
               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
                   GOBACK.
               MOVE +10 TO RESULT-CODE.
    
               GOBACK.
  2. An example of CEEMRCE called by PL/I:
    *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;