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 language elements

COBOL programs can use system files to input or output low-volume data (e.g. control statements). COBOL2000 supports access to system files and the console with the following language elements (see “COBOL2000 Reference Manual” [1]):

  • Program-internal mnemonic names for system files, declared in the SPECIAL-NAMES paragraph of the ENVIRONMENT DIVISION:
    PROCEDURE DIVISION statements can reference the assigned system files via these mnemonic names (see below). Among other things, mnemonic names can be declared for the following files:

    • input files:

      SYSDTA
      SYSIPT

      with TERMINAL IS mnemonic-name
      with SYSIPT IS mnemonic-name

    • output files:

      SYSOUT
      SYSLST
      SYSLSTnn
      SYSOPT

      with TERMINAL IS mnemonic-name
      with PRINTER IS mnemonic-name
      with PRINTERnn IS mnemonic-name (nn = 01...99)
      with SYSOPT IS mnemonic-name

  • The statements ACCEPT, DISPLAY and STOP literal of the PROCEDURE DIVISION:

    These access system files or the console according to the following rules:

    • ACCEPT...FROM mnemonic-name

      reads data from the input file that is associated (in the SPECIAL-NAMES paragraph) with mnemonic-name

      This causes the data to be transferred left-justified to the receiving item specified in the ACCEPT statement, its length being determined by this item as follows:
      If the item is longer than the value to be transferred, it is padded with spaces on the right; if it is shorter, the value is truncated on the right during the transfer to conform to the length of the item.

      If the input file has record format F (fixed-length records, see section "System files: primary assignments, reassignments, record formats"), the following also applies:
      If the length of the receiving item of the ACCEPT statement is greater than the logical record length of the system file, additional data is automatically requested, i.e. additional read operations (macro calls) are initiated.

      If the program detects the end-of-file condition while reading the system file, it issues message COB9121 or COB9122.
      Depending on the COMOPT operand CONTINUE-AFTER-MESSAGE or ERROR-REACTION in the RUNTIME-OPTIONS option (SDF), the program run is subsequently continued (default) or terminated.

      When the program run is continued the string “/*” is stored in the first two positions of the receiving item (“/” is stored if the receiving item is only one character long) and processing continues with the statement following ACCEPT.

    • ACCEPT (without FROM phrase)

      reads data by default from the system input file SYSIPT.

      With COMOPT REDIRECT-ACCEPT-DISPLAY=YES or
      ACCEPT-DISPLAY-ASSGN= *TERMINAL in the SDF option RUNTIME-OPTIONS, it is possible to switch the assignment to system file SYSDTA.

    • DISPLAY...UPON mnemonic-name

      writes data into the output file that is associated (in the SPECIAL-NAMES paragraph) with mnemonic-name.

      The size of the data transfer is determined by the length of the sending items orliterals specified in the DISPLAY statement:
      If the total number of characters to be transferred is greater than the maximum record length for the output file (see table 14 in section "System files: primary assignments, reassignments, record formats"), additional records are output until all characters are transferred. In the case of files with fixed-length records, if the number of characters is smaller than the record length, the records are space-filled on the right.

    • DISPLAY (without UPON phrase)

      writes data by default to the system output file SYSLST.

      With COMOPT REDIRECT-ACCEPT-DISPLAY=YES or
      ACCEPT-DISPLAY-ASSGN= *TERMINAL in the SDF option RUNTIME-OPTIONS, it is possible to switch the assignment to system file SYSOUT.

    • STOP literal

      outputs a literal (with a maximum length of 122 characters) on the console.

Example 8-1

Accessing a system file via a declared mnemonic name

IDENTIFICATION DIVISION.
    ...
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
    ...
SPECIAL-NAMES.
    SYSIPT IS SYS-INPUT —————————————————————————————————————————— (1)

    ...
PROCEDURE DIVISION.
    ...
    ACCEPT CONTROL-FIELD FROM SYS-INPUT.—————————————————————————— (2)

    ...

(1)

The program-internal mnemonic name SYS-INPUT is declared for the system file SYSIPT.

(2)

ACCEPT reads (via the mnemonic name SYS-INPUT) a value from SYSIPT into the item CONTROL-FIELD.