Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

COBOL language tools for the processing of indexed files

The following program skeleton summarizes the most important clauses and statements provided in COBOL2000 for the processing of indexed files. The most significant phrases and entries are briefly explained thereafter:

IDENTIFICATION DIVISION.
...
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT internal-file-name
    ASSIGN TO external-name
    ORGANIZATION IS INDEXED
    ACCESS MODE IS mode
    RECORD KEY IS primary-key
    ALTERNATE RECORD KEY IS secondary-key
    FILE STATUS IS status-items.
    ...
DATA DIVISION.
FILE SECTION.
FD  internal-file-name.
    BLOCK CONTAINS block-length-spec
    RECORD record-length-spec
    ...
01  data-record.
    nn item-1 type&length
    ...
    nn primary-key-item type&length
    nn secondary-key-item type&length
    ...
PROCEDURE DIVISION.
    ...
    OPEN open-mode internal-file-name
    ...
    START internal-file-name
    ...
    READ internal-file-name
    ...
    REWRITE data-record
    ...
    WRITE data-record
    ...
    DELETE internal-file-name
    ...
    CLOSE internal-file-name
    ...
STOP RUN.

SELECT internal-file-name

specifies the name by which the file is to be addressed in the compilation unit.

internal-file-name must be a valid user-defined word.

The format of the SELECT clause also permits the OPTIONAL phrase to be specified for input files that need not necessarily be present during the program run.

If, during program execution, no file has been assigned to a file name declared with SELECT OPTIONAL, then:

  • in the case of OPEN INPUT, program execution is interrupted with message COB9117 and an ADD-FILE-LINK command is requested (in dialog mode), or the AT END condition is initiated (in batch mode);

  • in the case of OPEN I-O or OPEN EXTEND, a file named FILE.COBOL.linkname is created.

ASSIGN TO external-name

specifies the system file associated with the file and defines the name via which a cataloged file can be assigned.

external-name must be either

  • a valid literal

  • a valid data-name defined in the Data Division, or

  • a valid implementor-name

from the ASSIGN clause format (see “COBOL2000 Reference Manual” [1]).

ORGANIZATION IS INDEXED

specifies that the file is organized as an indexed file.

ACCESS MODE IS mode

specifies the mode in which the records can be accessed.
The following may be specified for mode (see also section "Open modes and types of processing (indexed files)"):

SEQUENTIAL

specifies that the records can only be processed sequentially.

RANDOM

declares that the records can only be accessed in random mode.

DYNAMIC

allows the records to be accessed in either sequential or random mode.

The ACCESS MODE clause is optional. If it is not specified, the compiler assumes the default value ACCESS MODE IS SEQUENTIAL.

RECORD KEY IS primary-key

specifies which field in the record holds the primary record key.

primary-key must be declared as a data item in the associated record description entry (see below).

Except in sequential read operations, the primary record key of the record to be processed must be entered for primary-key before the execution of each I-O statement.

ALTERNATE RECORD KEY IS secondary-key

COBOL programs can also be used for processing files with records containing one or more secondary keys (ALTERNATE RECORD KEY) in addition to the mandatory primary record key (RECORD KEY).
If secondary keys are defined in a file, the user can access the records either via the primary key or via the secondary key(s).

The secondary key must be declared as a data item within the associated record description entry (see below).

FILE STATUS IS status-items

specifies the data items in which the runtime system stores status information after each access to a file. This information indicates

  • whether the I-O operation was successful and

  • the type of any errors that may have occurred.

The status items must be declared in the Working-Storage Section or the Linkage Section. Their format and the meaning of the various status codes are described in section "I-O status".

The FILE STATUS clause is optional. If it is not specified, the information mentioned above is not available to the program.

BLOCK CONTAINS block-length-spec

defines the maximum size of a logical block. It determines how many records are to be transferred together by each I-O operation into/from the buffer of the program.

block-length-spec must be a permissible specification from the BLOCK CONTAINS clause.

The blocking of records reduces

  • the number of accesses to peripheral storage and thus the runtime of the program;

  • the number of interblock gaps on the storage medium and thus the physical storage space required by the file.

On the other hand, accesses employing the locking mechanism during shared update processing (see section "Shared updating of files (SHARED-UPDATE)") cause the entire block containing the current record to be locked. In such a case, therefore a large blocking factor would lead to a reduction in processing speed.

During compilation, the compiler calculates a value for the buffer size on the basis of the record and block length entries given in the compilation unit. The runtime system rounds up this value for DMS to the next multiple of a PAM block (2048 bytes). This default value can be modified during the file assignment by specifying the BUFFER-LENGTH operand in the ADD-FILE-LINK command. It must be noted, however, that the specified buffer needs to be at least as large as the longest data record (see section "Definition of file attributes").

Except in the case of newly created files (OPEN OUTPUT), the block size entered in the catalog always takes priority over block size specifications in the program or ADD-FILE-LINK command.

The BLOCK CONTAINS clause is optional. If it is omitted, the compiler assumes the BLOCK CONTAINS 1 RECORDS, i.e. unblocked records.

RECORD record-length-spec

  • specifies whether records of fixed or variable length are to be processed and

  • defines, for variable-length records, a range of permissible values for the record length. If provided for in the format, a data item is additionally specified for the storage of current record length information.

The record-length-spec must conform to one of the three RECORD clause formats provided in COBOL2000. It must not be in conflict with the record lengths computed by the compiler from the specifications in the associated record description entry or entries.

The RECORD clause is optional. If it is not specified, records of variable length are assumed by the compiler.

01 data-record.
   nn item-1         type&length
   ...
   nn primary-key    type&length
   ...
   nn secondary-key  type&length

represents a record description entry for the associated file. It describes the logical format of data records.

At least one record description entry is required for each file. If more than one record description entry is specified for a file, the declared record format must satisfy the following rules:

  • for fixed-length records, all record description entries must specify the same size;

  • for variable-length records, the entries must not conflict with the record length specified in the RECORD clause, and even the record description entry with the shortest record length must still be capable of containing the entire record key.

At least one of the record description entries must explicitly declare the primary record key data item as a subordinate item of data-record. For type&length, the required length and format declarations (PICTURE and USAGE clauses etc.) must be entered (primary-key may have a maximum length of 255 bytes).

secondary-key is the data-name from the corresponding ALTERNATE RECORD KEY clause. Each secondary key item can be up to 127 bytes long. Overlaps with the primary key or other secondary keys are permissible provided two key items do not start at the same position. The COBOL2000 compiler also allows secondary keys defined as pure numeric (PIC 9) or alphabetic (PIC A) items.

The subdivision of data-record into subordinate data items (item-1, item-2, ...) is optional for all other record description entries.

OPEN open-mode internal-file-name

opens the file for processing in the specified open-mode.

The following phrases can be entered for open-mode:

INPUT

opens the file as an input file; it can only be read.

OUTPUT

opens the file as an output file; it can only be written.

EXTEND

opens the file as an output file; it can be extended.

I-O

opens the file as an I-O file; it can be read (one record at a time), updated and rewritten.

The open-mode entry determines with which I-O statements a file may be accessed (see section "Open modes and types of processing (indexed files)").

START internal-file-name
READ internal-file-name
REWRITE data-record
WRITE data-record
DELETE internal-file-name

are I-O statements for the file that

  • position to a record in the file

  • read a record

  • rewrite a record

  • write a record, and

  • delete a record.

The open mode declared in the OPEN statement determines which of these statements is admissible for the file. The relationship between access mode and open mode is described in section "Open modes and types of processing (indexed files)".

CLOSE internal file-name

terminates processing of the file.

The WITH LOCK phrase can be additionally specified to prevent the file from being opened again in the same program run.