The status of each access operation performed on a file is stored by the runtime system in specific data items, which can be assigned to every file in the program. These items, which are specified by using the FILE STATUS clause, provide information on
whether the I-O operation was successful, and
the type of errors that may have occurred.
This data can be evaluated (by USE procedures in the DECLARATIVES, for example) and used by the program to analyze I-O errors. As an extension to Standard COBOL, COBOL2000 provides the option of using DMS codes to include error messages in this analysis, thus allowing a finer differentiation between different causes of errors.
The FILE STATUS clause is specified in the FILE-CONTROL paragraph of the Environment Division. Its format is (see “COBOL2000 Reference Manual” [1]):
FILE STATUS IS data-name-1 [data-name-2]
where data-name-1 and data-name-2 (if specified) must be defined in the Working-Storage Section or the Linkage Section. The following rules apply with regard to the format and possible values for these two items:
data-name-1
must be declared as a two-byte alphanumeric data item, e.g.
01 data-name-1 PIC X(2).
contains a two-character numeric status code following each access operation on the associated file. The table provided at the end of this section lists all such codes together with their meanings.
data-name-2
must be declared as a 6-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).
is used for storing the DMS error code for the I-O status. Following each access operation on the associated file, data-name-2 contains a value that directly depends on the content of data-name-1. The relationship between the values is shown in the table below:
Contents of data-name-1 not equal 0?
DMS code not equal 0?
Value of data-name-2-1
Value of data-name-2-2
no
no
undefined
undefined
yes
no
0
undefined
yes
yes
64
DMS code of the associated error message
The DMS codes and the associated error messages are given in “Introductory Guide to DMS” [4].
I-O status | Meaning |
Execution successful | |
00 | The I-O statement terminated normally. No further information regarding the I-O operation is available. |
02 | A record was read with ALTERNATE KEY and subsequent sequential reading with the same key has found at least one record with an identical key. A record was written with ALTERNATE KEY WITH DUPLICATES and there is already a record with an identical key value for at least one alternate key. |
04 | Record length conflict: A READ statement terminated normally. However, the length of the record read lies outside the limits defined in the record description entry for the given file. |
05 | An OPEN statement was executed for an OPTIONAL file which does not exist. |
Execution unsuccessful: AT END condition | |
10 | An attempt was made to execute a sequential READ operation. However, no next logical record was available, as the end-of-file was encountered. |
Execution unsuccessful: invalid key condition | |
21 | File sequence error in conjunction with ACCESS MODE IS SEQUENTIAL:
|
22 | Duplicate key An attempt was made to create a record with ALTERNATE KEY, but without WITH DUPLICATES, and there is already an alternate key with the same value in the file. |
23 | Record not located |
24 | Boundary values exceeded |
Execution unsuccessful: unrecoverable error | |
30 | No further information regarding the I-O operation is available (the DMS code provides further information). |
35 | An OPEN statement with the INPUT, I-O or EXTEND phrase was issued for a non-optional file which does not exist. |
37 | OPEN statement on a file that cannot be opened due to the following violations:
|
38 | An attempt was made to execute an OPEN statement for a file previously closed with the LOCK phrase. |
39 | The OPEN statement was unsuccessful as a result of one of the following conditions:
|
Execution unsuccessful: logical error | |
41 | An attempt was made to execute an OPEN statement for a file which was already open. |
42 | An attempt was made to execute a CLOSE statement for a file which was not open. |
43 | For ACCESS MODE IS SEQUENTIAL: |
44 | Record length limits exceeded: |
46 | An attempt was made to execute a sequential READ statement for a file in INPUT or I-O mode. However, no valid next record is available since:
|
47 | An attempt was made to execute a READ or START statement for a file that is not open in INPUT or I-O mode. |
46 | An attempt was made to execute a WRITE statement for a file that
|
49 | An attempt was made to execute a DELETE or REWRITE statement for a file that is not in I-O mode. |
Other conditions with unsuccessful execution | |
90 | System error; no further information regarding the cause is available. |
91 | OPEN error: the actual cause is evident from the DMS code (see “FILE STATUS clause” specifying data-name-2). |
93 | For shared update processing only (see section "Shared updating of files (SHARED-UPDATE)"): |
94 |
|
95 | Incompatibility between values specified in the BLOCK-CONTROL-INFO or BUFFER-LENGTH operand of the ADD-FILE-LINK command and the file format, block size, or the format of the used volume. |
96 | READ PREVIOUS is not supported for modules which were compiled with COBRUN ENABLE-UFS-ACCESS=YES. |
Table 34: I-O status values for indexed files