Compaq COBOL
Reference Manual


Previous Contents Index

Additional References

5.3.53 VALUE IS

Function

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.

Syntax Rules

  1. The words THRU and THROUGH are equivalent.
  2. You must associate a signed numeric literal with either of the following:
    1. A data item that has a signed numeric PICTURE character-string
    2. A COMP-1 or COMP-2 data item
  3. If you specify a numeric literal value:
    1. It must fall in the range of values defined by the data item's PICTURE clause.
    2. It must not require truncation of nonzero digits; that is, it cannot have nonzero digits in positions represented by Ps in the item's PICTURE clause.
  4. If you specify a nonnumeric literal value, it must not exceed the size defined by the data item's PICTURE clause.
  5. The Format 1, 3, and 4 VALUE IS clause cannot be used in any entry that is part of the description or redefinition of an external data record.
  6. The Format 3 VALUE IS clause is allowed only for an item containing the USAGE IS POINTER phrase.
  7. The subject of the associated data description entry in a Format 4 VALUE IS clause must define a word or longword data item.
  8. In a screen description entry, the VALUE clause can be specified only at the elementary level.

General Rules

  1. The VALUE IS clause must be consistent with other clauses in the data description of both the item and all subordinate items. The following rules apply:
  2. In the File Section, the VALUE IS clause can apply only to condition-name entries. That is, you can use the clause only for level 88 data items. In the Linkage Section, VALUE IS produces a warning for the other 88 data items.
  3. Format 2 applies only to condition-name entries.
  4. If a VALUE IS clause is specified in a data description entry that contains an OCCURS clause with a DEPENDING ON phrase, every occurrence of the associated data item is set to the maximum value.
    A data item is associated with a variable occurrence data item in any of the following cases:
    If a VALUE IS clause is associated with the data item referenced by a DEPENDING ON phrase, that value is considered to be placed in the data item after the variable occurrence data item is initialized.
  5. If a VALUE IS clause is specified in a data description entry that contains an OCCURS clause, or in an entry that is subordinate to an OCCURS clause, every occurrence of the associated data item is assigned the specified value. (This applies to General Formats 1, 3, and 4.)

Condition-Name Rules for Format 2

  1. The VALUE IS clause is required in a condition-name entry. The condition-name entry can contain only the condition-name itself and the VALUE IS clause.
  2. The characteristics of a condition-name are implicitly the same as those of its conditional variable.
  3. When using the EXTERNAL option, the associated conditional variable must be a word or longword COMP data item.
  4. When using the REFERENCE option, the associated conditional variable must be POINTER usage.
  5. If the THRU phrase is used, each low-val, external-name, and data-name must be less than the corresponding high-val, external-name, and data-name.

Rules for Other Data Description Entries

  1. A Working-Storage Section VALUE IS clause takes effect only when the program enters its initial state.
  2. The VALUE IS clause initializes the data item to the value of lit.
  3. If a data item's data description entry does not have a VALUE IS clause, the initial contents of the data item are the following:
  4. In the Report Section, if an elementary report entry contains a VALUE IS clause but does not contain a GROUP INDICATE clause, the printable item assumes the specified value each time the Report Writer Control System (RWCS) prints the Report Group. However, if the entry contains the GROUP INDICATE clause, the RWCS presents the specified value only when certain run-time conditions exist. See the description of the GROUP INDICATE clause for more information.
  5. The VALUE IS clause cannot be used in a data description entry that has a REDEFINES clause or is subordinate to a data description entry with a REDEFINES clause.
  6. The VALUE IS clause can be in a data description entry for a group item. In this case:
  7. The VALUE IS clause cannot be used in the data description entry for a group that contains subordinate items with any of the following clauses:
  8. The VALUE IS clause cannot be used in the report group description entry for a group that contains subordinate items with a JUSTIFIED clause.
  9. The Format 3 VALUE IS clause results in the compile-time initialization of its data description entry to the address of data-name or to numeric-integer-lit. Use this clause to pass arguments to non-COBOL procedures requiring an address rather than a user-defined word.
  10. In Format 4, external-name must be the name of an external symbol (a symbol in another program unit) that is known to the linker when the program is linked.
  11. The Format 4 VALUE IS clause results in the linker storing the value of external-name at the storage location defined by the data description entry containing the VALUE IS EXTERNAL clause.

Technical Notes

Additional References

Examples

  1. The following is an example of initializing alphanumeric data items:


    01  ITEMA  PIC X(20) VALUE IS "12345678901234567890". 
    01  ITEMB  PIC XX    VALUE IS "NH". 
    

  2. The following is an example of initializing numeric data items:


    01  ITEMX  PIC S9999 VALUE IS -39. 
    01  ITEMZ  PIC 9     VALUE ZERO. 
    

  3. The following is an example of assigning condition-name values:


    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. 
    

  4. The VALUE IS EXTERNAL clause allows a COBOL program to equate a mnemonic system constant to a value representing a return status code rather than the numeric equivalent. The following are some examples of this clause:
    On OpenVMS


    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. 
    

  5. The following example shows the VALUE IS REFERENCE clause:


    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.                 <>
    

5.3.54 VALUE OF ID

Function

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.

General Rules

  1. Each file specification field in file-name augments the specification in the ASSIGN clause of the SELECT statement.
  2. A file specification field in the VALUE OF ID clause overrides the corresponding field in the SELECT statement. If a file specification field is either in the SELECT statement or in the VALUE OF ID clause (but not in both), it becomes part of the file specification.
  3. On Tru64 UNIX and Windows NT systems, if you specify a VALUE OF ID clause with which you specified an OpenVMS Alpha logical, you must use an environment variable, as follows:


    VALUE OF ID "DISK1" 
    

    Define the environment variable using one of the following:
    For Tru64 UNIX systems:


    % setenv DISK1 
    % setenv DISK1 /usr/data/ 
    % setenv DISK1 /usr/data/test1.dat                       <>
    

    For Windows NT systems:


    C:> set DISK1= 
    C:> set DISK1=\user\data\
    C:> set DISK1=\user\data\test1.dat            <>
    

  4. The number of bytes in the string making up file-name or data-name must not exceed 255.

Technical Notes

Additional References


Chapter 6
Procedure Division

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.

Table 6-1 Types and Categories of COBOL Statements
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)


Legend:
( 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.

Table 6-2 Contents of COBOL Sentences
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