IMS DB Checkpoint (CHKP)

CHKP (Checkpoint) is a DL/I function used to save the current state of the application and the database. If the program fails or abends later, IMS can restart from the last checkpoint, avoiding re-processing from the beginning. This is important in batch applications that process thousands/millions of records. It commits all database updates made since the last checkpoint, releases any locked resources, and records the current state of the program.

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

CALL 'CBLTDLI' USING
    DLI-CHKP
    IO-PCB
    IO-AREA-LEN
    IO-AREA
    [WS-LENGTH-n]
    [WS-AREA-n]
  • DLI-CHKP: A 4-character field with the value 'CHKP', indicating the Checkpoint 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-n: Length of the nth working storage area to be saved.
  • WS-AREA-n: The nth working storage area to be saved

Return Codes

After executing a 'CHKP' 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 'CHKP' call to establish checkpoints while processing records from an IMS database:

Hierarchical Structure -

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

Program -

IDENTIFICATION DIVISION.
PROGRAM-ID. EMPCHKPT.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.

DATA DIVISION.
WORKING-STORAGE SECTION.

01 DL-I-FUNCTIONS.
   05 DLI-GN      PIC X(4) VALUE 'GN  '.
   05 DLI-CHKP    PIC X(4) VALUE 'CHKP'.

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).

01 EMP-COUNT             PIC 9(4) VALUE ZERO.

LINKAGE SECTION.
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 "=== STARTING EMPLOYEE CHECKPOINT PROGRAM ===".

    PERFORM UNTIL STATUS-CODE NOT = '  '
        * Step 1: Retrieve the 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 2: Checkpoint after every 2 records
            IF EMP-COUNT = 2
                CALL 'CBLTDLI' USING DLI-CHKP,
                                     EMP-PCB,
                                     IO-AREA
                IF STATUS-CODE = '  '
                    DISPLAY "-- CHECKPOINT TAKEN SUCCESSFULLY --"
                ELSE
                    DISPLAY "** CHKP FAILED. STATUS = " STATUS-CODE
                END-IF
                MOVE 0 TO EMP-COUNT
            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

=== STARTING EMPLOYEE CHECKPOINT PROGRAM ===
EMPLOYEE READ: E001 - JOHN DOE
EMPLOYEE READ: E002 - JANE SMITH
-- CHECKPOINT TAKEN SUCCESSFULLY --
EMPLOYEE READ: E003 - ALICE BROWN
EMPLOYEE READ: E004 - BOB WHITE
-- CHECKPOINT TAKEN SUCCESSFULLY --
** END OF DATABASE **
=== PROGRAM COMPLETE ===