| Previous | Contents | Index |
Additional References
The VALUE IS clause defines the values associated with condition-names, the initial value of Working-Storage Section data items, the value of Report Section printable items, the compile-time initialization of variables to the address of data, external constants, and the constant values of literal screen items.
lit
is a numeric or nonnumeric literal. In a screen description entry, it is a nonnumeric literal.external-name
names a COBOL link-time bound constant. It must define a word or longword integer value. See Technical Notes for more information.data-name
names a data item in the File or Working-Storage or Subschema Section. data-name may be qualified.low-val
is a numeric or nonnumeric literal. It is the lowest value in a range of values associated with a condition-name in a level 88 data description entry.high-val
is a numeric or nonnumeric literal. It is the highest value in a range of values associated with a condition-name in a level 88 data description entry.numeric-integer-lit
is a positive numeric integer literal.
Condition-Name Rules for Format 2
Rules for Other Data Description Entries
01 ITEMA PIC X(20) VALUE IS "12345678901234567890". 01 ITEMB PIC XX VALUE IS "NH". |
01 ITEMX PIC S9999 VALUE IS -39. 01 ITEMZ PIC 9 VALUE ZERO. |
01 ITEMC PIC 99.
88 VAL1 VALUE IS 4.
88 VAL2 VALUE IS 5 THRU 9 12.
88 VAL3 VALUES ARE 10 14 THRU 23 27 29 30.
88 VAL4 VALUES ARE 0 THRU 49, 51 THRU 99.
88 VAL5 VALUES ARE 0 10 20 30 40 50.
|
WORKING-STORAGE SECTION.
*
* System Services
*
01 BADHEADER PIC S9(9) COMP
VALUE IS EXTERNAL SS$_BADFILHDR.
01 BADNAME PIC S9(9) COMP
VALUE IS EXTERNAL SS$_BADFILENAME.
01 NORMAL PIC S9(9) COMP
VALUE IS EXTERNAL SS$_NORMAL.
*
* Record Management Services
*
01 RMSDEV PIC S9(9) COMP
VALUE IS EXTERNAL RMS$_DEV.
*
* Database
*
01 DBMDBBUSY PIC S9(9) COMP
VALUE IS EXTERNAL DBM$_DBBUSY.
01 DBMEND PIC S9(9) COMP
VALUE IS EXTERNAL DBM$_END.
*
* Run-Time Library
*
01 LIBINVARG PIC S9(9) COMP
VALUE IS EXTERNAL LIB$_INVARG.
01 LIBINVSCRPOS PIC S9(9) COMP
VALUE IS EXTERNAL LIB$_INVSCRPOS.
PROCEDURE DIVISION.
OPEN...
IF RMS-STS = BADHEADER PERFORM...
IF RMS-STS = BADNAME PERFORM 100-FIX-NAME.
|
DATA DIVISION.
WORKING-STORAGE SECTION.
01 ITEM-LIST.
02 ITEM-PROCESS-NAME.
03 PIC S9(4) COMP VALUE 15.
03 PIC S9(4) COMP VALUE EXTERNAL JPI$_PRCNAM.
03 POINTER VALUE REFERENCE PROCESS-NAME.
03 POINTER VALUE REFERENCE PROCESS-NAME-LENGTH.
02 ITEM-USER-NAME.
03 PIC S9(4) COMP VALUE 12.
03 PIC S9(4) COMP VALUE EXTERNAL JPI$_USERNAME.
03 POINTER VALUE REFERENCE USER-NAME.
03 PIC S9(9) COMP VALUE 0.
02 ITEM-CPU-TIME.
03 PIC S9(4) COMP VALUE 4.
03 PIC S9(4) COMP VALUE EXTERNAL JPI$_CPUTIM.
03 POINTER VALUE REFERENCE CPU-TIME.
03 PIC S9(9) COMP VALUE 0.
02 ITEM-TURMINAL.
03 PIC S9(4) COMP VALUE 7.
03 PIC S9(4) COMP VALUE EXTERNAL JPI$_TERMINAL.
03 POINTER VALUE REFERENCE TURMINAL.
03 POINTER VALUE REFERENCE TURMINAL-LENGTH.
02 TERMINATOR-ENTRY PIC S9(9) COMP VALUE 0.
01 PROCESS-NAME PIC X(15) VALUE SPACES.
01 PROCESS-NAME-LENGTH PIC S9(4) COMP VALUE 0.
01 USER-NAME PIC X(12) VALUE SPACES.
01 CPU-TIME PIC S9(9) COMP VALUE 0.
01 TURMINAL PIC X(7) VALUE SPACES.
01 TURMINAL-LENGTH PIC S9(4) COMP VALUE 0. <>
|
The VALUE OF ID clause specifies, replaces, or completes a file specification.
file-name
is a nonnumeric literal. It contains the full or partial file specification.data-name
is the data-name of an alphanumeric Working-Storage Section data item. It contains the full or partial file specification.
VALUE OF ID "DISK1" |
% setenv DISK1 % setenv DISK1 /usr/data/ % setenv DISK1 /usr/data/test1.dat <> |
C:> set DISK1= C:> set DISK1=\user\data\ C:> set DISK1=\user\data\test1.dat <> |
This chapter includes the general formats for all Procedure Division
statements, describes their basic elements, and explains how to use
them.
6.1 Verbs, Statements, and Sentences
A COBOL verb is a reserved word that expresses an action to be taken by the compiler or the object program. A verb and its operands make up a COBOL statement. One or more statements terminated by a separator period form a COBOL sentence.
At the statement level, actions can be further differentiated: actions taken by the object program can be conditional or unconditional. In some cases, the verb in the statement defines whether the action is conditional or unconditional. One verb, IF, always defines a conditional action. Other verbs, such as READ, can define conditional action when you use phrases with them that make the action conditional. PERFORM and MOVE are examples of verbs that always define unconditional action. Most often, however, whether an action is conditional or unconditional depends on not only which verb, but also which phrases you use in the statement.
There are four types of COBOL statements:
Table 6-1 shows the four types of COBOL statements. It also shows that the imperative statements are further subdivided into nine categories and specifies the verbs that each category includes. When associated phrases are not specified, the verb alone defines the category. For compiler-directing and conditional statements, type and category are synonymous.
| Type | Category | Verb |
|---|---|---|
| Compiler-Directing | Compiler-Directing |
COPY
REPLACE USE RECORD |
| Conditional | Conditional |
ACCEPT ([NOT] AT END or
[NOT] ON EXCEPTION) ADD ([NOT] ON SIZE ERROR) CALL ([NOT] ON EXCEPTION or [NOT] ON OVERFLOW) COMPUTE ([NOT] ON SIZE ERROR) DELETE ([NOT] INVALID KEY) DISPLAY ([NOT] ON EXCEPTION) DIVIDE ([NOT] ON SIZE ERROR) EVALUATE IF MULTIPLY ([NOT] ON SIZE ERROR) READ ([NOT] AT END or [NOT] INVALID KEY) RETURN([NOT] AT END) REWRITE ([NOT] INVALID KEY) SEARCH(AT END) START ([NOT] INVALID KEY) STRING ([NOT] ON OVERFLOW) SUBTRACT ([NOT] ON SIZE ERROR) UNSTRING ([NOT] ON OVERFLOW) WRITE ([NOT] INVALID KEY or [NOT] END-OF-PAGE) |
| Imperative | Arithmetic |
ADD (1)
COMPUTE (1) DIVIDE (1) INSPECT (TALLYING) MULTIPLY (1) SUBTRACT (1) |
| Data-Movement |
ACCEPT (DATE, DAY, DAY-OF-WEEK or TIME)
INITIALIZE INSPECT (REPLACING or CONVERTING) MOVE SET (TO TRUE) STRING (5) UNSTRING (5) |
|
| Ending | STOP | |
| Imperative | Input-Output |
ACCEPT (identifier or CONTROL KEY IN identifier)
CLOSE DELETE (3) DISPLAY OPEN READ (4) REWRITE (3) SET (TO ON or TO OFF) START (3) STOP (literal) UNLOCK WRITE (6) |
|
Inter-Program
Communications |
CALL (2)
CANCEL |
|
| Procedure-Branching |
ALTER
CALL CONTINUE EXIT GO TO PERFORM |
|
| Table-Handling |
SEARCH
SET (TO, UP BY, or DOWN BY) SORT |
|
| Ordering |
MERGE
RELEASE RETURN SORT |
|
| Report Writing |
GENERATE
INITIATE SUPPRESS TERMINATE |
|
| Delimited-Scope | Delimited-Scope |
ACCEPT (END-ACCEPT)
ADD (END-ADD) CALL (END-CALL) COMPUTE (END-COMPUTE) DELETE (END-DELETE) DIVIDE (END-DIVIDE) EVALUATE (END-EVALUATE) IF (END-IF) MULTIPLY (END-MULTIPLY) PERFORM (END-PERFORM) READ (END-READ) RETURN (END-RETURN) REWRITE (END-REWRITE) SEARCH (END-SEARCH) START (END-START) STRING (END-STRING) SUBTRACT (END-SUBTRACT) UNSTRING (END-UNSTRING) WRITE (END-WRITE) |
( 1 ) Without the optional [NOT ] ON SIZE ERROR phrase
( 2 ) Without the optional [NOT ] ON EXCEPTION or [NOT ] ON OVERFLOW phrase
( 3 ) Without the optional [NOT ] INVALID KEY phrase
( 4 ) Without the optional [NOT ] AT END or [NOT ] INVALID KEY phrase
( 5 ) Without the optional [NOT ] ON OVERFLOW phrase
( 6 ) Without the optional [NOT ] INVALID KEY or [NOT ] END-OF-PAGE phrase
Like statements, COBOL sentences also can be compiler-directing, imperative, or conditional. Sentence type depends upon the types of statements the sentence contains. Table 6-2 summarizes the contents of the three types of COBOL sentences. The remaining text in this section describes each type of statement and sentence in greater detail.
| Type | Contents of Sentence |
|---|---|
| Imperative | One or more consecutive imperative statements ending with a period |
| Conditional | One or more conditional statements, optionally preceded by an imperative statement, terminated by the separator period |
| Compiler-Directing | Only one compiler-directing statement ending with a period |
| Previous | Next | Contents | Index |