Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

COMPILER-ACTION option

This option specifies a point in the compilation after which the compiler run is to be terminated. If a module is to be generated, this option can also be used to define its format and attributes.

Format

COMPILER-ACTION = *PRINT-MESSAGE-LIST / *SYNTAX-CHECK / *SEMANTIC-CHECK / *MODULE-GENERATION(...)


*MODULE-GENERATION(...)


|

,SHAREABLE-CODE = *NO / *YES


|

,ENABLE-INITIAL-STATE = *NO / *YES


|

,MODULE-FORMAT = *OM / *LLM (...)


|


LLM (...)


|


|

ALIGNMENT = *PAGE / *DOUBLE-WORD


|

,SUPPRESS-GENERATION = *NO / *AT-SEVERE-ERROR


|

,SEGMENTATION = *ELABORATE / *IGNORE


|

,UPDATE-REPOSITORY = *NO / *YES


|

,CALL-CONVENTION = *COBOL / *COMPATIBLE


|

,OPTION-DIRECTIVES = *KEEP / *IGNORE


COMPILER-ACTION = *PRINT-MESSAGE-LIST
The compiler prints a list of all possible error messages. No compilation takes place. This operand is not available in COBOL-BC.

COMPILER-ACTION = *SYNTAX-CHECK
The compiler only checks the compilation units for syntax errors.

COMPILER-ACTION = *SEMANTIC-CHECK
The compiler runs a syntax check on the compilation units and also verifies that they comply with the semantic rules. Since no module is to be generated, only a source listing and diagnostic listing can be requested.

COMPILER-ACTION = *MODULE-GENERATION(...)
A complete compilation run is to be performed and - unless explicitly suppressed - object modules are to be generated.

SHAREABLE-CODE = *NO / YES
If YES is specified, the compiler writes the code of the PROCEDURE DIVISION (without DECLARATIVES) into a shareable code module (see section "Shareable COBOL programs").
For the name convention see table 2 in "Output of modules".
Any segmentation of the PROCEDURE DIVISION is ignored.

ENABLE-INITIAL-STATE = *NO / *YES
If YES is specified, the compiler sets up areas for initialization. If NO is specified, programs to which a CANCEL statement refers or that contain the INITIAL clause or INITIALIZE statements with VALUE specification do not run as standard.

MODULE-FORMAT = *OM / *LLM (...)
The following specifications are ignored if the module is written to the POSIX file system (see MODULE-OUTPUT = <c-string...>).
OM: To enable further processing with BINDER, TSOSLNK, or DBL, the module is to be generated in OM format (object module format).
Maximum length for external names: 8 characters.
LLM: To enable further processing with BINDER or DBL, the module is to be generated in LLM format (link-and-load module format).
Maximum length for external names: 30 characters.


When classes and interfaces are compiled, the *LLM format should always be selected. Classes or interfaces that inherit from each other must all be available in the same module format.


ALIGNMENT = *PAGE / *DOUBLE-WORD
If PAGE is specified then the CSECTS have the PAGE attribute in the generated module and are therefore aligned at the boundary.
If DOUBLE-WORD is specified then the CSECTS are only aligned at double word boundaries.

SUPPRESS-GENERATION = *NO / *AT-SEVERE-ERROR
AT-SEVERE-ERROR can be specified to suppress the generation of the module and the expansion of the parameterized classes/interfaces used if an error with a severity code >= 2 occurs during compilation.
SUPPRESS-GENERATION = *AT-SEVERE-ERROR also results in the operand SUPPRESS-GENERATION = *AT-SEVERE-ERROR in the LISTING option. This also prevents the object, address and cross-reference lists from being output.

SEGMENTATION=*ELABORATE / *IGNORE
ELABORATE: permits segmentation. If the program contains nested programs and non-fixed segments (segment number greater than or equal to segment limit), the compilation is aborted and a message is output. Otherwise, only segmentation-related language elements are rejected with appropriate warnings.
If SEGMENTATION = ELABORATE is specified together with SHAREABLE-CODE = YES or MODULE-FORMAT = LLM, it is rejected with an error message.
IGNORE: ignores segmentation-related language elements (SEGMENT-LIMIT clause, segment numbers in section header). When they occur, they are indicated with appropriate warnings.

UPDATE-REPOSITORY = *NO / *YES
If YES is specified, the compiler places the external interface of the compilation units in the external repository assigned with the link name REPOUT. If a corresponding interface already exists in the repository, no check is performed to determine whether any changes in the interface have occurred, i.e., the existing definition is blindly overwritten with the new one. If no link with the name REPOUT exists, the library SYS.PROG.LIB is used.
This output always occurs and cannot be suppressed with SUPRESS-GENERATION. Repository data is stored as an element of type X. To enable a differentiation, classes are assigned the suffix $CLS, interfaces the suffix $IFC, parameterized classes the suffix $PCL, parameterized interfaces the suffix $PIF and programs or program prototypes the suffix $PRO.

CALL-CONVENTION = *COBOL / *COMPATIBLE
When COBOL is specified, the value COBOL is set for the >>CALL-CONVENTION directive.
When COMPATIBLE is specified, COMPATIBLE is assumed as the default value for the >>CALL-CONVENTION directive.

OPTION-DIRECTIVES = *KEEP / *IGNORE
When IGNORE is specified, all >>IMP directives in the source text which relate to compiler options (LISTING-OPTIONS, COMPILER-ACTION and RUNTIME-ERRORS) are ignored. The result of this is that the options set externally are effective regardless of the directives specified in the source text.
In the case of expansion of parameterized classes/interfaces, OPTION-DIRECTIVES=*KEEP is always assumed.