Compaq COBOL
Reference Manual


Previous Contents Index

  • Alphanumeric receiving item:
    (The PICTURE of ITEMA is X(4).)
      ITEMA
    Value
    ITEMB
    Description
    ITEMB
    Contents
    a. ABCD PIC X(4) ABCD
    b. ABCD PIC X(6) ABCDss
    c. ABCD PIC X(6) JUST ssABCD
    d. ABCs PIC X(6) JUST ssABCs
    e. ABCD PIC XXX ABC
    f. ABCD PIC XX JUST CD
  • Alphanumeric edited receiving item:
    (The PICTURE of ITEMA is X(7).)
      ITEMA
    Value
    ITEMB
    Description
    ITEMB
    Contents
    a. 063080s XX/99/XX 06/30/80
    b. 30JUN80 99BAAAB99 30sJUNs80
    c. 6374823 XXXBXXX/XX/X 637s482/3s/s
    d. 123456s 0XB0XB0XB0XB 01s02s03s04s
  • Numeric edited sending item:
      ITEMA
    PICTURE
    ITEMA
    Value
    ITEMB
    PICTURE
    ITEMB
    Value
    a. Z,ZZZ.99- 1,234.56- 999.999- 234.560-
    b. ZZZ,ZZZ.99- ss1,234.56- $$$,$$$.99- s$1,234.56-
    c. $$$,$$$.99CR s$1,234.56CR $$$,$$$.99- s$1,234.56-
    d. $$$,$$$.99DB s$1,234.56DB ZZZ,ZZZ.99CR ss1,234.56CR
    e. +++++.99 +1234.56 ZZZZZ.99+ s1234.56+
    f. ++++++.99 s-1234.56 ZZZZZZ.99- ss1234.56-
    g. ----- .99 -1234.56 ZZZZZ.99DB s1234.56DB
    h. ------ .99 ss1234.56 $$,$$$.99 $1,234.56
    i. $$$$.99- $123.45- /XXBXXBXXBXX/ /$1s23s.4s5-/
    j. $$$$.99- $123.45- /99B99B99B99/ /00s00s01s23/

    6.8.23 MULTIPLY

    Function

    The MULTIPLY statement multiplies two numeric operands and stores the product in one or more data items.


    num

    is a numeric literal or the identifier of an elementary numeric item.

    rsult

    is the identifier of an elementary numeric item. However, in Format 2, rsult can be an elementary numeric edited item. It is the resultant identifier.

    stment

    is an imperative statement executed when an on size error condition has occurred.

    stment2

    is an imperative statement executed when no on size error condition has occurred.

    General Rules

    1. In Format 1, the value of num is multiplied by the value of the first rsult. The product replaces the current value of the first rsult. The process repeats for each succesive occurrence of rsult.
    2. In Format 2, the values of the two operands before the word GIVING are multiplied together. The product replaces the current value of each rsult.

    Additional References

    Examples

    Each of the examples assume these data descriptions and beginning values:

    INITIAL VALUES


         03  ITEMA  PIC S99 VALUE 4.                     4 
         03  ITEMB  PIC S99 VALUE -35.                 -35 
         03  ITEMC  PIC S99 VALUE 10.                   10 
         03  ITEMD  PIC S99 VALUE 5.                     5 
    

    1. Without GIVING phrase: RESULTS


      MULTIPLY 2 BY ITEMB.                       ITEMB = -70 
      

    2. SIZE ERROR phrase:
      (When the SIZE ERROR condition occurs, the values of the affected resultant identifiers do not change.)


      MULTIPLY 3 BY ITEMB                          
        ON SIZE ERROR                            ITEMB = -35 
           MOVE 0 TO ITEMC.                      ITEMC =   0 
      

    3. NOT ON SIZE ERROR phrase:


      MULTIPLY 2 BY ITEMB                        
        ON SIZE ERROR                            ITEMB = -70 
           MOVE 0 TO ITEMC                       
        NOT ON SIZE ERROR                        
           MOVE 1 TO ITEMC.                      ITEMC =   1 
      

    4. END-MULTIPLY and MULTIPLY results with SIZE ERROR:
      (The stment in the SIZE ERROR phrase executes if any operation causes a size error condition. The first MULTIPLY statement terminates with END-MULTIPLY. The second MULTIPLY executes whether or not the SIZE ERROR condition occurs.)


        MULTIPLY 4 BY ITEMA ITEMB ITEMC 
          ON SIZE ERROR 
            MOVE 1 TO ITEMD 
        END-MULTIPLY 
        MULTIPLY 2 BY ITEMA ITEMB ITEMC 
          ON SIZE ERROR 
            ADD 1 TO ITEMD 
        END-MULTIPLY. 
       
      
      After First
      MULTIPLY
      After Second
      MULTIPLY
      ITEMA = 16 ITEMA = 32
      ITEMB = -35 ITEMB = -70
      ITEMC = 40 ITEMC = 80
      ITEMD = 1 ITEMD = 1


      If the initial value of ITEMB had been -20, a SIZE ERROR condition would not have occurred during the first MULTIPLY. However, the second MULTIPLY would have caused the condition:
      After First
      MULTIPLY
      After Second
      MULTIPLY
      ITEMA = 16 ITEMA = 32
      ITEMB = -80 ITEMB = -80
      ITEMC = 40 ITEMC = 80
      ITEMD = 5 ITEMD = 6

    6.8.24 OPEN

    Function

    The OPEN statement creates an access stream to the file, makes the file available to the program, begins the processing of a file, and specifies file sharing.


    file-name

    is the name of a file described in the Data Division. It cannot be the name of a sort or merge file.

    Leading and trailing blanks and tabs are removed from file specifications on both OpenVMS Alpha and Tru64 UNIX systems before an OPEN is attempted. Embedded blanks and tabs are removed on OpenVMS Alpha systems only.

    Syntax Rules

    Format 1---Sequential, Line Sequential, Relative, or Indexed Files

    1. The NO REWIND phrase can be used only for files with sequential organization.
    2. The I-O phrase can be used only for mass storage files.
    3. The I-O phrase cannot be used with LINE SEQUENTIAL.
    4. The EXTEND phrase can be used for sequential access mode files only.
    5. It is invalid to specify both X/Open standard (WITH [NO] LOCK or LOCK MODE) and Compaq standard (LOCK-HOLDING, ALLOWING, or REGARDLESS) file sharing for the same file connector. Hence, the WITH LOCK phrase cannot be used with the ALLOWING phrase.

    Format 2---Report Writer Files

    1. file-name must be in a file description entry containing a REPORT clause.

    General Rules

    All Files

    1. Successful OPEN statement execution:
      • Creates an access stream to the file
      • Makes the file available to the program
      • Puts the file in an open mode
      • Associates the file with file-name through the file connector
    2. An executable image can open a file-name more than once with the INPUT, OUTPUT, I-O, and EXTEND phrases. After the first OPEN statement, each later OPEN for the same file-name must follow the execution of a CLOSE statement for the file-name. However, the CLOSE statement must not have a REEL, UNIT, or LOCK phrase.
    3. The OPEN statement does not get or release the first data record.
    4. For an OPEN statement with the INPUT, I-O, or EXTEND phrases, file-name's file description entry must be equivalent to that used when the file was created.
    5. The NO REWIND phrase applies only to sequential single-reel/unit files. If the concept of rewinding does not apply to the file's storage medium, then the open is successful and an I-O status is set.
    6. If the file's storage medium allows rewinding, and:
      • There is neither an EXTEND nor a NO REWIND phrase, then OPEN statement execution positions the file at its beginning.
      • There is a NO REWIND phrase, then the OPEN statement does not reposition the file. The file must already be positioned at its beginning before the OPEN statement executes.
    7. Successful execution of an OPEN statement sets the Current Volume Pointer to:
      • The first or only reel/unit for an available input or input-output file
      • The reel/unit containing the last logical record for an extend file
      • The new reel/unit for an unavailable output, input-output, or extend file
    8. If more than one file-name is in the OPEN statement, execution is the same as if there were a separate OPEN statement for each file-name.
    9. A file's maximum record size is established when the file is created and must not subsequently be changed.

    Format 1---Sequential, Line Sequential, Relative, or Indexed Files

    1. A file is available if it is both:
      • Physically present
      • Recognized by the I-O system

      Table 6-14 shows the result of opening available and unavailable sequential, relative, and indexed files.

      Table 6-14 Opening Available and Unavailable Sequential, Line Sequential, Relative, and Indexed Files
      Open Mode File Is Available File Is Unavailable
      INPUT Normal open Error
       
      INPUT
      (Optional File)
      Normal open Normal open
      The first read causes the at end condition or invalid key condition
       
      I-O Normal open Error
       
      I-O
      (Optional File)
      Normal open The OPEN creates the file
       
      OUTPUT Creates a new version of the file
      See General Rule 24
      The OPEN creates the file
       
      EXTEND Normal open Error
       
      EXTEND
      (Optional File)
      Normal open The OPEN creates the file

    2. Successful OPEN statement execution makes the file's record area available to the program. If the file connector is an external file connector, the file has only one record area for the executable image.
    3. When a file is not in an open mode, no statement that references the file can execute either implicitly or explicitly, except for:
      • A MERGE statement
      • An OPEN statement
      • A SORT statement with the USING or GIVING phrase
    4. An OPEN statement for a file must successfully execute before any allowable input-output statement executes for the file. Table 6-15 shows allowable input-output statements by file organization, access mode, and open mode for sequential, line sequential, relative, and indexed files.

      Table 6-15 Allowable Input-Output Statements for Sequential, Line Sequential, Relative, and Indexed Files
            Open Mode
      File
      Organization
      Access
      Mode
      Statement INPUT OUTPUT I-O EXTEND
      SEQUENTIAL SEQUENTIAL READ
      REWRITE
      WRITE
      UNLOCK
      Yes
      No
      No
      Yes
      No
      No
      Yes
      Yes
      Yes
      Yes
      No
      Yes
      No
      No
      Yes
      Yes
       
      LINE SEQUENTIAL SEQUENTIAL READ
      REWRITE
      WRITE
      UNLOCK
      Yes
      No
      No
      Yes
      No
      No
      Yes
      Yes
      No
      No
      No
      No
      No
      No
      Yes
      Yes
       
      RELATIVE SEQUENTIAL DELETE
      READ
      REWRITE
      START
      WRITE
      UNLOCK
      No
      Yes
      No
      Yes
      No
      Yes
      No
      No
      No
      No
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      No
      Yes
      No
      No
      No
      No
      Yes
      Yes
         
        RANDOM DELETE
      READ
      REWRITE
      WRITE
      UNLOCK
      No
      Yes
      No
      No
      Yes
      No
      No
      No
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      No
      No
      No
      No
      No
         
        DYNAMIC DELETE
      READ
      READ NEXT
      REWRITE
      START
      WRITE
      UNLOCK
      No
      Yes
      Yes
      No
      Yes
      No
      Yes
      No
      No
      No
      No
      No
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      No
      No
      No
      No
      No
      No
      No
       
      INDEXED SEQUENTIAL DELETE
      READ
      REWRITE
      START
      WRITE
      UNLOCK
      No
      Yes
      No
      Yes
      No
      Yes
      No
      No
      No
      No
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      No
      Yes
      No
      No
      No
      No
      Yes
      Yes
         
        RANDOM DELETE
      READ
      REWRITE
      WRITE
      UNLOCK
      No
      Yes
      No
      No
      Yes
      No
      No
      No
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      No
      No
      No
      No
      No
         
        DYNAMIC DELETE
      READ
      READ NEXT
      READ PRIOR
      REWRITE
      START
      WRITE
      UNLOCK
      No
      Yes
      Yes
      Yes
      No
      Yes
      No
      Yes
      No
      No
      No
      No
      No
      No
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      Yes
      No
      No
      No
      No
      No
      No
      No
      No

    5. If the file opened with the INPUT phrase is an optional file that is not present, the OPEN statement sets the File Position Indicator to indicate this condition.
    6. An OPEN statement with the EXTEND phrase positions the file immediately after its last logical record. The definition of last logical record differs by file organization:
      • For sequential and line sequential files, it is the last record written in the file.
      • For relative files, it is the currently existing record with the highest relative record number.
      • For indexed files in ascending sort order, it is the currently existing record with the highest prime record key value.
        For indexed files in descending sort order, it is the currently existing record with the lowest prime record key.
      • For Report Writer files, the last logical record is the last record written in the file.
    7. Files for which the LINAGE clause has been specified must not be opened in the EXTEND mode.
    8. The I-O phrase opens a mass storage file for both input and output operations.
    9. The ALLOWING phrase specifies a file-sharing option for the file.
      Automatic record-locking is the system default.
      The LOCK-HOLDING option declares the manual record-locking ALLOWING phrase must be used if the program includes the LOCK-HOLDING option of the I-O-CONTROL paragraph.
    10. When LOCK MODE IS AUTOMATIC or LOCK MODE IS MANUAL is specified and WITH LOCK is not specified, the file is shareable, and can be opened by more than one access stream (except for files opened in OUTPUT mode, which cannot be shared).
    11. The NO OTHERS option or WITH LOCK option specifies exclusive file access by this access stream. The access stream created by the OPEN ALLOWING NO OTHERS or OPEN WITH LOCK statement has exclusive access to the file and, therefore, no other concurrent access stream can access (or open) the file.
    12. The READERS option permits read-only access to the file for concurrent access streams.
      However, on Tru64 UNIX and Windows NT systems, the ALLOWING READERS phrase is minimally supported for indexed files, and should not be used. See the description of file handling for indexed files in the Compaq COBOL User Manual, in the section on sharing files. <>
    13. The ALL, WRITERS, and UPDATERS phrases allow concurrent access streams access to the file.
    14. If there is no ALLOWING phrase or WITH LOCK phrase, the default file-sharing behavior for files depends on the open mode and whether X/Open standard or Compaq standard file sharing is in effect.
      For files opened in input mode:
      • Compaq standard---The default is ALLOWING READERS (see General Rule 21 for the exception).
      • X/Open standard---The default is to make the file fully shareable.

      For files opened in modes other than input mode, the default is always to make the file exclusive. (Also see General Rule 24.)
      The selection of X/Open or Compaq standard file-sharing default behavior is made as follows by the compiler:
      • If X/Open standard syntax (LOCK MODE or WITH [NO] LOCK) has been specified for file-name prior to the OPEN statement, the compiler interprets the statement according to the X/Open standard.
      • If Compaq standard syntax (LOCK-HOLDING, ALLOWING, or REGARDLESS) has been specified for file-name prior to the OPEN statement, the compiler interprets the statement according to the Compaq standard.
      • If no file-sharing syntax (LOCK-HOLDING, ALLOWING, REGARDLESS, LOCK MODE, or WITH [NO] LOCK) has been specified for file-name prior to the OPEN statement, then the compiler uses the /STANDARD=[NO]XOPEN qualifier on OpenVMS (or the Tru64 UNIX equivalent -std [no]xopen flag) to determine whether the OPEN INPUT statement is interpreted as X/Open or Compaq standard: a setting of xopen selects the X/Open standard, whereas a setting of noxopen selects the Compaq standard.

      Any subsequent I-O locking syntax for the same file connector in your program must be consistent: X/Open standard locking and Compaq standard locking (implicit or explicit) cannot be mixed for the same file connector.
    15. On Tru64 UNIX and Windows NT systems, files opened in OUTPUT mode adhere to the same file-sharing protocols as do files opened in the EXTEND and I-O modes. Access can be denied or granted depending on the file lock requested and the file lock held. <>
      On OpenVMS Alpha systems, file sharing is limited for OUTPUT mode. A higher-numbered version is always created by default. <>
      If X/Open standard file sharing is in effect, files opened in OUTPUT mode cannot be shared.
    16. On Tru64 UNIX systems, when two file connectors in one process concurrently access the same physical file, a file-locked condition is not generated. <>
      On OpenVMS Alpha and Windows NT systems, when two file connectors in one process concurrently access the same physical file, a file-locked condition might be generated. <>
    17. For files specified with a MULTIPLE FILE TAPE clause:
      • The NO REWIND phrase, if specified, is ignored.
      • Any required rewinding or positioning of the reel (or device) is accomplished according to the relative position of the file as specified in the MULTIPLE FILE TAPE clause.
    18. An OPEN OUTPUT statement for a file specified with a POSITION phrase of a MULTIPLE FILE TAPE clause is invalid unless the tape contains all the files at positions prior to the position specified.
    19. An OPEN OUTPUT statement for a file specified with a POSITION phrase of a MULTIPLE FILE TAPE clause is invalid if the tape already contains a file at the position specified.
    20. An OPEN INPUT statement for a file specified with a POSITION phrase of a MULTIPLE FILE TAPE clause is invalid unless the tape contains a file at that position, as well as all the files at the positions prior to the position specified.
    21. A file specified in a MULTIPLE FILE TAPE clause cannot be opened in either I-O or EXTEND mode.

    Format 2---Report Writer Files

    1. A file is available if it is physically present and recognized by the I-O system.
      Table 6-16 shows the results of opening available and unavailable Report Writer files.

      Table 6-16 Opening Available and Unavailable Report Writer Files
      Open Mode File Is Available File Is Unavailable
      OUTPUT Creates a new version of the file The OPEN creates the file
      EXTEND Normal OPEN The OPEN is unsuccessful
      EXTEND
      (optional file)
      Normal OPEN The OPEN creates the file

    2. Successful OPEN statement execution makes the file's record area available to the Report Writer Control System. If the file connector is an external file connector, the file has only one record area for the executable image.
    3. When a file is not in an open mode, no statement that references the file can execute either implicitly or explicitly, except for the OPEN statement.
    4. An OPEN statement for a file-name must execute successfully before an INITIATE statement executes for the file. Table 6-17 shows allowable Report Writer statements by file organization and open mode for Report Writer files.

      Table 6-17 Allowable Statements for Report Writer Files
        Open Mode
      Statement OUTPUT EXTEND
      INITIATE Yes Yes
      GENERATE Yes Yes
      SUPPRESS Yes Yes
      TERMINATE Yes Yes
      All other I-O statements No No (for record I-O only)


    Previous Next Contents Index