Function
The VALUE clause defines the initial value of a data item in the WORKING-STORAGE SECTION and LOCAL-STORAGE SECTION, the value of a printable data item of the REPORT SECTION. The VALUE clauses in the WORKING-STORAGE SECTION, the LOCAL-STORAGE SECTION, in the FILE SECTION and in the LINKAGE SECTION are meaningful when an INITIALIZE statement with the BY VALUE phrase is executed.
In the case of condition names, the VALUE clause determines the value or range of values which is assigned to this condition name.
Format 1 | of the VALUE clause is specified to define the initial value of a data item or the value of a printable data item or the value of the sending item for the INITIALIZE statement with the BY VALUE phrase. |
Format 2 | of the VALUE clause is specified to define the value or range of values associated with a condition-name. The optional addition "WHEN SET TO FALSE IS LITERAL-4" defines the value to which the related data item is set when the "SET condition-name TO FALSE" statement is executed. |
Format 3 | serves to initialize table elements. |
Format 1
VALUE IS literal
Syntax rules
The literal specified can be replaced by a figurative constant.
A numeric literal must have a size which is within the number of positions specified by the PICTURE clause, and must not have a value which would require truncation of nonzero digits.
A non-numeric literal must not exceed the size specified in the PICTURE clause.
If the category of the item being described is alphabetic, alphanumeric, alphanumeric edited or numeric edited, the literal in the VALUE clause must be alphanumeric.The length of alphanumeric literals in the VALUE clause of an elementary item may not be greater than the length which is defined by an explicitly specified PICTURE clause.The length of alphanumeric literals in the VALUE clause of an alphanumeric group may not be greater than the length of the group.
A signed numeric literal must be associated with a PICTURE clause which provides a signed numeric character-string.
If the category of the item being described is numeric, the literal in the VALUE clause must be a numeric literal. The value of the literal must be in the range described by the PICTURE clause. All digits at positions which correspond to the PICTURE symbol P must be 0.
If the VALUE clause is used in an entry at the group level, the literal must be a figurative constant or a non-numeric literal. The VALUE clause cannot be stated at the subordinate levels within the group.
The VALUE clause must not be specified for a group item containing subordinate items with descriptions that include JUSTIFIED, SYNCHRONIZED or USAGE (other than USAGE DISPLAY or USAGE NATIONAL).
No VALUE clause may be specified for a strongly typed group item.
The VALUE clause is prohibited for external floating-point data items.
If the category of the data item is national, all literals in the VALUE clause must be national.
The length of national literals in the VALUE clause of an elementary item may not be greater than the length which is defined by an explicitly specified PICTURE clause.
The length of national literals in the VALUE clause of an alphanumeric group may not be greater than the length of the group.
General rules
If a VALUE clause is specified in a data description entry of a data item which is associated with a variable-length data item, the initialization of the data item behaves as if the value of the data item referenced by the DEPENDING ON phrase in the OCCURS clause specified for the variable-length data item had the maximum possible value. A data item is associated with a variable-length data item in any of the following cases:
It is a group data item which contains a variable-length data item.
It is a variable-length data item.
It is a data item that is subordinate to a variable-length data item.
If the VALUE clause is used in an entry at the group level, the group area will be initialized without consideration for the individual elementary or group items contained within the group.
The literal is aligned in the data item as if the data item had been described as alphanumeric. The JUSTIFIED clause has no influence here and no editing takes place.
Initialization of a data item is not affected by any BLANK WHEN ZERO or JUSTIFIED clause that may be specified.
A VALUE clause specified in a data description entry that contains an OCCURS clause or in an entry that is subordinate to a data description entry that contains an OCCURS clause causes every occurrence of the associated data item to be assigned the specified initial value.
In the WORKING-STORAGE and LOCAL-STORAGE SECTION, the VALUE clause may be used to specify the initial value of any data item; in this case, the clause causes the item to be initialized to the specified value at the start of program execution. If the VALUE clause is not specified in the description of a data item, the initial value of that item is undefined.
A data item of the class “object“ or “pointer” cannot have a VALUE clause; it is always initialized with NULL (undefined).
Example 7-33
77 FELD PICTURE IS AA VALUE IS "AA"
Here the value of FIELD is initialized to AA.
Format 2
{VALUE | VALUES} {IS | ARE} {literal-1 [{THRU | THROUGH} literal-2]} ...
[WHEN SET TO FALSE IS literal-4]
Syntax rules
A format 2 VALUE clause may be used only in connection with condition-names (level-number 88).
Level number 88 applies to declarations of condition-names which are associated with a conditional variable; these declarations are called condition-name declarations. A conditional variable is a data item which is followed by one or more condition-name declarations. A condition-name defines a value or a range of values which is to be queried as the contents of the conditional variable at the execution time of the program. A condition-name can then be "true" or "false" during program execution. A condition-name is not a data item and requires no storage space (see "Condition-name condition").
Condition names may not follow a data item for which an ANY LENGTH clause is specified.
Condition names may not follow a type definition with the STRONG phrase or a group item which is subordinate to a type definition with the STRONG phrase.The specified literals may be replaced by figurative constants.
All numeric literals must have a length which is within the number of positions specified by the PICTURE clause for the related elementary item (conditional variable), and must not have a value which would require truncation of non-zero digits.
Non-numeric literals must not exceed the size specified in the PICTURE clause for the related elementary item (conditional variable).
If the category of the item being described is alphabetic, alphanumeric, alphanumeric edited or numeric edited, the literal in the VALUE clause must be alphanumeric.The length of alphanumeric literals in the VALUE clause of an elementary item may not be greater than the length which is defined by an explicitly specified PICTURE clause.
If the category of the item being described is numeric, all literals in the VALUE clause must be numeric literals. The value of the literal must be in the range of values described by the PICTURE clause. All digits at positions which correspond to the PICTURE symbol P must be 0.
A signed numeric literal must be associated with a PICTURE clause which provides a signed numeric character-string.
When the THRU/THROUGH phrase is used, the literal preceding THRU/THROUGH must be less than the literal which follows it.
The THRU/THROUGH phrase assigns a range of values to the specified condition-name.
literal-4 may not be equal to any literal-1.
The following must apply to each literal-1, literal-2 pair: literal-4 must be less than literal-1 or greater than literal-2.
If the category of the data item is national, all literals in the VALUE clause must be national.
The length of national literals in the VALUE clause of an elementary item may not be greater than the length which is defined by an explicitly specified PICTURE clause.
General rules
The VALUE clause is prohibited for external floating-point data items and for data of the class object or pointer.
The VALUE clause must not be specified for items whose size, whether explicitly or implicitly, is variable.
The VALUE clause must not conflict with other clauses in the data description of an item or in the data description within the hierarchy of an item. The following rules are applicable:
The value is aligned in the data item as if the data item had been described as alphanumeric.
Format 2 of the VALUE clause is only allowed in the FILE, WORKING-STORAGE, LOCAL-STORAGE and LINKAGE SECTION. It must not be specified in the REPORT SECTION.
The specification of FALSE in the VALUE clause is relevant only when the condition-name is used in a SET-TO-FALSE statement.
Example 7-34
02 CITIES PICTURE 9. 88 BERLIN VALUE 1. 88 HAMBURG VALUE 2. 88 MUNICH VALUE 3. 88 COLOGNE VALUE 4.
Here, CITIES is the conditional variable, and BERLIN, HAMBURG, MUNICH, and COLOGNE are the condition-names. If a statement IF MUNICH GO TO TEST-C were written in the Procedure Division, then the value of the conditional variable CITIES would be compared to the value 3; this statement would be equivalent to the statement
IF CITIES IS EQUAL TO 3 GO TO TEST-C.
Example 7-35
02 AGE PICTURE 99. 88 TWENTIES VALUE 20 THRU 29. 88 THIRTIES VALUE 30 THRU 39.
If the statement IF TWENTIES... were to be written in the Procedure Division, the value of the conditional variable AGE would be compared to the values 20, 21, ... and 29. This statement would be equivalent to the statement IF AGE NOT LESS THAN 20 AND NOT GREATER THAN 29...
Example 7-36
02 NAME-OF-DAY PICTURE X(3). 88 BEGINNING-WEEK VALUE "MON" "TUE" "WED". 88 END-OF-WEEK VALUE "THRU" "FRI". 88 WEEKEND VALUE "SAT" "SUN".
If the statement IF BEGINNING-OF-WEEK... were to be written in the Procedure Division, the conditional variable NAME-OF-DAY would be compared with "MON", "TUE" and "WED". This statement would be equivalent to
IF NAME-OF-DAY IS EQUAL TO "MON" OR "TUE" OR "WED"...
Format 3
{{VALUE | VALUES} [FROM ({subscript-1}...)] [IS | ARE]
{literal-2}... [REPEATED {integer-1 TIMES | TO END}]} ...
Syntax rules
All numeric literals in a VALUE clause of an item must have a value which is within the range of values indicated by the associated PICTURE clause, and must not have a value which would require truncation of non-zero digits.
Non-numeric literals in a VALUE clause of an item must not exceed the size indicated by the associated PICTURE clause.
If the category of the item being described is alphabetic, alphanumeric, alphanumeric edited or numeric edited, all literals in the VALUE clause must be alphanumeric literals.The length of alphanumeric literals in the VALUE clause of an elementary item may not be greater than the length which is defined by an explicitly specified PICTURE clause. The length of alphanumeric literals in the VALUE clause of an alphanumeric group may not be greater than the length of the group.
If the VALUE clause is used in an entry at the group level, the literal must be a figurative constant or a non-numeric literal, and the group area is initialized without consideration for the individual elementary or group items contained within this group. The VALUE clause must not be stated at the subordinate levels within this group.
The VALUE clause must not be specified for a group item containing data items with descriptions including JUSTIFIED, SYNCHRONIZED or USAGE (other than USAGE DISPLAY or USAGE NATIONAL).
When format 3 is specified, the data description entry must contain an OCCURS clause or be subordinate to a data description entry that contains an OCCURS clause.
Subscript-1 must be a numeric literal that is an integer. If all subscripts have the value 1, no subscripts need be specified; otherwise, all subscripts required to reference an individual element in a table must be specified.
The number of table elements to be initialized is determined as follows:
If integer-1 is not specified, it is the number of repetitions of literal-2.
If integer-1 is specified, it is the number of repetitions of literal-2 times integer-1.
The number of table elements to be initialized must not exceed the maximum number of occurrences in the table from the point of reference to the end of the table.
If multiple format 3 VALUE clauses are specified in an entry:
The TO END phrase may be specified only once.
A specified table element may be referenced only once.
If the category of the data item is national, all literals in the VALUE clause must be national.
The length of national literals in the VALUE clause of an elementary item may not be greater than the length which is defined by an explicitly specified PICTURE clause.
The length of national literals in the VALUE clause of an alphanumeric group may not be greater than the length of the group.
General rules
- All formats of the VALUE clause can be used in one table.
- Within the same data description entry, if more than one VALUE clause references the same table element, the value defined by the last specified VALUE clause in the data description entry is assigned to the table element.
- A format 3 VALUE clause initializes a table element to the value of literal-2. The table element initialized is identified by subscript-1. Consecutive table elements are initialized, in turn, to the successive occurrences of the value of literal-2. Consecutive table elements are referenced by augmenting by 1 the subscript that represents the least inclusive dimension of the table. When any reference to a subscript, prior to augmenting it, is equal to the maximum number of occurrences specified by its corresponding OCCURS clause, that subscript is set to 1 and the subscript for the next most inclusive dimension of the table is augmented by 1.
- If the REPEATED phrase is specified, all occurrences of literal-2 are reused, in the order specified.
If the TO END phrase is specified, this reuse occurs until the end of the table is reached. If the integer-1 TIMES phrase is specified, the occurrences of literal-2 are reused, in the order specified, integer-1 times.
If the REPEATED phrase is not specified, the occurrences of literal-2 are used, in the order specified, only once. - If a VALUE clause is specified in a data description entry of a data item which is associated with a variable-occurrence data item, the initialization of the data item behaves as if the value of the data item referenced by the DEPENDING ON phrase in the OCCURS clause specified for the variable-occurrence data item is set to the maximum number of occurrences as specified by that OCCURS clause. A data item is associated with a variable-occurrence data item in any of the following cases:
- It is a group data item which contains a variable-occurrence data item.
- It is a variable-occurrence data item.
- It is a data item that is subordinate to a variable-occurrence data item.
The VALUE clause must not conflict with other clauses in the data description of the item or in the data description within the hierarchy of the item. The following rules apply:
If the category of the item is “numeric”, all literals in the VALUE clause must be numeric. The literal is aligned in the data item according to the standard alignment rules.
The literal is aligned in the data item as if the data item had been described as alphanumeric. The JUSTIFIED clause has no influence here and no editing takes place.
A data item is initialized regardless of whether a BLANK WHEN ZERO or JUSTIFIED clause was specified.
Example 7-37
IDENTIFICATION DIVISION. PROGRAM-ID. TAB. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. TERMINAL IS T. DATA DIVISION. ***** WORKING-STORAGE SECTION. 01 FIELD1. 02 A OCCURS 20. 03 B OCCURS 4. 49 PIC X(01) VALUE FROM (5 2) IS "1" "2" "3" REPEATED 4. * 01 FIELD2. 02 Z PIC 99. 02 A OCCURS 1 TO 78 DEPENDING ON Z. 49 PIC X VALUE "x". * 01 FIELD3. 02 A OCCURS 20 VALUE FROM (1) IS "ab" "c" REPEATED 10 TIMES. 03 B OCCURS 4. 49 PIC X. PROCEDURE DIVISION. MAIN SECTION. P1. MOVE 78 TO Z. DISPLAY FIELD1 UPON T. DISPLAY FIELD2 UPON T. DISPLAY FIELD3 UPON T. STOP RUN.
This results in the following field assignments:
FIELD1: | B(5,2) = "1" B(5,3) = "2" B(5,4) = "3" | B(6,1) = "1" B(6,2) = "2" B(6,3) = "3" B(6,4) = "1" | B(7,1) = "2" . . . | B(8,1) = "3" |
All other table elements are not assigned
FIELD2 | 78 times "x" | |
FIELD3: | A(1) = "ab'BLANK''BLANK'" A(3) = "ab'BLANK''BLANK'" ... A(19) = "ab'BLANK''BLANK'" | A(2) = "c'BLANK''BLANK''BLANK'" A(4) = "c'BLANK''BLANK''BLANK'" ... A(20) = "c'BLANK''BLANK''BLANK'" |