IMS DB Restart (XRST)

The 'XRST' (Extended Restart) call is a DL/I function used to resume a batch program execution from the last established checkpoint after an abnormal termination. It restores position in the database and program variables (if stored in a restart area).

In a COBOL program, the 'XRST' call is made using the following syntax:

CALL 'CBLTDLI' USING
    DLI-XRST
    IO-PCB
    IO-AREA-LEN
    IO-AREA
    [WS-LENGTH-1]
    [WS-AREA-1]
    ...
    [WS-LENGTH-n]
    [WS-AREA-n]
  • DLI-XRST: A 4-character field with the value 'XRST', indicating the Extended Restart function.
  • DB-PCB: The I/O Program Communication Block, defined in the LINKAGE SECTION.
  • IO-AREA-LEN: Length of the largest database I/O area.
  • IO-AREA: Area in the WORKING-STORAGE SECTION containing the checkpoint ID (an 8-character identifier).
  • WS-LENGTH-1 to WS-LENGTH-n: Lengths of the working storage areas to be restored.
  • WS-AREA-1 to WS-AREA-n: Working storage areas to be restored.

Return Codes

After executing a 'XRST' call, IMS sets a status code in the IO-PCB to indicate the outcome:

  • Blank (' '): Call was successful.

Example

Scenario - Below is a simplified example of a COBOL program that uses the 'XRST' call to resume processing from the last checkpoint after an abnormal termination:

Hierarchical Structure -

COMPANY       ← root segment  
 └─ PROJECT    ← child of COMPANY  
      └─ EMPLOYEE   ← child of PROJECT 

Program -

IDENTIFICATION DIVISION.
PROGRAM-ID. RESTARTE.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.

DATA DIVISION.
WORKING-STORAGE SECTION.

* DL/I Function Codes
01 DL-I-CODES.
   05 DLI-XRST    PIC X(4) VALUE 'XRST'.
   05 DLI-GN      PIC X(4) VALUE 'GN  '.
   05 DLI-CHKP    PIC X(4) VALUE 'CHKP'.

* I/O Area for IMS data
01 IO-AREA.
   05 COMPANY-ID         PIC X(5).
   05 COMPANY-NAME       PIC X(30).
   05 PROJECT-ID         PIC X(5).
   05 PROJECT-NAME       PIC X(30).
   05 EMPLOYEE-ID        PIC X(5).
   05 EMPLOYEE-NAME      PIC X(25).

* Restart/Checkpoint area (application-specific)
01 RESTART-AREA.
   05 EMP-COUNT          PIC 9(4) VALUE ZERO.
   
LINKAGE SECTION.
* PCB Mask
01 EMP-PCB.
   05 DBD-NAME           PIC X(8).
   05 SEG-LEVEL          PIC XX.
   05 STATUS-CODE        PIC XX.
   05 PROC-OPTIONS       PIC X(4).
   05 FILLER             PIC X(4).
   05 SEGMENT-NAME-FB    PIC X(8).
   05 LENGTH-KEY-FB      PIC S9(5) COMP.
   05 NUM-SENSITIVES     PIC S9(5) COMP.
   05 KEY-FEEDBACK       PIC X(50).

PROCEDURE DIVISION.

    DISPLAY "=== IMS EMPLOYEE RESTART PROGRAM ===".

    * Step 1: Resume from last checkpoint if restart is requested
    CALL 'CBLTDLI' USING DLI-XRST,
                         EMP-PCB,
                         RESTART-AREA

    IF STATUS-CODE = '  '
        DISPLAY "-- XRST SUCCESSFUL, RESUMING..."
    ELSE IF STATUS-CODE = '   '
        DISPLAY "-- FIRST RUN (NO XRST NEEDED)"
    ELSE
        DISPLAY "** XRST ERROR. STATUS = " STATUS-CODE
        GOBACK
    END-IF.

    PERFORM UNTIL STATUS-CODE NOT = '  '
        * Step 2: Read next EMPLOYEE segment
        CALL 'CBLTDLI' USING DLI-GN,
                             EMP-PCB,
                             IO-AREA

        IF STATUS-CODE = '  '
            ADD 1 TO EMP-COUNT
            DISPLAY "EMPLOYEE READ: " EMPLOYEE-ID " - " EMPLOYEE-NAME

            * Step 3: Take a checkpoint after 2 records
            IF EMP-COUNT = 2
                CALL 'CBLTDLI' USING DLI-CHKP,
                                     EMP-PCB,
                                     RESTART-AREA

                IF STATUS-CODE = '  '
                    DISPLAY "-- CHECKPOINT TAKEN"
                    MOVE 0 TO EMP-COUNT
                ELSE
                    DISPLAY "** CHECKPOINT FAILED. STATUS = " STATUS-CODE
                END-IF
            END-IF
        ELSE IF STATUS-CODE = 'GB'
            DISPLAY "** END OF DATABASE **"
        ELSE
            DISPLAY "** ERROR OCCURRED. STATUS = " STATUS-CODE
        END-IF
    END-PERFORM.

    DISPLAY "=== PROGRAM COMPLETE ===".
    GOBACK.

Sample Output

=== IMS EMPLOYEE RESTART PROGRAM ===
-- XRST SUCCESSFUL, RESUMING...
EMPLOYEE READ: E003 - SARA LEE
EMPLOYEE READ: E004 - BOB KING
-- CHECKPOINT TAKEN
EMPLOYEE READ: E005 - ALICE MOON
...
=== PROGRAM COMPLETE ===