Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

COBOL compilation group

The following formats illustrate the general structure of a COBOL compilation group and the structure of the compilation units contained in it. A compilation unit can be compiled separately.

Format of the compilation group


{compilation unit}...



Compilation unit:


{  Program-prototype
 | Program-definition
 | Class-definition
 | Interface-definition
}



Program prototype:


[IDENTIFICATION DIVISION.]

PROGRAM-ID. {program-prototype-name-1} IS PROTOTYPE.

[environment-division]

[data-division]

[procedure-division]

END PROGRAM program-prototype-name-1.



Program definition; nested program definition:


[IDENTIFICATION DIVISION.]

PROGRAM-ID. program-name-1 [IS {| COMMON | {INITIAL |  RECURSIVE } |}  PROGRAM ].

[environment-division]

[data-division]

[procedure-division [nested program-definition]...]

[END PROGRAM program-name-1.]


 

Class definition:


[IDENTIFICATION DIVISION.]

CLASS-ID. class-name-1 [IS FINAL]
   [ INHERITS  FROM {class-name-2}...]
   [ USING  {parameter-name-1}...].

[environment-division]

[ [IDENTIFICATION DIVISION.]
  FACTORY.
  [environment-division]
  [data-division]
  [object-oriented procedure-division]
  END FACTORY.
]

[ [IDENTIFICATION DIVISION.]
  OBJECT.
  [environment-division]
  [data-division]
  [object-oriented procedure-division]
  END OBJECT.
]

END CLASS class-name-1.




Interface definition:


[IDENTIFICATION DIVISION.]

INTERFACE-ID. interface-name-1
   [INHERITS FROM {interface-name-2}...]
   [USING {parameter-name-1}...].

[environment-division]

[object-oriented procedure-division]

END INTERFACE interfacename-1.


 

Object-oriented Procedure Division


PROCEDURE DIVISION.
[{methods-definition}...]



Methods definition:


[IDENTIFICATION DIVISION.]

METHOD-ID. method-name-1 [OVERRIDE] [IS FINAL].

[environment-division]

[data-division]

[procedure-division]

END METHOD method-name-1.


Syntax rules

  1. Within a compilation group, the program-prototype-definitions must precede all other compilation units.

  2. If a compilation group contains a program definition and a program prototype definition with the same name, the interfaces of these two compilation units must be identical.

  3. The Data Division of a method within an interface definition may contain only the Linkage Section.

  4. The Procedure Division of a method within an interface definition may contain only a Procedure Division header.

General rules

  1. In the program prototype compilation unit, all sections in the Data Division except for the Linkage Section and everything in the Procedure Division except for the Procedure Division header are ignored. The ignored parts must still contain the correct COBOL syntax.

  2. The beginning of a compilation unit is indicated by the corresponding Identification Division. The end is indicated by one of the following:

    • the END marker

    • the end of the entire source code.

  3. When an END marker indicates the end of an individual compilation unit, it is either followed by no further source code or by the Identification Division of the next individual compilation unit (for a sequence of compilation units).

  4. The assignment of source lines between compilation units, i.e. to preceding or succeeding compilation units, is undefined.