Function
The EXIT PERFORM statement makes it possible to branch to the end of the PERFORM statement or to a repetition of the loop from an in-line PERFORM statement.
Format
EXIT {[TO TEST OF] PERFORM | PERFORM CYCLE}
Syntax rules
An EXIT [TO TEST OF] PERFORM statement can only be specified within an in-line PERFORM.
An EXIT TO TEST OF PERFORM statement can only refer to format 2, 3, or 4 PERFORM statements (see section "PERFORM statement" ).
EXIT PERFORM CYCLE is a synonym for EXIT TO TEST OF PERFORM.
General rules
The associated in-line PERFORM statement is exited during an EXIT PERFORM.
Depending on the format of the PERFORM statement, different branches are made as the result of EXIT TO TEST OF PERFORM:
In a format 2 PERFORM, control passes to the test of "end of loop".
In a format 3 PERFORM, control passes to the test of "UNTIL condition".
When TEST AFTER is specified in format 4, control passes to the test of "UNTIL condition". If the condition is satisfied, the PERFORM statement is terminated. If the condition is not satisfied, augmentation is carried out.
When TEST BEFORE is specified in format 4, control is passed to the increment counter. The test of "UNTIL condition" then follows.
Example 8-39
IDENTIFICATION DIVISION. PROGRAM-ID. EXITP. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. TERMINAL IS T. DATA DIVISION. WORKING-STORAGE SECTION. 01 INPUTA PIC 99. 01 INPUT-STATUS PIC X VALUE LOW-VALUE. 88 INPUT-FINISH VALUE HIGH-VALUE. 01 AMOUNT PIC 9(3). 01 COUNTER PIC 99. 01 AVERAGE PIC Z9.9(2). PROCEDURE DIVISION. PROC SECTION. COMPUTATION. MOVE 0 TO COUNTER AMOUNT DISPLAY "Calculation of the average of numbers" UPON T PERFORM WITH TEST AFTER UNTIL INPUT-FINISH DISPLAY "Input numbers (2 digits, end at input 00)" UPON T ACCEPT INPUTA FROM T IF INPUTA IS NOT NUMERIC THEN DISPLAY "Input is not numeric or not with 2 digits!" UPON T EXIT TO TEST OF PERFORM END-IF IF INPUTA = 0 THEN SET INPUT-FINISH TO TRUE EXIT TO TEST OF PERFORM END-IF ADD 1 TO COUNTER ADD INPUTA TO AMOUNT END-PERFORM IF COUNTER > 0 THEN COMPUTE AVERAGE ROUNDED = AMOUNT / COUNTER DISPLAY "Average = " AVERAGE UPON T ELSE DISPLAY "No calculation of average performed" UPON T END-IF STOP RUN.
The program calculates the average of numbers that have been input at the terminal. End criterion is the input of 00; invalid input is reported.