IMS DB Get Next in Parent (GNP)

The 'GNP' (Get Next in Parent) call is used to retrieve dependent segments sequentially under an established parent segment in the IMS database hierarchy. Unlike the 'GN' (Get Next) call, which retrieves the next segment in the database regardless of its parent, the 'GNP' call restricts retrieval to the dependents of the current parent segment. The syntax of a GU call is as follows −

CALL 'CBLTDLI' USING
    DLI-GNP
    DB-PCB
    IO-AREA
    [SSA1]
    [SSA2]
    ...
  • DLI-GNP: A 4-character field with the value 'GNP ', indicating the 'Get Next within Parent' 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 'GNP' call, IMS sets a status code in the DB-PCB to indicate the outcome:

  • Blank (' '): Call was successful; segment retrieved.
  • GE: Segment not found that satisfies the SSA; no segment retrieved.
  • GP: GNP issued but parentage was not previously established; no segment retrieved.​

Example

Scenario - This program will retrieve all the nodes within parent using GNP (Get Next within Parent) — using the familiar Company → Project → Employee hierarchy.

Hierarchical Structure -

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

Program -

IDENTIFICATION DIVISION.
PROGRAM-ID. GNPEXAMP.

DATA DIVISION.
WORKING-STORAGE SECTION.

* DL/I FUNCTION CODES
01 DL-I-CODES.
   05 DLI-GU   PIC X(4) VALUE 'GU  '.
   05 DLI-GNP  PIC X(4) VALUE 'GNP '.

* I/O AREA
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 SSAS.
   05 SSA-COMPANY          PIC X(30) VALUE 'COMPANY(COMPANY-ID =C001)'.
   05 SSA-PROJECT          PIC X(30) VALUE 'PROJECT(PROJECT-ID =P100)'.

LINKAGE SECTION.
* PCB MASK
01 PROJECT-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 DB GNP PROGRAM START ===".

    * Step 1: Position on specific PROJECT using GU
    CALL 'CBLTDLI' USING DLI-GU,
                         PROJECT-PCB,
                         IO-AREA,
                         SSA-COMPANY,
                         SSA-PROJECT

    IF STATUS-CODE = '  '
        DISPLAY "PROJECT FOUND: " PROJECT-ID " - " PROJECT-NAME
        DISPLAY "RETRIEVING EMPLOYEES FOR PROJECT..."

        * Step 2: Loop using GNP to retrieve EMPLOYEEs under this project
        PERFORM UNTIL STATUS-CODE NOT = '  '
            CALL 'CBLTDLI' USING DLI-GNP,
                                 PROJECT-PCB,
                                 IO-AREA

            IF STATUS-CODE = '  '
                DISPLAY "EMPLOYEE ID   : " EMPLOYEE-ID
                DISPLAY "EMPLOYEE NAME : " EMPLOYEE-NAME
            ELSE IF STATUS-CODE = 'GE'
                DISPLAY "** No more employees under project **"
            ELSE
                DISPLAY "** ERROR OCCURRED: STATUS = " STATUS-CODE
            END-IF
        END-PERFORM
    ELSE
        DISPLAY "** PROJECT NOT FOUND OR ERROR. STATUS = " STATUS-CODE
    END-IF.

    DISPLAY "=== PROGRAM END ===".
    GOBACK.

Sample Output

=== IMS DB GNP PROGRAM START ===
PROJECT FOUND: P100 - AI SYSTEMS
RETRIEVING EMPLOYEES FOR PROJECT...
EMPLOYEE ID   : E001
EMPLOYEE NAME : JOHN DOE
EMPLOYEE ID   : E002
EMPLOYEE NAME : JANE SMITH
** No more employees under project **
=== PROGRAM END ===