PROCEDURE DIVISION Statements and Sentences
There are three types of statements and sentences in the PROCEDURE
DIVISION:
* Conditional statements and sentences.
* Compiler directing statements and sentences.
* Imperative statements and sentences.
Conditional Statements and Sentences
A conditional statement specifies that a condition is to be tested, and
depending upon the truth value of the condition, determines the action of
the object program.
HP COBOL II contains the following conditional statements:
* EVALUATE, IF, SEARCH, or RETURN statement.
* READ statement specifying the AT END, NOT AT END, INVALID KEY,
NOT INVALID KEY phrase.
* WRITE statement specifying the INVALID KEY, NOT INVALID KEY,
END-OF-PAGE or NOT AT END-OF-PAGE phrase.
* START, REWRITE, or DELETE statement specifying the INVALID KEY, or
NOT INVALID KEY phrase.
* Arithmetic statements (ADD, COMPUTE, DIVIDE, MULTIPLY, or
SUBTRACT) specifying the ON SIZE ERROR or NOT ON SIZE ERROR
phrase.
* STRING or UNSTRING statements specifying the ON OVERFLOW or NOT
ON OVERFLOW phrase.
* CALL statement specifying the ON OVERFLOW, ON EXCEPTION, or NOT
ON EXCEPTION phrase.
* ACCEPT statement specifying the ON INPUT ERROR, or NOT ON INPUT
ERROR phrase.
A conditional sentence is a conditional statement, optionally preceded by
an imperative statement, terminated by a period followed by a space.
Compiler Directing Statements and Sentences
A compiler directing statement consists of a compiler directing verb
(either COPY, USE or REPLACE) followed by the verb's operands. It
causes the compiler to take a specific action during compilation.
A compiler directing sentence is a single compiler directing statement
terminated by a period followed by a space.
Imperative Statements and Sentences
An imperative statement either begins with an imperative verb and
specifies an unconditional action to be taken, or it is a conditional
statement that is delimited by its explicit scope terminator (delimited
scope statement). Scope terminators are described later in this chapter.
An imperative statement may consist of a sequence of one or more
imperative statements.
Note that when the phrase imperative-statement appears in a format, it
refers to that sequence of consecutive imperative statements that must be
ended in one of the following ways:
* By a period.
* By an ELSE phrase associated with a previous IF statement.
* By a WHEN phrase associated with a previous SEARCH statement.
* By the verb's explicit scope terminator.
An imperative sentence is an imperative statement terminated by a period
followed by a space. Verbs used in forming imperative statements are
shown in Table 8-1 below.
Table 8-1. Imperative Verbs
-------------------------------------------------------------------------------
| | | |
| ACCEPT(1) ON INPUT | EXCLUSIVE | RELEASE |
| ERROR | | |
| | | |
| ADD(2) ON SIZE ERROR | EXAMINE | REWRITE(3) INVALID KEY |
| | | |
| ALTER | EXIT | SET |
| | | |
| CALL(4) ON OVERFLOWON | GO TO | SORT |
| EXCEPTION | | |
| | | |
| CANCEL | GOBACK | START (3) |
| | | |
| CLOSE | INITIALIZE | STOP |
| | | |
| COMPUTE(2) | INSPECT | STRING (5) ON OVERFLOW |
| | | |
| CONTINUE | MERGE | SUBTRACT (2) |
| | | |
| DELETE (3) | MOVE | TERMINATE |
| | | |
| DISPLAY | MULTIPLY (2) | UN-EXCLUSIVE |
| | | |
| DIVIDE (2) | OPEN | UNSTRING (5) |
| | | |
| ENTER | PERFORM | WRITE (6) INVALID KEY |
| | | END-OF-PAGE |
| | | |
| EVALUATE | READ (7) AT END INVALID | |
| | KEY | |
| | | |
-------------------------------------------------------------------------------
(1) Without the optional and NOT ON INPUT ERROR phrase.
(2) Without the optional and NOT ON SIZE ERROR phrases.
(3) Without the optional and NOT INVALID KEY phrases.
(4) Without the optional , , and NOT ON EXCEPTION phrases.
(5) Without the optional and NOT ON OVERFLOW phrases.
(6) Without the optional , NOT INVALID KEY, , and NOT AT END-OF-PAGE
phrases.
(7) Without the optional , NOT AT END, , and NOT INVALID KEY phrases.
Categories of Statements
HP COBOL II statements fall into 11 categories. These categories, and
the verbs used in them, are listed in Table 8-2 .
Table 8-2. Categories of Statements
--------------------------------------------------------------------------------------------
| | |
| Category | Verbs |
| | |
--------------------------------------------------------------------------------------------
| | |
| Arithmetic | ADD |
| | COMPUTE |
| | DIVIDE |
| | MULTIPLY |
| | SUBTRACT |
| | |
--------------------------------------------------------------------------------------------
| | |
| Compiler | COPY |
| Directing | REPLACE |
| | USE |
| | |
--------------------------------------------------------------------------------------------
| | |
| Conditional | ACCEPT (ON INPUT ERROR or NOT ON INPUT ERROR) |
| | ADD (SIZE ERROR or NOT ON SIZE ERROR) |
| | CALL (ON OVERFLOW, ON EXCEPTION, NOT ON EXCEPTION) |
| | COMPUTE (SIZE ERROR or NOT ON SIZE ERROR) |
| | DELETE (INVALID KEY or NOT INVALID KEY) |
| | DIVIDE (SIZE ERROR or NOT ON SIZE ERROR) |
| | EVALUATE |
| | IF |
| | MULTIPLY (SIZE ERROR or NOT ON SIZE ERROR) |
| | READ (AT END, NOT AT END INVALID KEY, |
| | or NOT INVALID KEY) |
| | RETURN (AT END or NOT AT END) |
| | REWRITE (INVALID KEY or NOT INVALID KEY) |
| | SEARCH |
| | START (INVALID KEY or NOT INVALID KEY) |
| | STRING (ON OVERFLOW or NOT ON OVERFLOW) |
| | SUBTRACT (SIZE ERROR or NOT ON SIZE ERROR) |
| | UNSTRING (ON OVERFLOW or NOT ON OVERFLOW) |
| | WRITE (INVALID KEY, NOT INVALID KEY, END-OF-PAGE, |
| | or NOT AT END-OF-PAGE) |
| | |
--------------------------------------------------------------------------------------------
| | |
| Data | ACCEPT (DATE, DAY, DAY-OF-WEEK, or TIME) |
| Movement | EXAMINE (REPLACING) |
| | INITIALIZE |
| | INSPECT (REPLACING) (CONVERTING) |
| | MOVE |
| | STRING |
| | UNSTRING |
| | |
--------------------------------------------------------------------------------------------
Table 8-2. Categories of Statements (cont.)
--------------------------------------------------------------------------------------------
| | |
| Category | Verbs |
| | |
--------------------------------------------------------------------------------------------
| | |
| Ending | STOP |
| | STOP RUN |
| | GOBACK (in main program) |
| | |
--------------------------------------------------------------------------------------------
| | |
| Input-Output | ACCEPT (identifier) |
| | CLOSE |
| | DELETE |
| | DISPLAY |
| | EXCLUSIVE |
| | OPEN |
| | READ |
| | REWRITE |
| | SEEK |
| | START |
| | STOP (literal) |
| | UN-EXCLUSIVE |
| | WRITE |
| | |
--------------------------------------------------------------------------------------------
| | |
| Interprogram | CALL |
| Communication | CANCEL |
| | ENTRY |
| | EXIT PROGRAM |
| | GOBACK |
| | |
--------------------------------------------------------------------------------------------
| | |
| Ordering | MERGE |
| | RELEASE |
| | RETURN |
| | SORT |
| | |
--------------------------------------------------------------------------------------------
| | |
| Procedure | ALTER |
| Branching | CALL |
| | EXIT |
| | GO TO |
| | PERFORM |
| | |
--------------------------------------------------------------------------------------------
| | |
| Table | SEARCH |
| Handling | SET |
| | |
--------------------------------------------------------------------------------------------
| | |
| No Operation | CONTINUE |
| | |
--------------------------------------------------------------------------------------------
Scope Terminators
Scope terminators mark the end of the PROCEDURE DIVISION statements that
contain them. There are two types of scope terminators: explicit and
implicit.
The explicit scope terminators are:
END-ACCEPT END-IF END-SEARCH
END-ADD END-MULTIPLY END-START
END-CALL END-PERFORM END-STRING
END-COMPUTE END-READ END-SUBTRACT
END-DELETE END-RETURN END-UNSTRING
END-DIVIDE END-REWRITE END-WRITE
END-EVALUATE
Examples
In the following example, the READ and IF statements have explicit scope
terminators.
READ IN FILE
AT END
MOVE 'YES' TO EOF-SW
IF IN-COUNT = 0
DISPLAY "EMPTY FILE"
END-IF
END-READ
The implicit scope terminators are:
* At the end of a sentence: the separator period, which terminates
the scope of all previous statements not yet terminated.
* Within any statement containing another statement: the next
phrase of the containing statement following the contained
statement terminates the scope of any unterminated statement.
ELSE, WHEN, and NOT AT END are examples of such phrases.
In the next example, the IF statement in line 2 is terminated by the ELSE
clause on line 6. The IF statement on line 1 is terminated by the period
(.) on line 7.
1 IF HOURS > 40
2 IF PAYCODE = NONEXEMPT
3 PERFORM OVERTIME
4 ELSE
5 PERFORM NORMAL-PAY
6 ELSE
7 PERFORM NORMAL-PAY.