Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

EXTERNAL clause

Function

With the EXTERNAL clause, a file can be defined as external. External files can be accessed by any program in which the file is described.

Format


IS EXTERNAL


Syntax rule

  1. Names of external files can have a maximum length of 30 characters.

General rules

  1. If a file is defined as external, the records in that file are also implicitly external.

  2. If the file description entry for a sequential file contains the LINAGE clause and the EXTERNAL clause, the LINAGE-COUNTER special register is implicitly an external data item.

  3. The following may not be used as names for external files:

    • external record-names from the WORKING-STORAGE SECTION of other compilation units in the run unit,

    • PROGRAM-ID names of the run unit, except for program names of contained programs of a nested program,

    • names used as entry points in the ENTRY statement,

    • names that identify interfaces (LZS-name, etc.).

  4. The effect of the FILE STATUS clause for external files is always local to the program, i.e. the file status is supplied only by I-O operations in the program that contains a corresponding specification in the file description entry.

  5. The EXTERNAL clause may not be specified in file or record description entries for files that use a common I-O area (SAME RECORD AREA clause).

  6. The EXTERNAL clause may not be specified for files that are assigned to the system devices SYSIPT, SYSOPT, PRINTER or PRINTERnn.

  7. The EXTERNAL clause may not be specified for files for which user labels and corresponding USE procedures are defined.

  8. An external file must be essentially described in the same manner via explicit clauses or implicit default values in all programs that wish to access the file. The following table shows how and to what extent the descriptions must match:

    Clauses / specificationsIn all programs
    Name of external filesame to full length (30 characters)
    OPTIONAL phrase (SELECT clause)same specification*)
    ASSIGN TO data-namesame form of assignment
    ASSIGN TO PRINTER literalsame form of assignment
    ORGANIZATION clausesame form of organization
    ACCESS MODE clausesame access method
    RELATIVE KEY phrasesame number of digits
    RECORD KEY clausesame length and position
    ALTERNATE RECORD KEY clausesame number, position, length and DUPLICATES phrase
    BLOCK CONTAINS clausesame block size in bytes
    MULTIPLE FILE TAPE clausesame position number
    RECORD clausesame minimum and maximum record length
    LABEL RECORDS clausesame specification*)
    REPORT clause (Report Writer)same specification*)
    LINAGE clausesame specification*)
    CODE SET clausesame specification*)
    RECORDING MODE clausesame specification*)

    *) Same specification means that the relevant clause may either be specified in none of the programs or must be specified the same in all programs.

    All programs that access the same external file must have been compiled with the same value of the compiler option ENABLE-UFS-ACCESS or with the same module format (see the "COBOL2000 User Guide" [1]).

If a file is defined as external, this does not mean that the associated file-name is implicitly a global name.

Additional rules, depending on the module format

The following applies to the names of external files when generating the *OMF format (see the "COBOL2000 User Guide" [1]):

  1. The eighth character must not be a hyphen.

  2. Only the first 7 characters of the name are used for identification. These characters should therefore be unique for each external name in the run unit.