Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

Random creation of a relative file

The following example illustrates a simple COBOL program with which a relative file can be randomly created. The records may be written to the file in any order.

Example 9-9

Program for the random creation of a relative file

 IDENTIFICATION DIVISION.
  PROGRAM-ID. RELATIV.
  ENVIRONMENT DIVISION.
  CONFIGURATION SECTION.
  SPECIAL-NAMES.
      TERMINAL IS T.
  INPUT-OUTPUT SECTION.
  FILE-CONTROL.
      SELECT RELATIVE-FILE
      ASSIGN TO "RELFILE"
      ORGANIZATION IS RELATIVE
     ACCESS MODE IS RANDOM —————————————————————————————————(1) 
     RELATIVE KEY IS REL-KEY ———————————————————————————————(2) 
     FILE STATUS IS FS-CODE DMS-CODE. ——————————————————————(3)
  DATA DIVISION.
  FILE SECTION.
  FD RELATIVE-FILE.
  01 RELATIVE-RECORD               PIC X(33).
  WORKING-STORAGE SECTION.
  01 REL-KEY                       PIC 9(3).
     88 END-OF-INPUT                          VALUE ZERO.
  01 I-O-STATUS.
     05 FS-CODE                    PIC 9(2).
     05 DMS-CODE.
        06 DMS-CODE-1              PIC 9(2) COMP.
           88 DMS-CODE-2-DEFINED              VALUE 64.
        06 DMS-CODE-2              PIC X(4).
  01 CLOSE-SCWITCH                 PIC X      VALUE "0".
     88 FILE-OPEN                             VALUE "1".
     88 FILE-CLOSED                           VALUE "0".
  01 RELATIVE-TEXT.
     05                            PIC X(24)
       VALUE „******HERE IS RECORD NO. „.
     05 REC-NO                     PIC 9(3).
     05                            PIC X(6)   VALUE "$$$$$$".
  PROCEDURE DIVISION.
  DECLARATIVES.
  OUTPUT-ERROR SECTION.
    USE AFTER STANDARD ERROR PROCEDURE ON RELATIVE-FILE.
 UNRECOVERABLE-ERROR. ——————————————————————————————————————(4)
      IF FS-CODE NOT LESS THAN 30
         DISPLAY „UNRECOVERABLE ERROR ON RELATIVE-FILE"
          UPON T
       DISPLAY „FILE STATUS: „ FS-CODE UPON T
       IF DMS-CODE-2-DEFINED
          DISPLAY „DMS-CODE: „ DMS-CODE-2 UPON T 
       END-IF
       IF FILE-OPEN
          CLOSE RELATIVE-FILE
       END-IF
      DISPLAY „PROGRAM TERMINATED ABNORMALLY" UPON T
       STOP RUN
    END-IF. 
 OUTPUT-ERROR-END.
        EXIT.
 END DECLARATIVES.
 INITIALIZATION.
     OPEN OUTPUT RELATIVE-FILE
     SET FILE-OPEN TO TRUE.
 LOAD-FILE.
     PERFORM INPUT-RELATIVE-KEY
        WITH TEST AFTER
        UNTIL REL-KEY IS NUMERIC
     PERFORM WITH TEST BEFORE UNTIL END-OF-INPUT
        WRITE RELATIVE-RECORD FROM RELATIVE-TEXT
            INVALID KEY —————————————————————————————————————(5) 
              DISPLAY „RECORD NO. „ REL-KEY
                 „ALREADY EXISTS IN FILE" UPON T
         END-WRITE
         PERFORM INPUT-RELATIVE-KEY
            WITH TEST AFTER
            UNTIL REL-KEY IS NUMERIC
      END-PERFORM.
 TRAILER.
     SET FILE-CLOSED TO TRUE
     CLOSE RELATIVE-FILE
     STOP RUN.
 INPUT-RELATIVE-KEY.
    DISPLAY „PLEASE ENTER RELATIVE KEY: THREE-DIGIT WITH L
-  „EADING ZEROES" UPON T 
    DISPLAY „TERMINATE PROGRAM ENTERING ‚000'" UPON T
    ACCEPT REL-KEY FROM T
    IF REL-KEY NUMERIC
       THEN MOVE REL-KEY TO REC-NO
       ELSE DISPLAY „INPUT MUST BE NUMERIC" UPON T
    END-IF.

 

(1)

The ACCESS MODE clause specifies random access for records of the file named RELATIVE-FILE. They may thus be written to the file in any order during creation.

(2)

The RELATIVE KEY clause defines REL-KEY as the relative key data item for the relative record number. It is declared in the Working-Storage Section as a three-digit numeric data item.

(3)

The FILE STATUS clause is defined so as to make the DMS code available to the program in addition to the FILE STATUS code. The data items required for storing this information are declared in the Working-Storage Section and evaluated in the DECLARATIVES.

(4)

The DECLARATIVES provide only one procedure for unrecoverable I-O errors (FILE STATUS >= 30), since an AT END condition cannot occur for output files and record key errors can be caught via INVALID KEY.

(5)

An INVALID KEY condition occurs in the case of a random WRITE operation when the record with the associated relative record number is already present in the file.