Compaq COBOL
Reference Manual


Previous Contents Index

Additional References

Examples

  1. device-name clause:


    CARD-READER IS THE-CARDS 
    CONSOLE IS LOCAL-USER 
    

    On Tru64 UNIX and Windows NT, this example allows ACCEPT and DISPLAY statements to use THE-CARDS to refer to the environment variable COBOL_CARDREADER and LOCAL-USER to refer to the environment variable COBOL_CONSOLE. <>
    On OpenVMS, this example allows ACCEPT and DISPLAY statements to use THE-CARDS to refer to the logical name COB$CARDREADER and LOCAL-USER to refer to the logical name COB$CONSOLE. <>

  2. Top-of-page-name clause:


    C01 IS STARTING-NEW-FORM 
    

    The following WRITE statement causes the line to appear on the first line of a new page:


    WRITE REPORT-REC AFTER STARTING-NEW-FORM. 
    

  3. SWITCH clause:


    SWITCH 1 IS FIRST-SWITCH ON IS ONE-ON OFF IS ONE-OFF 
    SWITCH-4 ON FOUR-ON 
    

    (Procedure Division statements can use the condition-names defined in the SWITCH clause. The SET statement can change the status of a switch.)
    The following results assume that switch 1 is on and switch 4 is off.
    Condition Truth
    Value
    IF FOUR-ON false
    IF ONE-ON true
    IF NOT ONE-OFF true
    IF ONE-ON AND NOT FOUR-ON true

  4. ALPHABET clause:


    ALPHABET EB-CONV IS EBCDIC 
    

    If a file's SELECT clause contains a CODE-SET IS EB-CONV clause, this ALPHABET clause causes translation from EBCDIC to the native character set when the program reads data from the file.

  5. User-defined collating sequence:


    ALPHABET ALPH-B IS 
        "A" THRU "Z" 
        "9" THRU "0" 
        " " ALSO "/" ALSO "\" 
        "," 
    

    This ALPHABET clause defines a collating sequence in which uppercase letters are lower than numeric characters. The space, slash (/), and backslash (\) characters have the same position in the collating sequence. The comma is the next higher character. It is implicitly followed by the rest of the character set.
    The following Procedure Division conditional statements show the effect of this ALPHABET clause when the OBJECT-COMPUTER paragraph contains the clause: PROGRAM COLLATING SEQUENCE IS ALPH-B.
    Statements Truth
    Value
    MOVE "A" TO ITEMA.
    MOVE "9" TO ITEMB.
    IF ITEMA < ITEMB


    true
    MOVE " " TO ITEMA.
    MOVE "\" TO ITEMB.
    IF ITEMA = ITEMB AND ITEMB > "Z"


    true
    MOVE "1" TO ITEMA.
    MOVE "9" TO ITEMB.
    IF ITEMA < ITEMB


    false

  6. User-defined collating sequence with numeric literals:


    ALPHABET ALPH-C IS 128 THRU 1 
    

    This clause inverts the positions of the ASCII characters.
    The following Procedure Division statements assume that the OBJECT-COMPUTER paragraph contains the SEQUENCE IS ALPH-C clause.
    Statements Truth
    Value
    MOVE "A" TO ITEMA.
    MOVE "B" TO ITEMB.
    IF ITEMA < ITEMB


    false
    MOVE "9" TO ITEMA.
    IF ITEMA < "2"

    true
    MOVE "HELLO" TO ITEMA.
    IF ITEMA > SPACES

    false

  7. SYMBOLIC CHARACTERS clause:


    SYMBOLIC CHARACTERS ESCAPE POUND DOUB-L ARE 28 36 55. 
    

    The following DISPLAY statement displays the literal "Enter value" in double width on an ANSI terminal.


    DISPLAY "Enter value" ESCAPE POUND DOUB-L. 
    

  8. CURRENCY SIGN clause:


    01  ITEMA  PIC X(5). 
    01  ITEMB  PIC X(5). 
    01  ITEMC  PIC GG,GG9.99. 
    01  ITEMD  PIC ZZZ.ZZ9,99. 
    01  ITEME  PIC ZZZ,. 
       .
       .
       .
    CURRENCY SIGN "G" 
    

    The following MOVE statements show the effect of the CURRENCY SIGN clause (the character s represents a space):
    Statement ITEMC
    Result
    MOVE 12.34 TO ITEMC sssG12.34
    MOVE 100 TO ITEMC ssG100.00
    MOVE 1000 TO ITEMC G1,000.00

  9. DECIMAL-POINT IS COMMA clause:


    01  ITEMA  PIC X(5). 
    01  ITEMB  PIC X(5). 
    01  ITEMC  PIC GG,GG9.99. 
    01  ITEMD  PIC ZZZ.ZZ9,99. 
    01  ITEME  PIC ZZZ,. 
    

    The following MOVE statements show the effect of the DECIMAL-POINT IS COMMA clause (the character s represents a space):
    Statement ITEMD
    Result
    MOVE 1 TO ITEMD ITEMD = ssssss1,00
    MOVE 1000 TO ITEMD ITEMD = ss1.000,00
    MOVE 1,1 TO ITEMD ITEMD = ssssss1,10
    MOVE 12 TO ITEME ITEME = s12,

  10. CURSOR IS clause:


    SPECIAL-NAMES. 
        CURSOR IS CURSOR-POSITION. 
     
    DATA DIVISION. 
    WORKING-STORAGE SECTION. 
     
    01  CURSOR-POSITION. 
        02  CURSOR-LINE    PIC 99. 
        02  CURSOR-COL     PIC 99. 
    

    In this example, the cursor's position is defined by data items containing a two-digit line number (CURSOR-LINE) and a two-digit column number (CURSOR-COL).

  11. CRT STATUS IS clause:


    SPECIAL-NAMES. 
     
        SYMBOLIC CHARACTERS 
            FKEY-10-VAL 
        ARE 11 
     
        CRT STATUS IS CRT-STATUS. 
            
    DATA DIVISION. 
    WORKING-STORAGE SECTION. 
            
    01  CRT-STATUS. 
        03 KEY1               PIC 9. 
        03 KEY2               PIC X. 
           88 FKEY-10         VALUE FKEY-10-VAL. 
        03 FILLER             PIC X. 
        .
        .
        .
        ACCEPT MENU-SCREEN. 
     
        IF KEY1 EQUAL "0" 
           PERFORM OPTION_CHOSEN 
     
        ELSE IF KEY1 EQUAL "1" AND FKEY-10 
           DISPLAY "You pressed the F10 key; exiting..." LINE 22. 
    

    The first two characters (KEY1 and KEY2) constitute the code that shows the cause of termination of an ACCEPT operation. (See Table 4-1.) Note that the SPECIAL-NAMES paragraph provides for the capturing of the F10 function key.

4.2 INPUT-OUTPUT Section

The INPUT-OUTPUT Section can contain two paragraphs:

The FILE-CONTROL paragraph can contain the following clauses:

The I-O-CONTROL paragraph can contain the following clauses:

This section first describes the FILE-CONTROL paragraph and its clauses, then it describes the I-O-CONTROL paragraph.

4.2.1 FILE_CONTROL

Function

The FILE-CONTROL paragraph declares the program's data files.



Note

*Clauses marked with an asterisk (*) can be in either the SELECT clause of the Environment Division or the file description entry of the Data Division. They cannot be in both places for the same file.

file-name

is the internal name of a file connector. Each file-name must have a file description (or Sort-Merge File Description) entry in the Data Division. The same file-name cannot appear more than once in the FILE-CONTROL paragraph.

Syntax Rules

All Formats

  1. SELECT is optional in the FILE-CONTROL paragraph.
  2. If SELECT is used in the FILE-CONTROL paragraph, it must be the first clause. Other clauses may follow it in any order.
  3. Each file described in the Data Division must be specified only once in the FILE-CONTROL paragraph.
  4. On OpenVMS for every format, the first form of ASSIGN TO (marked "OpenVMS ONLY") is available only on the OpenVMS Alpha operating system and only if the default /STANDARD=NOXOPEN qualifier is in effect.
    The second form of ASSIGN TO is available on the OpenVMS Alpha system if the /STANDARD=XOPEN qualifier is in effect. <>

Format 6---Report Files

  1. Each SELECT clause specifying a Report File must have a file description entry containing a REPORT clause in the Data Division of the same program.

General Rules

Formats 1, 2, 3, and 4---Sequential, Line Sequential, Relative, or Indexed Files

  1. You must specify an OPTIONAL phrase for files opened in INPUT, I-O, or EXTEND mode that need not be present when the program runs.
  2. The rules for the OPEN statement describe the effects of the OPTIONAL phrase.
  3. If the file connector referenced by file-name is an external file connector, all file control entries in the run unit that reference this file connector must have the following characteristics:

Format 6---Report Files

  1. If the file connector referenced by file-name is an external file connector, all file control entries in the run unit that reference this file connector must have the following characteristics:

Additional References

Examples

The following examples assume that the VALUE OF ID clause is not in any associated file description entry.

  1. Sequential file:


    SELECT FILE-A 
      ASSIGN TO "INFILE". 
    

    This example refers to a file with sequential organization. The word INFILE is equivalent to the nonnumeric literal "INFILE". If there is no VALUE OF ID clause, the program accesses a file named INFILE.DAT on OpenVMS Alpha systems, or a file named INFILE on Tru64 UNIX systems.

  2. Indexed file:


    SELECT OPTIONAL FILE-A 
      ASSIGN TO "INFILE" 
      ORGANIZATION INDEXED. 
    

    In this example, the SELECT clause specifies that the indexed file need not be present when the program opens it for INPUT, I-O, or EXTEND.

  3. Sort or merge file:


    SELECT SORT-FILE 
      ASSIGN TO "SDFILE". 
    

  4. Report file:


    SELECT SUMMARY-REPORT 
      ASSIGN TO "OUTFIL" 
      FILE STATUS IS REPORT-ERRORS. 
    

4.2.2 ASSIGN

Function

The ASSIGN clause associates a file with a partial or complete file specification.


file-spec

on OpenVMS is either a nonnumeric literal or a COBOL word formed according to the rules for user-defined names. It represents a partial or complete file specification. It must conform to the rules for file specifications as defined by RMS. <>

data-name

is the name of a COBOL data item that contains a partial or complete file specification.

literal

is a nonnumeric literal containing a partial or complete file specification.

DISK

uses the file specification declared in the optional VALUE OF ID clause as the file name. If the VALUE OF ID clause is not present, file-name-1 is used as the file name in the current directory.

PRINTER

creates a print file as if the PRINT-CONTROL phrase of the APPLY clause were specified in the I-O CONTROL paragraph. A print file should contain only printable characters and line and page advancing information written using the ADVANCING clause of the WRITE verb.

REEL or UNIT

on Tru64 UNIX, creates the file on a magnetic tape using the ANSI standard format as defined by American National Standard X3.27-1978 (Level 3), Magnetic Tape Labels and File Structure for Information Interchange. <>

Syntax Rules

  1. data-name cannot be DISK or PRINTER.
  2. EXTERNAL and DYNAMIC are allowed for syntax compatibility with other COBOL vendors. They are treated as documentation only.
  3. On OpenVMS, format 1 is available only on the OpenVMS Alpha operating system and only if the default /STANDARD=NOXOPEN qualifier is in effect.
    Format 2 is available on the OpenVMS Alpha operating system if the /STANDARD=XOPEN qualifier is in effect. <>
    On Tru64 UNIX and Windows NT, format 2 is the default. <>

General Rules

  1. If there is no VALUE OF ID clause in the file description entry, or that clause contains no file specification, the file specification in the ASSIGN clause is the file specification.
  2. If there is a file specification in an associated VALUE OF ID clause, the ASSIGN clause contains the default file specification. File specification components in the VALUE OF ID clause override those in the ASSIGN clause.
  3. On OpenVMS if file-spec is not a literal, the compiler:
  4. file-spec may contain a logical name. <>
  5. If you specify ASSIGN TO unquoted string, you need not specify this name in the WORKING-STORAGE section. For example:


    ASSIGN TO TEST1 
    
    This assignment would use "TEST1.DAT" on OpenVMS Alpha. <>
    On Tru64 UNIX and Windows NT systems, you would specify:


    ASSIGN TO "TEST1.DAT" 
    
    or:


    ASSIGN TO TEST1 
    ... 
    WORKING-STORAGE SECTION. 
    01 TEST1 PIC X(9) VALUE IS "TEST1.DAT". 
    

  6. The file specification derived from one or both of the ASSIGN and VALUE OF ID clauses might refer to an environment variable.
  7. On Tru64 UNIX and Windows NT systems "" is not a valid file specification. <>
  8. Tru64 UNIX and Windows NT on all platforms, file-spec must conform to the rules of the operating system where the run-time I-O occurs.
    For indexed files, file-spec must conform to the rules of the ISAM package being used. Some older versions of ISAM on Tru64 UNIX may have a 10-character maximum for file-spec length. On Windows NT, up to 128 characters are permitted for a file-spec. <>

Format 3

For files assigned to magnetic tape using ASSIGN TO REEL clause:

  1. If the length of the file name exceeds 17 characters it is truncated. Any lowercase characters in a file name are uppercased and others outside the ANSI-"a" character set are converted to 'Z'.
    An "a" character is one of the set of the digits 0,1..9, the uppercase letters A,B..Z, and the following special characters:
    SP ! " % & ' ( ) * + , - . / : ; < = > ?
  2. Magnetic tape files must be ORGANIZATION SEQUENTIAL and either fixed or variable length record format.

Technical Notes

Additional Reference

See Section 5.3.54 clause in Chapter 5, Data Division. For information on defining a file connector, see the Processing Files and Records chapter in the Compaq COBOL User Manual.

4.2.3 BLOCK CONTAINS

Function

On OpenVMS Alpha systems, the BLOCK CONTAINS clause specifies the size of a physical record. <>

On Tru64 UNIX and Windows NT systems, block size for INDEXED organization is for documentation purposes only. <>


smallest-block

is an integer literal. It specifies the minimum physical record size.

blocksize

is an integer literal. It specifies the exact or maximum physical record size.

Syntax Rule

The BLOCK CONTAINS clause can be in the file's Data Division file description entry. However, it cannot be in both the SELECT clause and the file description entry for the same file.

General Rules

  1. The BLOCK CONTAINS clause specifies physical record size.
  2. The compiler ignores smallest-block.
  3. The RECORDS phrase specifies physical record size in terms of logical records.
  4. The CHARACTERS phrase specifies physical record size in terms of characters.
    The physical record size is the maximum of: (1) blocksize bytes, and (2) the size of the largest logical record; plus any overhead bytes for variable-length records.
  5. If there is no BLOCK CONTAINS clause, physical record size assumes a default value.
    The physical record size is the size of the largest record plus any overhead bytes.
  6. The size of physical records (in characters) must be a multiple of four. Otherwise, the I/O system rounds up the physical record size to the next multiple of four.


Previous Next Contents Index