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

The EXTERNAL clause enables a file with organization XML to be defined as external. External XML files can be accessed by any program in which they are described.

Format


IS EXTERNAL


Syntax rules

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

  2. The EXTERNAL clause may not be specified for files with organization XML which have the DATA or LENGTH phrase specified in their SELECT clause.

General rules

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

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

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

    2. PROGRAM-ID names of the run unit, except for program names of contained names of a nested program,

    3. names used as entry points in an ENTRY statement,

    4. names that identify an interface (e.g. runtime system names).

  3. 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 phrase in the file description entry.

  4. An external file with organization XML must be described largely identically in all compilation units that wish to access it.
    The table below shows how and to what extent the descriptions must match.

    Clause/specificationIn all programs
    Name of the external fileSame to full length (30 characters)
    ORGANIZATION clauseXML
    ACCESS MODE clauseXML
    Record description entries in the FDIdentical, also the order of the record description entries. However, the system only checks whether the hierarchical structure of the IDENTIFIED phrases and the COUNT phrases in the record description entries match, and whether the ATTRIBUTE and ELEMENT, BY and USING phrases in NAMESPACE match.
  5. Data items specified in the IDENTIFIED clause under USING and BY or IS which are not contained in a record description entry of the FD are always effective for external files on a local program basis, i.e. they are only supplied with values or used in the program which executes the input operation.

If a file is defined as external, the associated file name is not implicitly a global name.