Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

CONTINUE statement

The CONTINUE statement is a no operation statement. It indicates that no executable statement is present. Processing is continued with the next executable statement.

Format


CONTINUE


Syntax rule

  1. The CONTINUE statement may be used anywhere a conditional statement or an imperative-statement may be used.

General rule

  1. The CONTINUE statement has no effect on the execution of the program.

Example 8-29

IDENTIFICATION DIVISION.
PROGRAM-ID. CONT1.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SPECIAL-NAMES.
    TERMINAL IS T.
DATA DIVISION.
WORKING-STORAGE SECTION.
77 N PIC 9.
77 K PIC 9(3).
77 Z PIC 9(6) VALUE ALL ZERO.
77 E PIC 9(3).
PROCEDURE DIVISION.
PROC SECTION.
INPUT-PAR.
    DISPLAY "Enter upper limit N" UPON T.
    ACCEPT N FROM T.
    IF N NUMERIC
    THEN 
     CONTINUE
    ELSE 
     DISPLAY "Incorrect entry" UPON T
     PERFORM INPUT-PAR
    END-IF.
COMPUTATION.
    PERFORM WITH TEST BEFORE VARYING K FROM 1 BY 1 UNTIL K > N
      COMPUTE E = K ** 3
      ADD E TO Z
    END-PERFORM
    DISPLAY "Result = " Z UPON T.
FINISH-PAR.
    STOP RUN.

The effect of CONTINUE is to make the IF statement syntactically correct even though the THEN branch does not contain an executable statement.

Example 8-30

READ INPUT-DATEI AT END CONTINUE.

AT END is used in order to avoid program abortion at the end of the file; CONTINUE specifies the unconditional statement which is required by the statement syntax, even though nothing is to be done at this point in the program.