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 processing relative files

The following program skeleton summarize the most important clauses and statements provided in COBOL2000 for the processing of relative 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 RELATIVE
    ACCESS MODE IS mode RELATIVE KEY IS key
    FILE STATUS IS status-items.
    ...
DATA DIVISION.
FILE SECTION.
FD  internal-file-name
    BLOCK CONTAINS block-length-spec
    RECORD CONTAINS record-length-spec
    ...
01  data-record.
    nn item-1                type&length.
    nn item-2                type&length.
    ...
WORKING-STORAGE SECTION.
    ...
    nn key                   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 permissible literal,

  • a permissible data name defined in the DATA division, or

  • a valid implementor name

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

ORGANIZATION IS RELATIVE

specifies that the file is organized as a relative file.

ACCESS MODE IS mode

specifies the mode in which the records in the file can be accessed.

The following may be specified for mode (see also section "Open modes and types of processing (relative 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.

RELATIVE KEY IS key

specifies the relative key data item for holding the relative record numbers in the case of random access to the records.

key must be declared as an unsigned integer data item and must not be a part of the associated record description entry.
In the case of random access, the relative record number of the record to be processed must be supplied in key before each I-O operation.

The RELATIVE KEY phrase is optional for files for which ACCESS MODE IS SEQUENTIAL is declared; it is mandatory when ACCESS MODE IS RANDOM or DYNAMIC is specified.

FILE STATUS IS status-items

specifies the data items in which the runtime system will store 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

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 an integer and must not be shorter than the record length of the file or greater than 32767. It specifies the size of the logical block in bytes. 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, access 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 each 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.

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 not specified, the compiler assumes the record length of the file as the block size.

RECORD record-length-spec

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

  • defines, for variable length records, a range for the valid record sizes and, if specified in the format, a data item to contain the current record length information.

record-length-spec must match one of the three formats in the RECORD clause supported by COBOL2000. It must not conflict with the record lengths the compiler computes from the specifications in the associated record description entry or entries.

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

 

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 be considered:

  • For records of fixed length all record description entries must be of the same size,

  • for records of variable length they must not conflict with the record length specification 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.
The relative key data item declared in the RELATIVE KEY phrase must not be subordinate to data-record.

nn key type&length

defines the relative key data item specified in the RELATIVE KEY phrase.

When specifying values for type&length, it should be noted that key must be an unsigned integer data item.
In the case of random access, the relative record number of the record to be processed must be supplied in key before each I-O operation.

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