Compilation Group

A compilation group is everything that is submitted to a compiler at one time. A compilation group contains a series of source units. A source element is a term used to refer to a source unit excluding any nested source units. For more information on compilation groups and source units, see the topic Compilation Groups.

The following compilation group is an example of some of these concepts.

  FUNCTION-ID. factorial.
  DATA DIVISION.
  LINKAGE SECTION.
  01  parm1 BINARY-LONG.
  01  fact  BINARY-LONG.
  PROCEDURE DIVISION USING parm1 RETURNING fact.
     IF parm1 = 0
        COMPUTE fact = 1
     ELSE
        COMPUTE fact = parm1 * factorial (parm1 - 1)
     END-IF
     EXIT FUNCTION.
  END FUNCTION factorial.
  PROGRAM-ID. program-1.
  ENVIRONMENT DIVISION.
  CONFIGURATION SECTION.
  REPOSITORY.
      FUNCTION factorial.
  DATA DIVISION.
  WORKING-STORAGE SECTION.
  01  i  BINARY-LONG.
  PROCEDURE DIVISION.
      COMPUTE i = factorial (10)
  ...
  END PROGRAM program-1.
  PROGRAM-ID. program-2.
  ENVIRONMENT DIVISION.
  CONFIGURATION SECTION.
  REPOSITORY.
      FUNCTION-ID. factorial.
  DATA DIVISION.
  WORKING-STORAGE SECTION.
  01  i  BINARY-LONG.
  01  global-item PIC X(30) GLOBAL VALUE "The factorial is: "
  PROCEDURE DIVISION.
      COMPUTE i = factorial (11)
      CALL display-it USING i
      ...

      PROGRAM-ID. display-it.
      LINKAGE SECTION.
      01 n BINARY-LONG.
      PROCEDURE DIVISION USING n.
          DISPLAY global-item, n
      END PROGRAM display-it.

  END PROGRAM program-2.

This compilation group consists of three compilation units: the function factorial, the program program-1, and the program program-2. Each compilation unit is also a source unit. The source unit program-2 contains another source unit, the program display-it. Each of the four source units is also a source element. The difference between the source elements and the source units is that the source element program-2 does not include the nested program.

From each of the 3 compilation units, a separate runtime module is created by the compiler. Typically, a linkage editor is used to combine runtime modules, from one or multiple compilations, into a run unit.

The runtime module for the function factorial contains one runtime element, the function factorial. The runtime module for the program program-1 contains one runtime element. The runtime module for program-2 contains two runtime elements, one for program-2 and one for display-it.

This example illustrates how the user-defined function factorial can override the intrinsic function factorial. The compiler would use the factorial intrinsic function if FUNCTION factorial INTRINSIC were specified in the REPOSITORY paragraph. However, since the INTRINSIC phrase is not specified in the example, the user-defined function is the function that is activated.

To compile these programs, use the REPOSITORY directive. For example, use:

cobol program-1.cbl nognt repository(update on)