Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

FILE STATUS clause

Function

The FILE STATUS clause specifies a data item that indicates the status of an XML file operation. In addition, when a further data item is specified, an error code is also made available.

Format


FILE STATUS IS data-name-1 [data-name-2]


Syntax rules

  1. data-name-1 and data-name-2 must be defined in the WORKING-STORAGE SECTION, LOCAL-STORAGE SECTION or LINKAGE SECTION of the DATA DIVISION.

  2. data-name-1 must be a two-character alphanumeric data item.

  3. data-name-2 must be a six-byte group item with the following format:

    01 data-name-2.
       02 data-name-2-1 PIC 9(2) COMP.
       02 data-name-2-2 PIC X(4).

General rules

  1. If the FILE STATUS clause is specified, the I-O status is transferred to data-name-1 following an I/O statement for the file to whose file control entry this clause is subordinate.

  2. If specified, data-name-2 is assigned as follows:

    • If data-name-1 contains the value 0, the contents of data-name-2 are undefined.

    • If data-name-1 contains a non-zero value, data-name-2 contains the additional error code. The value 96 in data-name-2-1 indicates that this code is the SIS code (POSIX). The value 231 indicates that this code is the CBX code (error code of the XML parser).

  3. The command HELP SIS <content of data-name-2-2> or HELP CBX <content of data-name-2-2> supplies more detailed information on the particular error code.

  4. The I-O status is transferred during execution of each OPEN, OPEN DOCUMENT, CLOSE, CLOSE DOCUMENT, READ or START statement that references the specified file, and prior to the execution of each corresponding USE procedure (see "I-O status for XML files" in section "Error handling").