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 sequential files

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

IDENTIFICATION DIVISON.
    .
    .
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT internal-file-name
    ASSIGN TO external-name
    ORGANIZATION IS SEQUENTIAL
    ACCESS MODE IS SEQUENTIAL
    FILE STATUS IS status-items.
    .
    .
DATA DIVISION.
FILE SECTION.
FD  internal-file-name
    BLOCK CONTAINS block-length-spec
    RECORD record-length-spec
    RECORDING MODE IS record-format
    ...
01  data-record.
    nn item-1              type&length.
    nn item-2              type&length.
    ...
PROCEDURE DIVISION.
    ...
    OPEN open-mode internal-file-name.
    ...
    WRITE data-record.
    ...
    READ internal-file-name
    ...
    REWRITE data-record.
    ...
    CLOSE internal-file-name.
    ...
    STOP RUN.

SELECT internal-file-name

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

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

The SELECT clause format also permits use of the OPTIONAL phrase for input files whose presence is not essential at program runtime.
If a file name declared with SELECT OPTIONAL is not assigned any file during program execution, then:

  • in the case of OPEN INPUT, the program run 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 with the name
    FILE.COBOL.link-name 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 permissible literal or

  • a permissible data name defined in the DATA DIVISION

  • a valid implementor name

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

ORGANIZATION IS SEQUENTIAL

specifies that the file is sequentially organized.

The ORGANIZATION clause may be omitted in the case of sequential files, since the compiler assumes sequential file organization by default.

ACCESS MODE IS SEQUENTIAL

specifies that the records of the file can only be accessed sequentially.
The ACCESS MODE clause is optional and only serves for documentation purposes in the case of sequential files. This is because sequential access is the default value assumed by the compiler and is the only permitted access mode for sequential files.

FILE STATUS IS status-items

specifies the data items in which the runtime system stores status information after each access operation on 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 meanings of individual status codes are described in section "Processing magnetic tape files".
The FILE STATUS clause is optional. If it is not specified, the information mentioned above is not available.

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 value from the format of BLOCK CONTAINS clause.

The blocking of records reduces

  • the number of accesses 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.

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. In the case of disk files, the runtime system rounds up this value for the 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 (see section "Definition of file attributes").

In this case, it must be noted that

  • the buffer must be at least as large as the longest data record, and

  • there must be space for the management information (PAM key) in the buffer when processing in non-key format (BLKCTRL = DATA) (see section "Disk and file formats").

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 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.

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, the record format is obtained from the phrase in the RECORDING MODE clause (see below). Should this clause also be omitted, records of variable length are assumed by the compiler (see section "Permissible record formats and access modes" for the relationship between the RECORD and RECORDING MODE clauses).

RECORDING MODE IS U

defines the format of the logical records as “undefined”; i.e. the file may contain an optional combination of fixed or variable records.

The RECORDING MODE clause is optional and is only required when declaring records of undefined length, since fixed- and variable-length records can also be specified in the RECORD clause (see section "Permissible record formats and access modes").

 

01 data-record.
   nn item-1      type&length
   nn item-2      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 record size

  • for variable-length records, they must not be in conflict with the record length specified in the RECORD clause.

The subdivision of data-record into data items (item-1, item-2, ...) is optional. For type&length, the required length and format declarations (PICTURE and USAGE clauses etc.) must be entered.

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 (sequential processing)").

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

are I-O statements for the file that

  • write or

  • read or

  • rewrite

one record at a time.

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 (sequential processing)".

CLOSE internal-file-name

terminates processing. Depending on the entry in the format, it may apply to

  • the file (no further phrase) or

  • a disk storage unit (phrase: UNIT) or

  • a magnetic tape reel (phrase: REEL).

This clause can optionally be used to prevent

  • a tape from being rewound (phrase: WITH NO REWIND) or

  • a file from being opened again (phrase: WITH LOCK) in the same program run.