IMS DB Replace (REPL)

The 'REPL' (Replace) call is a DL/I function used to update the contents of an existing segment in the database. It allows modification of one or more fields within a segment, excluding key fields. Before issuing a 'REPL' call, the segment must be retrieved and held using a Get Hold call such as 'GHU', 'GHN', or 'GHNP'. In a COBOL program, the 'REPL' call is made using the following syntax:

CALL 'CBLTDLI' USING
    DLI-REPL
    DB-PCB
    IO-AREA
    [SSA1]
    [SSA2]
    ...
  • DLI-REPL: A 4-character field with the value 'REPL', indicating the Replace function.
  • DB-PCB: The Program Communication Block for the database, defined in the LINKAGE SECTION. It specifies the database to be accessed and contains status codes and other information after the call.
  • IO-AREA: The area in the WORKING-STORAGE SECTION where the retrieved segment data will be placed.
  • SSA1, SSA2, ...: Optional. Defines the segment type and optional qualification criteria for the retrieval.

Return Codes

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

  • Blank (' '): Call was successful; segment replaced.
  • DA: Attempted to change a key field in the segment.
  • DJ: 'REPL' call issued without a preceding Get Hold call.
  • AJ: Invalid SSA format.
  • AK: Invalid field name in SSA.​

Example

Scenario - Below is a simplified example of a COBOL program that uses the 'REPL' call to update an 'EMPLOYEE' segment in an IMS database:

Hierarchical Structure -

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

Program -

IDENTIFICATION DIVISION.
PROGRAM-ID. REPLEXAM.

DATA DIVISION.
WORKING-STORAGE SECTION.

* DL/I Function Codes
01 DL-I-CODES.
   05 DLI-GHU     PIC X(4) VALUE 'GHU '.
   05 DLI-REPL    PIC X(4) VALUE 'REPL'.

* I/O Area for segment 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).

* SSA Strings
01 SSA-STRINGS.
   05 SSA-COMPANY         PIC X(30) 
       VALUE 'COMPANY(COMPANY-ID =C001)'.
   05 SSA-PROJECT         PIC X(30) 
       VALUE 'PROJECT(PROJECT-ID =P105)'.
   05 SSA-EMPLOYEE        PIC X(35) 
       VALUE 'EMPLOYEE(EMPLOYEE-ID=E999)'.
   
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 "=== START: REPLACE EMPLOYEE ===".

    * Step 1: Get and hold the specific EMPLOYEE segment
    CALL 'CBLTDLI' USING DLI-GHU,
                         EMP-PCB,
                         IO-AREA,
                         SSA-COMPANY,
                         SSA-PROJECT,
                         SSA-EMPLOYEE

    IF STATUS-CODE = '  '
        DISPLAY "EMPLOYEE FOUND AND HELD FOR UPDATE:"
        DISPLAY "   EMPLOYEE ID   : " EMPLOYEE-ID
        DISPLAY "   EMPLOYEE NAME : " EMPLOYEE-NAME

        * Step 2: Change the employee name
        MOVE 'ALAN UPDATED' TO EMPLOYEE-NAME

        * Step 3: Replace the EMPLOYEE segment with new name
        CALL 'CBLTDLI' USING DLI-REPL,
                             EMP-PCB,
                             IO-AREA

        IF STATUS-CODE = '  '
            DISPLAY "EMPLOYEE NAME SUCCESSFULLY UPDATED"
            DISPLAY "   NEW NAME: " EMPLOYEE-NAME
        ELSE
            DISPLAY "** REPLACE FAILED. STATUS = " STATUS-CODE
        END-IF
    ELSE
        DISPLAY "** EMPLOYEE NOT FOUND. STATUS = " STATUS-CODE
    END-IF.

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

Sample Output

=== START: REPLACE EMPLOYEE ===
EMPLOYEE FOUND AND HELD FOR UPDATE:
   EMPLOYEE ID   : E999
   EMPLOYEE NAME : ALAN RICKMAN
EMPLOYEE NAME SUCCESSFULLY UPDATED
   NEW NAME: ALAN UPDATED
=== PROGRAM COMPLETE ===