[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

HP COBOL
Reference Manual


Previous Contents Index


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.

  • 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 systems, if you specify a VALUE OF ID clause with which you specified an OpenVMS logical, you must use an environment variable, as follows:


      VALUE OF ID "DISK1"
      

      Define the environment variable using one of the following:


      % setenv DISK1
      % setenv DISK1 /usr/data/
      % setenv DISK1 /usr/data/test1.dat                       <>
      
    4. The number of bytes in the string making up file-name or data-name must not exceed 255.

    Technical Notes

    • file-name is a complete or partial file specification. The resultant file specification must adhere to the rules for file specifications as defined by the file system.
    • If the associated file connector is an external file connector, all file description entries in the run unit that are associated with that file connector must define the same file specification. For a data-name it must be external and reference the same data item in all programs defining the file.

    Additional References

    • Section 4.2.2
    • HP COBOL User Manual, on exception condition handling
    • On OpenVMS, OpenVMS Record Management Services Reference Manual in the OpenVMS documentation set <>


    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:

    • Compiler-directing statements specify an action taken by the compiler during compilation. See Section 6.1.1 for more information.
    • Imperative statements specify an unconditional action taken by the object program at run time. See Section 6.1.2 for more information.
    • Conditional statements specify a conditional action taken by the object program at run time. See Section 6.1.3 for more information.
    • Delimited-scope statements specify their explicit scope terminator. See Section 6.1.4 for more information.

    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


    Previous Next Contents Index