Function
The FILE STATUS clause specifies a data item that indicates the status of input/output operations during processing. In addition, by specifying a further item, an additional error code is made available.
Format
FILE STATUS IS data-name-1 [, data-name-2]
Syntax rules
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.
data-name-1 must be a two-byte alphanumeric data item.
data-name-2 must be a 6-character 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
If the FILE STATUS clause is specified, the runtime system copies the I-O status to data-name-1.
If specified, data-name-2 is assigned as follows:
If data-name-1 has the value 0, the contents of data-name-2 are undefined.
If data-name-1 has a non-zero value, data-name-2 contains the additional error code. The value 64 in data-name-2 indicates that this code is the (BS2000) DMS code; the value 96 in data-name-2 indicates that the code is the (POSIX) SIS code. The command HELP DMS <contents-of-data-name-2-2> or HELP SIS <contents-of-data-name-2-2> supplies more detailed information on the corresponding error code.
The I-O status is copied during the execution of each OPEN, CLOSE, READ, WRITE, REWRITE or START statement that references the specified file, and prior to the execution of each corresponding USE procedure (see chapter "General concepts").