Nested COBOL programs

COBOL programs can contain COBOL programs. Contained programs are included immediately before the END PROGRAM statement of the containing program. A contained program can also be a containing program, that is, it can itself contain other programs. Each contained or containing program is terminated by an END PROGRAM statement.

For an explanation of valid calls to nested programs and of the COMMON attribute of a nested program, see the Enterprise COBOL for z/OS Customization Guide.

The CICS translator treats top-level and nested programs differently.

The translator translates a top-level program (a program that is not contained by any other program) in the normal way, with one addition. The translator assigns the GLOBAL attribute for all translator-generated variables in the WORKING-STORAGE SECTION.

The translator translates nested or contained programs in a special way as follows:
  • A DATA DIVISION and LINKAGE SECTION are added if they do not already exist.
  • Declarations for DFHEIBLK (EXEC interface block) and DFHCOMMAREA (communication area) are inserted into the LINKAGE SECTION.
  • EXEC CICS commands and CICS built-in functions are translated.
  • The PROCEDURE DIVISION header is not modified.
  • No translator-generated temporary variables, used for pre-call assignments, are inserted in the WORKING-STORAGE SECTION.
The translator interprets that the input source starts with a top-level program if the first non-comment record is any of the following:
  • IDENTIFICATION DIVISION statement
  • CBL card
  • PROCESS card

If the first record is none of these, the translator treats the input as part of the PROCEDURE DIVISION of a nested program. The first CBL or PROCESS card indicates the start of a top-level program and of a new unit of compilation. Any IDENTIFICATION DIVISION statements that are found before the first top-level program indicate the start of a new nested program.

The practical effect of these rules is that nested programs cannot be held in separate files and translated separately. A top-level program and all its directly and indirectly contained programs constitute a single unit of compilation and must be submitted together to the translator.

Comments in nested programs

The translator treats comments that follow an END PROGRAM statement as belonging to the next program in the input source. Comments that precede an IDENTIFICATION DIVISION statement appear in the listing after the IDENTIFICATION DIVISION statement.

To avoid confusion always place comments:
  • After the IDENTIFICATION DIVISION statement that initiates the program to which they refer.
  • Before the END PROGRAM statement that terminates the program to which they refer.

If you are using a separate translator

If you are using a separate translator, and not using the integrated CICS translator, for nested programs that contain EXEC CICS commands, you need to explicitly code EIB and COMMAREA on the USING phrases on CALL and on the PROCEDURE DIVISION, as described in this section.

If you are using the integrated CICS translator, this action is not necessary for nested programs that contain EXEC CICS commands. The compiler, in effect, declares DFHEIBLK and DFHCOMMAREA as global in the top-level program. This means that explicit coding is not required.

If you are using a separate translator:
  1. In each nested program that contains EXEC CICS commands, CICS built-in functions, or references to the EIB or COMMAREA, code DFHEIBLK and DFHCOMMAREA as the first two parameters of the PROCEDURE DIVISION header as follows:
    PROCEDURE DIVISION USING DFHEIBLK
    DFHCOMMAREA PARM1 PARM2 ...
  2. In every call to a nested program that contains EXEC CICS commands, CICS built-in functions, or references to the EIB or COMMAREA, code DFHEIBLK and DFHCOMMAREA as the first two parameters of the CALL statement as follows:
    CALL 'PROGA' USING DFHEIBLK
    DFHCOMMAREA PARM1 PARM2 ...
  3. For every call that forms part of the control hierarchy between the top-level program and a nested program that contains EXEC CICS commands, CICS built-in functions, or references to the EIB or COMMAREA, code DFHEIBLK and DFHCOMMAREA as the first two parameters of the CALL statement. In the PROCEDURE DIVISION in the called programs code DFHEIBLK and DFHCOMMAREA. This is necessary to allow addressability to the EIB and COMMAREA to be passed to programs not directly contained by the top-level program.
  4. If it is not necessary to insert DFHEIBLK and DFHCOMMAREA in the PROCEDURE DIVISION of a nested program for any of the reasons previously listed, calls to that program should not include DFHEIBLK and COMMAREA in the parameter list of the CALL statement.

An example of a nested program

A unit of compilation consists of a top-level program W and three nested programs, X, Y, and Z, all directly contained by W.
Program W
During initialization and termination, calls Y and Z to do initial CICS processing and non-CICS file access. Calls X to do main processing.
Program X
Calls Z for non-CICS file access and Y for CICS processing.
Program Y
Issues CICS commands. Calls Z for non-CICS file access.
Program Z
Accesses files in batch mode.
Figure 1. Nested program example—nesting structure
A top-level program W and three nested programs, X, Y, and Z, all directly contained by W, as described in the text.
Applying the rules:
  • Y must be COMMON to enable a call from X.
  • Z must be COMMON to enable calls from X and Y.
  • Y issues CICS commands, so if you are using a separate translator:
    • All calls to Y must have DFHEIBLK and a COMMAREA as the first two parameters.
    • Y's PROCEDURE DIVISION header must have DFHEIBLK and DFHCOMMAREA as the first two parameters.
  • Though X does not access the EIB or the communication area, it calls Y, which issues CICS commands. Therefore if you are using a separate translator, the call to X must have DFHEIBLK and a COMMAREA as the first two parameters, and X's PROCEDURE DIVISION header must have DFHEIBLK and DFHCOMMAREA as its first two parameters.
Figure 2 illustrates these points.
Figure 2. Nested program example: coding
IDENTIFICATION DIVISION.
PROGRAM-ID. W...
PROCEDURE DIVISION...
CALL Z...
CALL Y USING DFHEIBLK COMMAREA...
CALL X USING DFHEIBLK COMMAREA...
IDENTIFICATION DIVISION.
PROGRAM-ID. X...
PROCEDURE DIVISION USING DFHEIBLK DFHCOMMAREA..
CALL Z...
CALL Y USING DFHEIBLK COMMAREA...
END PROGRAM X.
IDENTIFICATION DIVISION.
PROGRAM-ID. Y IS COMMON...
PROCEDURE DIVISION USING DFHEIBLK DFHCOMMAREA...
CALL Z...
EXEC CICS.....
END PROGRAM Y.
IDENTIFICATION DIVISION.
PROGRAM-ID. Z IS COMMON...
PROCEDURE DIVISION...
END PROGRAM Z.
END PROGRAM W.