Function
The USE statement introduces declarative procedures and defines the conditions for their execution. The USE statement itself, however, is not executed.
Format 1 | declares label handling routines. |
Format 2 | declares procedures to be run if an input/output error occurs for a file. |
Format 3 | same as format 2 but with the GLOBAL statement, and applies to nested programs only. |
Format 4 | declares procedures to be run if an exception condition has been triggered. |
Format 5 | declares procedures to be executed by the Report Writer before the output of listings (see the chapter "Report Writer"). |
Format 1 for sequential file organization
USE {BEFORE | AFTER} STANDARD [ENDING
| BEGINNING] [REEL
| UNIT
| FILE] LABEL PROCEDURE ON {file-name-1}...
Syntax rules
file-name-1 must be defined in a file description (FD) entry of the program’s Data Division.
file-name-1 must not be the name of a sort file.
file-name-1 refers to the file description entry for which the specified label handling procedures are to be performed.
The procedures specified are executed in conjunction with OPEN and CLOSE statements for the file.
Once a USE procedure has been executed, program execution resumes with the calling routine.
BEFORE or AFTER indicates the types of labels to be processed.
BEFORE indicates that nonstandard labels are to be processed (such labels may be specified only for tape files).
AFTER indicates that user labels follow standard file labels and that these user labels are to be processed.BEGINNING or ENDING indicates that header or trailer labels, respectively, are to be processed.
If the BEGINNING and ENDING phrases are omitted, the declared procedures will be run for both header and trailer labels.The phrases REEL, UNIT or FILE indicate that the declared procedures are to be run if volume, reel, or file labels are present.
The REEL phrase is not applicable to disk storage files. The UNIT phrase is not applicable to files in the random access mode, since only file labels are processed in that mode. The compiler treats the REEL and UNIT phrases as interchangeable.
If the above phrases are omitted, the declarative procedures are executed depending on the type of volume involved, either for reel labels and file labels, or for volume labels and file labels.
Format 1 of the USE statement is not permitted for line sequential files.
General rules
The labels to be processed for a file must be specified within the file description entry of that file as data-names in the LABEL RECORDS clause. These labels must be defined as level-01 data items within the file description entry or the LINKAGE SECTION.
The same file-name may appear in more than one variant of the format-1 USE statement. However, this must not cause two or more declarative procedures to be initiated at the same time.
If the file-name-1 specification is used, the file description for the file-name must not specify a LABEL RECORDS clause with the OMITTED phrase.
No user label routines can be declared for external files.
The standard system procedures are performed on all standard label records consisting of system and user labels.
Labels on input or input/output files are checked in the following order:
The I-O system checks standard header labels.
The USE procedures (if any) check user header labels.
The I-O system checks standard trailer labels.
The USE procedures (if any) check user trailer labels.
Labels on output files are created in the following order:
The I-O system creates standard header labels.
The USE procedures (if any) create user header labels.
Before the user header labels are written, they are checked to see whether they begin with the string UHL.
The I-O system creates standard trailer labels.
The USE procedures (if any) create user trailer labels.
Before the user trailer labels are written, they are checked to see whether they begin with the string UTL.
Within a USE procedure, there must be no reference to nondeclarative procedures except for the PERFORM statement.
References to procedure names which are subordinate to a USE statement may be made from another procedure or from a nondeclarative procedure by using a PERFORM statement only.The exit from a format-1 declarative procedure is generated by the compiler following the last statement in a given section. All logical paths within that section must lead to this exit point.
There is one exception to general rule 7:
The GO TO statement with the MORE-LABELS phrase may be used as a special exit point. After this statement is executed, the runtime system will take one of the following actions:
If labels are currently being created, the system will write the current header or trailer labels; the program will then continue at the beginning of the declarative section in order to create more labels. The user must make sure that the last statement in the section is executed after all labels are created. At this point, it should be noted that after execution of the GO TO statement with the MORE-LABELS phrase, a label will be written in any case; if the user did not supply a new label, the runtime system will generate a dummy label record in analogy to general rule 7.
If labels are currently being checked, the system will read an additional header or trailer label; the program will then continue at the beginning of the declarative section in order to check more labels. However, when processing user labels, the system will reenter the section only when there is another user label to check. Thus, in this case, the programmer does not have to provide a program path that flows through the last statement in the section. On the other hand, when processing nonstandard labels, the system does not know how many labels exist. The last statement in the section must therefore be executed in this case in order to terminate nonstandard label processing.
Example 8-82
In this example, one declarative section (ALPHA) handles header labels and another (BETA) handles trailer labels. The declarative procedures are executed both in input and output modes.
IDENTIFICATION DIVISION. PROGRAM-ID. USESEQ. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. TERMINAL IS T. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT SAMPLE-FILE ASSIGN TO "TESTTAPE". DATA DIVISION. FILE SECTION. FD SAMPLE-FILE, RECORD CONTAINS 100 CHARACTERS, LABEL RECORD IS SAMPLE-LABEL, DATA RECORD IS SAMPLE-RECORD. 01 SAMPLE-LABEL. 02 LABEL-ID PICTURE X(4). 02 LABEL-INFO PICTURE X(76). 01 SAMPLE-RECORD PICTURE X(100). WORKING-STORAGE SECTION. 77 I-O-INDICATOR PICTURE X. 88 INPUT-MODE VALUE "I". 88 OUTPUT-MODE VALUE "O". 77 LABEL-COUNTER PICTURE 9. PROCEDURE DIVISION. DECLARATIVES. ALPHA SECTION. USE AFTER STANDARD BEGINNING FILE LABEL PROCEDURE ON SAMPLE-FILE. ALPHA-1. IF INPUT-MODE THEN DISPLAY "512010 THIS LABEL READ:-" SAMPLE-LABEL UPON T GO TO MORE-LABELS ELSE IF LABEL-COUNTER = 0 THEN MOVE "UHL1" TO LABEL-ID MOVE "THIS WAS PRODUCED BY ALPHA SECTION." TO LABEL-INFO DISPLAY "511030 THIS LABEL CREATED:-" SAMPLE-LABEL UPON T MOVE 1 TO LABEL-COUNTER GO TO MORE-LABELS ELSE MOVE "UHL2" TO LABEL-ID MOVE "SECOND LABEL PRODUCED BY ALPHA SECTION" TO LABEL-INFO DISPLAY "511530 AND THIS LABEL TOO:-" SAMPLE-LABEL UPON T MOVE 2 TO LABEL-COUNTER END-IF END-IF. ALPHA-END. EXIT. BETA SECTION. USE AFTER STANDARD ENDING FILE LABEL PROCEDURE ON SAMPLE-FILE. BETA-1. IF INPUT-MODE THEN DISPLAY "522010 THIS LABEL READ:-" SAMPLE-LABEL UPON T GO TO MORE-LABELS ELSE IF LABEL-COUNTER = 0 THEN MOVE "UTL1" TO LABEL-ID MOVE "THIS WAS PRODUCED BY BETA SECTION" TO LABEL-INFO DISPLAY "521030 THIS LABEL CREATED:-" SAMPLE-LABEL UPON T MOVE 1 TO LABEL-COUNTER GO TO MORE-LABELS ELSE MOVE "UTL2" TO LABEL-ID MOVE "SECOND LABEL PRODUCED BY BETA SECTION" TO LABEL-INFO DISPLAY "521530 AND THIS LABEL TOO: " SAMPLE-LABEL UPON T MOVE 2 TO LABEL-COUNTER END-IF END-IF. BETA-END. EXIT. END DECLARATIVES. GAMMA SECTION. HERE-GOES. MOVE "O" TO I-O-INDICATOR. OPEN OUTPUT SAMPLE-FILE CLOSE SAMPLE-FILE STOP RUN.
Example 8-83
In this example, UHL-FIELD, LABEL-NO and USER-INFO are common label items. Therefore, the unqualified reference to UHL-FIELD in the paragraph named L-1 is legitimate.
Data Division entries:
FD FILE-1. ... LABEL RECORD IS LABEL-1 ... 01 LABEL-1. 02 UHL-FIELD PIC X(3). 02 LABEL-NO PIC 9. 02 USER-INFO PIC X(76). 01 RECORD-1. ... FD FILE-2 ... LABEL RECORD IS LABEL-2 ... 01 LABEL-2. 02 UHL-FIELD PIC X(3). 02 LABEL-NO PIC 9. 02 USER-INFO PIC X(76). 01 RECORD-2.
Procedure Division statements:
L SECTION. USE AFTER STANDARD LABEL PROCEDURE ON INPUT. L-1. IF UHL-FIELD NOT = "UHL" THEN STOP RUN. ... GO TO MORE-LABELS. L-9. EXIT. M SECTION. ... HOUSEKEEPING SECTION. FILE-OPEN. OPEN INPUT FILE-1, FILE-2.
Format 2 for all types of file organization
USE AFTER STANDARD {ERROR | EXCEPTION} PROCEDURE ON { {FILE-NAME-1}... | INPUT | OUTPUT | I-O | EXTEND}
Syntax rules
The ERROR and EXCEPTION phrases are equivalent and may be used interchangeably.
file-name-1 must not appear in more than one USE statement. The INPUT, OUTPUT,I-O, and EXTEND phrases may each be specified only once.
Files referenced either implicitly (INPUT, OUTPUT, I-O and EXTEND) or explicitly (file-name-1, file-name-2, ...) in the USE statement need not have the same organization and access mode.
General rules
The USE procedures are performed:
when an at end condition occurs, provided that the input/output statement in which this condition appears does not contain an AT END phrase or an invalid key or when an invalid key condition occurs if the input/output statement which encountered this condition does not include an INVALID KEY.
when a severe error occurs (FILE STATUS CODE ≥ 30).
If no corresponding USE procedure exists for the file when a) or b) occurs, the program will abort.
When file-name-1 is specified, the error handling procedures are executed only for the named files. No other USE procedures are performed for these files.
Before execution of the user error routine, the standard system error routines for input/output error handling are executed.
After a USE procedure is executed, control passes to the calling routine.
INPUT indicates that the specified procedures are executed only for files opened in input mode (OPEN statement with the INPUT phrase.)
OUTPUT indicates that the specified procedures are executed only for files opened in output mode (OPEN statement with the OUTPUT phrase).
I-O indicates that the specified procedures are executed only for files opened in I-O mode (OPEN statement with the I-O phrase).
EXTEND indicates that the specified procedures are executed only for files opened in extend mode (OPEN statement with the EXTEND phrase).
Within a USE procedure, there must be no reference to nondeclarative procedures, except for the PERFORM and RESUME statement.
Reference to procedure names which are subordinate to a USE statement may be made from another procedure or from a nondeclarative procedure by using a PERFORM statement only.
The statements within a USE procedure may not result in a USE procedure which is still active being activated again.
Example 8-84
IDENTIFICATION DIVISION. PROGRAM-ID. USESEQ2. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. TERMINAL IS T. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT MASTER-FILE ASSIGN "MASTER-FILE" FILE STATUS INDICATOR. FILE SECTION. FD MASTER-FILE. 01 REC PIC X(80). WORKING-STORAGE SECTION. 01 INDICATOR PIC XX. 01 CLOSE-INDICATOR PIC X VALUE "0". 88 FILE-CLOSED VALUE "0". 88 FILE-OPEN VALUE "1". PROCEDURE DIVISION. DECLARATIVES. INPUT-ERROR SECTION. USE AFTER ERROR PROCEDURE ON MASTER-FILE. STATUS-QUERY. IF INDICATOR = "10" DISPLAY "End of MASTER-FILE encountered" UPON T ELSE DISPLAY "Unrecoverable error (" Indicator ") for MASTER-FILE" UPON T IF FILE-OPEN CLOSE MASTER-FILE END-IF DISPLAY "Program terminated abnormally" UPON T STOP RUN END-IF. END DECLARATIVES. BEGIN SECTION. WORK. OPEN INPUT MASTER-FILE. SET FILE-OPEN TO TRUE. READ MASTER-FILE. CLOSE MASTER-FILE WITH LOCK. SET FILE-CLOSED TO TRUE. OPEN INPUT MASTER-FILE. CLOSE MASTER-FILE. STOP RUN.
Example 8-85
IDENTIFICATION DIVISION. PROGRAM-ID. USEREL. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. TERMINAL IS T. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT OPTIONAL WORKFILE ASSIGN TO "WORKFILE" ORGANIZATION IS RELATIVE ACCESS MODE IS DYNAMIC RELATIVE KEY IS RELKEY FILE STATUS INDICATOR. DATA DIVISION. FILE SECTION. FD WORKFILE. 01 REC. 03 INHOLD PIC X(100). WORKING-STORAGE SECTION. 01 INDICATOR PIC XX. 01 RELKEY PIC 9(4). 01 CLOSE-INDICATOR PIC X VALUE "0". 88 FILE-CLOSED VALUE "0". 88 FILE-OPEN VALUE "1". PROCEDURE DIVISION. DECLARATIVES. INPUT-ERROR SECTION. USE AFTER ERROR PROCEDURE ON WORKFILE. STATUS-QUERY. EVALUATE INDICATOR WHEN "10" DISPLAY "End of WORKFILE encountered" UPON T WHEN "22" DISPLAY "Record with key" RELKEY "ALREADY EXISTS" UPON T WHEN "23" DISPLAY "Record with key" RELKEY "NON-EXISTENT" UPON T WHEN OTHER DISPLAY "Unrecoverable error "(" INDICATOR")" "FOR FILE-INPUT" UPON T IF FILE-OPEN THEN CLOSE WORKFILE END-IF DISPLAY "Program terminated abnormally" UPON T STOP RUN END-EVALUATE. END-DECLARATIVES. MAIN SECTION. OPEN-CLOSE. ... STOP RUN.
Example 8-86
IDENTIFICATION DIVISION. PROGRAM-ID. USEIND. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. TERMINAL IS T. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT MASTER-FILE ASSIGN "IN-OUT" ORGANIZATION IS INDEXED RECORD KEY ISAMKEY ACCESS MODE IS DYNAMIC FILE STATUS INDICATOR. DATA DIVISION. FILE SECTION. FD FILE1. 01 RECORD-FORMAT. 03 ISAMKEY PIC 9(8). 03 CONTENTS PIC X(72). WORKING-STORAGE SECTION. 01 INDICATOR PIC XX. 01 CLOSE-INDICATOR PIC X VALUE "0". 88 FILE-CLOSED VALUE "0". 88 FILE-OPEN VALUE "1". PROCEDURE DIVISION. DECLARATIVES. FILE-ERROR SECTION. USE AFTER ERROR PROCEDURE ON FILE1. STATUS-QUERY. EVALUATE INDICATOR WHEN "10" DISPLAY "End of FILE1 encountered" UPON T WHEN "21" DISPLAY "Record with key" ISAMKEY "ALREADY EXISTS OR NOT IN" "ASCENDING ORDER" UPON T WHEN "22" DISPLAY "Record with key" ISAMKEY "ALREADY EXISTS" UPON T WHEN "23" DISPLAY "Record with key" ISAMKEY "NON-EXISTENT" UPON T WHEN OTHER DISPLAY "Unrecoverable error" "(" INDICATOR") FOR MASTER FILE" UPON T IF FILE-OPEN THEN CLOSE FILE1 END-IF DISPLAY "Program terminated abnormally" UPON T STOP RUN END-EVALUATE. END DECLARATIVES. BEGIN SECTION. OPEN-CLOSE. . . . STOP RUN.
Format 3 USE statement with GLOBAL phrase
USE GLOBAL AFTER STANDARD {EXCEPTION | ERROR} PROCEDURE ON {{file-name-1}... | INPUT | OUTPUT | I-O | EXTEND}
The USE statement with the GLOBAL phrase can be specified in nested programs in order to define procedure declarations or label routines as global.
For the declaration of user label routines cannot contain a GLOBAL clause.
Syntax rules
A USE procedure in format 2 requires no FD entry with a GLOBAL clause.
For further syntax rules relating to the USE statement, refer to the formats above.
General rules
The GLOBAL phrase for a USE procedure has the same effect as the GLOBAL clause in data and file descriptions.
If an I-O statement requires the use of a USE procedure, then the valid USE procedure is selected from the sum total of all the USE procedures declared in the nested program, in accordance with the following rules of precedence:
The valid USE procedure (see format 2) is the one defined in the same program.
If a) does not apply, the valid USE procedure is the one declared as global in the directly superordinate (next outer) program.
If neither a) nor b) applies, the valid USE procedure is the one declared as global in the indirectly superordinate program.
Rule c) applies until all indirectly superordinate programs have been searched for the valid global USE procedure.
If no suitable USE procedure is found, then none is executed.
As an extension to ANS85, the compiler described here also permits PERFORM statements that relate to program segments outside of the DECLARATIVES. These program segments may also contain CALL, GO TO, GOBACK and EXIT PROGRAM statements. When a global USE procedure is used, this may result in recursive calling of the program that activated the USE procedure. A recursive call (always inadmissible) is not detected until program execution time, and results in program abortion.
A global USE procedure should not therefore execute any EXIT PROGRAM statement.
Example 8-87
of the scope of validity of global USE procedures
Format 4 for exception conditions
USE AFTER {EXCEPTION CONDITION | EC } {exception-condition-name | EC-ALL} ...
Syntax rules
exception-condition-name must be one of the names listed in table 45 in section "Exception conditions and exception statuses".
No reference to procedures outside the declaratives may be contained in a USE statement with the exception of the PERFORM and RESUME statements.
Procedure names which are subordinate to a USE statement may only be referenced from another procedure or outside the declaratives with a PERFORM statement.
EC means the same as EXCEPTION CONDITION.
General rules
The statements within a USE procedure may not result in a USE procedure which is still active being activated again.
If an exception condition is triggered, the first USE procedure in which the associated exception condition name is specified is selected.
If this exception condition name is not specified in any USE procedure, the first USE procedure in which EC-ALL is specified is selected.
If EC-ALL is also not specified in any USE procedure, the program run is aborted depending on the category of the exception condition (fatal/non-fatal) or continued at the next executable statement.If a USE procedure is activated by a exception condition, the program run is aborted if the USE procedure was not exited by executing an explicit statement (e.g. GOBACK, RESUME).