VMS Help  —  COBOL  ENVIRONMENT_DIVISION
  The Environment Division describes the program's physical environment.  It
  also specifies input-output control and describes special control
  techniques and hardware characteristics.

  Format -

  [ ENVIRONMENT DIVISION.

  [ CONFIGURATION SECTION.
  [ SOURCE-COMPUTER. [source-computer-entry] ]
  [ OBJECT-COMPUTER.  [object-computer-entry] ]
  [ SPECIAL-NAMES.  [special-names-entry] ] ]

  [ INPUT-OUTPUT SECTION.
    FILE-CONTROL. {file-control-entry} ...
  [ I-O-CONTROL. [input-output-control-entry] ] ] ]

1  –  SOURCE-COMPUTER

  The SOURCE-COMPUTER paragraph specifies the computer on which the source
  program is to be compiled.

  Format -

   SOURCE-COMPUTER. [ { Alpha         } [WITH DEBUGGING MODE] . ]
                    [ { I64           } [WITH DEBUGGING MODE] . ]
                    [ { computer-type }                         ]

1.1  –  computer-type

  is a user-defined word that names the computer.

2  –  OBJECT-COMPUTER

  The OBJECT-COMPUTER paragraph describes the computer on which the program
  is to execute.

  Format -

   OBJECT-COMPUTER. [ { Alpha         }
                    [ { I64           }
                    [ { computer-type }

     [                     { WORDS      } ]
     [ MEMORY SIZE integer { CHARACTERS } ]
     [                     { MODULES    } ]

     [ PROGRAM COLLATING SEQUENCE IS alphabet-name ]

     [ SEGMENT-LIMIT IS segment-number] . ]

2.1  –  computer-type

  is a user-defined word that names the computer.

2.2  –  alphabet-name

  is the name of a collating sequence defined in the ALPHABET clause of
  the SPECIAL-NAMES paragraph.

2.3  –  segment-number

  is an integer from 1 through 49.

3  –  SPECIAL-NAMES

  The SPECIAL-NAMES paragraph: (1) associates compiler features and
  OpenVMS logical names with user-defined mnemonic-names, (2) defines
  symbolic-characters, (3) specifies the currency sign, (4) selects the
  decimal point, (5) relates alphabet-names to character sets or
  collating sequences, (6) relates class-names to character sets,
  (7) provides for cursor positioning for an ACCEPT (Format 5) statement,
  and (8) provides information on the cause of termination of an ACCEPT
  (Format 5) statement.

  Format -

   SPECIAL-NAMES. [

   [ { CARD-READER       }                                            ]
   [ { PAPER-TAPE-READER }                                            ]
   [ { CONSOLE           } IS device-name                             ]
   [ { LINE-PRINTER      }                                            ]
   [ { PAPER-TAPE-PUNCH  }                                            ]
   [                                                                  ]
   [C01 IS top-of-page-name                                           ]
   [                                                                  ] ...
   [SWITCH switch-name                                                ]
   [ { IS switch-name                                            }    ]
   [ {        [ON STATUS IS cond-name] [OFF STATUS IS cond-name] }    ]
   [ { IS switch-name                                            }    ]
   [ {        [OFF STATUS IS cond-name] [ON STATUS IS cond-name] }    ]
   [ { ON STATUS IS cond-name [OFF STATUS IS cond-name]          }    ]
   [ { OFF STATUS IS cond-name [ON STATUS IS cond-name]          }    ]

   [                          { ASCII                               } ]
   [                          { STANDARD-1                          } ]
   [                          { STANDARD-2                          } ]
   [ALPHABET alphabet-name IS { NATIVE                              } ] ...
   [                          { EBCDIC                              } ]
   [                          { {first-literal                }     ] ]
   [                          { { [{ THRU    } last-literal ] } ... } ]
   [                          { { [{ THROUGH }              ] }     } ]
   [                          { { [{ ALSO lit } ...         ] }     } ]

   [SYMBOLIC CHARACTERS                                               ]
   [     {{{symbolic-char} ... { IS  } {char-val} ... } ...   }       ] ...
   [     {{                    { ARE }                }       }       ]
   [     {{                                [IN alphabet-name] } ...   ]

   [CLASS class-name IS {first-literal [{THROUGH} last-literal]}      ]
   [                    {              [{THRU   }             ]} ...  ] ...

   [CURRENCY SIGN IS char]

   [DECIMAL-POINT IS COMMA]

   [CURSOR IS cursor-position]

   [CRT STATUS IS crt-status-code]. ]

3.1  –  device-name

  is a mnemonic-name for a device.  It always possesses the global
  attribute.  Only the ACCEPT and DISPLAY statements can refer to it.

3.2  –  top-of-page-name

  is the first line of a logical page (top-of-page).  It always possesses
  the global attribute.  Only the WRITE statement can refer to it.

3.3  –  switch-num

  is the number of a program switch. Its value can range from 1 through
  16.

3.4  –  switch-name

  is a mnemonic-name for the program switch.

3.5  –  cond-name

  is a condition-name for the "on" or "off" status of the switch.  It
  always possesses the global attribute.  Its truth value is "true" when
  the STATUS phrase matches the status of the switch, "false" when it
  does not.

3.6  –  alphabet-name

  is the user-defined word for a character set and/or collating sequence.
  It always possesses the global attribute.

3.7  –  first-literal

  is a literal.  It specifies: (1) the value of one or more alphabetic
  characters, or (2) the first in a range of values.

3.8  –  last-literal

  is a literal. It specifies the last in a range of values.

3.9  –  lit

  is a literal. It specifies an alphabetic character value.

3.10  –  symbolic-char

  is a user-defined word that names the symbolic-character.  It always
  possesses the global attribute.  The same symbolic-char cannot appear
  more than once in the SYMBOLIC CHARACTERS clause.

3.11  –  char-val

  is an integer that indicates the ordinal position of a character in the
  native character set.

3.12  –  class-name

  is the user-defined word for a class. It always possesses the global
  attribute

3.13  –  char

  is a one-character nonnumeric literal that specifies the currency
  symbol.  It cannot be a symbolic character.

3.14  –  cursor-position

  is a data item declared in the Working-Storage Section of the program.
  It is either an elementary unsigned numeric integer either four or
  six characters in length, described as USAGE IS DISPLAY, or a group
  item either four or six charaters in length, consisting of two
  elementary unsigned data items.

3.15  –  crt-status-code

  is a group data item three characters in length, declared in the
  Working-Storage Section of the program.

4  –  FILE-CONTROL

  The FILE-CONTROL paragraph contains the file-related specifications.

4.1  –  1format_sequential

  FILE-CONTROL.

  Format 1 - Sequential File

   SELECT [OPTIONAL] file-name

      { ASSIGN TO  [ EXTERNAL ] file-spec     }
      {            [ DYNAMIC  ]               }
      {                                       }
      { ASSIGN TO  [ EXTERNAL ] { data-name } }
      {            [ DYNAMIC  ] { literal   } }
      {                         { DISK      } }
      {                         { PRINTER   } }

      [ RESERVE reserve-num [ AREA  ] ]
      [                     [ AREAS ] ]

      [ [ ORGANIZATION IS ] SEQUENTIAL ]

      [ BLOCK CONTAINS [smallest-block TO] blocksize { RECORDS    } ]
      [                                              { CHARACTERS } ]

      [CODE-SET IS alphabet-name]
      [PADDING CHARACTER IS pad-char]
      [RECORD DELIMITER IS STANDARD-1]
      [ACCESS MODE IS SEQUENTIAL]

      [LOCK MODE IS { AUTOMATIC [WITH LOCK ON RECORD] } ]
      [             { EXCLUSIVE                       } ]

      [FILE STATUS IS file-stat] .

4.2  –  2format_line_sequential

  FILE-CONTROL.

  Format 2 - Line Sequential File

   SELECT [OPTIONAL] file-name

      { ASSIGN TO  [ EXTERNAL ] file-spec     }
      {            [ DYNAMIC  ]               }
      {                                       }
      { ASSIGN TO  [ EXTERNAL ] { data-name } }
      {            [ DYNAMIC  ] { literal   } }
      {                         { DISK      } }
      {                         { PRINTER   } }

      [ RESERVE reserve-num [ AREA  ] ]
      [                     [ AREAS ] ]

      [ [ ORGANIZATION IS ] LINE SEQUENTIAL ]

      [ BLOCK CONTAINS [smallest-block TO] blocksize { RECORDS    } ]
      [                                              { CHARACTERS } ]

      [CODE-SET IS alphabet-name]
      [PADDING CHARACTER IS pad-char]
      [RECORD DELIMITER IS STANDARD-1]
      [ACCESS MODE IS SEQUENTIAL]

      [LOCK MODE IS { AUTOMATIC [WITH LOCK ON RECORD] } ]
      [             { EXCLUSIVE                       } ]

      [FILE STATUS IS file-stat] .

4.3  –  3format_relative

  FILE-CONTROL.

  Format 3 - Relative File

   SELECT [OPTIONAL] file-name

      { ASSIGN TO  [ EXTERNAL ] file-spec     }
      {            [ DYNAMIC  ]               }
      {                                       }
      { ASSIGN TO  [ EXTERNAL ] { data-name } }
      {            [ DYNAMIC  ] { literal   } }
      {                         { DISK      } }
      {                         { PRINTER   } }

      [ RESERVE reserve-num [ AREA  ] ]
      [                     [ AREAS ] ]

      [ ORGANIZATION IS ] RELATIVE

      [ BLOCK CONTAINS [smallest-block TO] blocksize { RECORDS    } ]
      [                                              { CHARACTERS } ]

      [RECORD DELIMITER IS STANDARD-1]

      [                { SEQUENTIAL [RELATIVE KEY IS rel-key] } ]
      [ ACCESS MODE IS { { RANDOM  } RELATIVE KEY IS rel-key  } ]
      [                { { DYNAMIC }                          } ]

      [             { MANUAL WITH LOCK ON MULTIPLE RECORDS } ]
      [LOCK MODE IS { AUTOMATIC [WITH LOCK ON RECORD]      } ]
      [             { EXCLUSIVE                            } ]

      [FILE STATUS IS file-stat] .

4.4  –  4format_indexed

  FILE-CONTROL.

  Format 4 - Indexed File

   SELECT [OPTIONAL] file-name

      { ASSIGN TO  [ EXTERNAL ] file-spec     }
      {            [ DYNAMIC  ]               }
      {                                       }
      { ASSIGN TO  [ EXTERNAL ] { data-name } }
      {            [ DYNAMIC  ] { literal   } }
      {                         { DISK      } }
      {                         { PRINTER   } }

      [ RESERVE reserve-num [ AREA  ] ]
      [                     [ AREAS ] ]

      [ ORGANIZATION IS ] INDEXED

      [ BLOCK CONTAINS [ smallest-block TO ] blocksize { RECORDS    } ]
      [                                                { CHARACTERS } ]

      [RECORD DELIMITER IS STANDARD-1]

      [                { SEQUENTIAL } ]
      [ ACCESS MODE IS { RANDOM     } ]
      [                { DYNAMIC    } ]

      [RECORD KEY IS { rec-key | seg-key = {seg}... }             ]
      [                          [WITH DUPLICATES] [ ASCENDING  ] ]
      [                                            [ DESCENDING ] ]

      [ALTERNATE RECORD KEY IS { alt-key | seg-key = {seg}... }   ]
      [                          [WITH DUPLICATES] [ ASCENDING  ] ]
      [                                            [ DESCENDING ] ] ...

      [             { MANUAL WITH LOCK ON MULTIPLE RECORDS } ]
      [LOCK MODE IS { AUTOMATIC [WITH LOCK ON RECORD]      } ]
      [             { EXCLUSIVE                            } ]

      [FILE STATUS IS file-stat] .

4.5  –  5format_sort-merge

  FILE-CONTROL.

  Format 5 - Sort or Merge File

   SELECT file-name

      { ASSIGN TO  [ EXTERNAL ] file-spec     }
      {            [ DYNAMIC  ]               }
      {                                       }
      { ASSIGN TO  [ EXTERNAL ] { data-name } }
      {            [ DYNAMIC  ] { literal   } }
      {                         { DISK      } }
      {                         { PRINTER   } }

4.6  –  6format_report

  FILE-CONTROL.

  Format 6 - Report File

   SELECT file-name

      { ASSIGN TO  [ EXTERNAL ] file-spec     }
      {            [ DYNAMIC  ]               }
      {                                       }
      { ASSIGN TO  [ EXTERNAL ] { data-name } }
      {            [ DYNAMIC  ] { literal   } }
      {                         { DISK      } }
      {                         { PRINTER   } }

      [ RESERVE reserve-num [ AREA  ] ]
      [                     [ AREAS ] ]

      [ [ ORGANIZATION IS ] SEQUENTIAL ]

      [ BLOCK CONTAINS [smallest-block TO] blocksize { RECORDS    }]
      [                                              { CHARACTERS }]

      [CODE-SET IS alphabet-name]
      [PADDING CHARACTER IS pad-char]
      [RECORD DELIMITER IS STANDARD-1]
      [ACCESS MODE IS SEQUENTIAL]
      [FILE STATUS IS file-stat] .

4.7  –  clauses

4.7.1  –  ASSIGN

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

  Format -

   ASSIGN TO file-spec

4.7.1.1  –  file-spec

  is a nonnumeric literal or a COBOL word formed according to the
  rules for user-defined names.  It represents a partial or complete
  file specification.

4.7.2  –  BLOCK_CONTAINS

  The BLOCK CONTAINS clause specifies the size of a physical record.

  Format -

   BLOCK CONTAINS [smallest-block TO] blocksize { RECORDS    }
                                                { CHARACTERS }

4.7.2.1  –  smallest-block

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

4.7.2.2  –  blocksize

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

4.7.3  –  CODE-SET

  The CODE-SET clause specifies the representation of data on external
  media.

  Format -

   CODE-SET IS alphabet-name

4.7.3.1  –  alphabet-name

  is the name of a character set defined in the SPECIAL-NAMES
  paragraph.  It cannot be described with literals in the ALPHABET
  clause.

4.7.4  –  LOCK_MODE

  The LOCK MODE clause specifies a locking technique to use for a
  file. LOCK MODE is part of the X/Open COBOL standard.

  Format -

      [             { MANUAL WITH LOCK ON MULTIPLE RECORDS } ]
      [LOCK MODE IS { AUTOMATIC [WITH LOCK ON RECORD]      } ]
      [             { EXCLUSIVE                            } ]

4.7.5  –  ORGANIZATION

  The ORGANIZATION clause specifies a file's logical structure.

  Format -

                       { SEQUENTIAL      }
   [ ORGANIZATION IS ] { LINE SEQUENTIAL }
                       { RELATIVE        }
                       { INDEXED         }

4.7.6  –  PADDING_CHARACTER

  The PADDING CHARACTER clause specifies the character to be used to
  pad blocks in sequential files.

  Format -

   PADDING CHARACTER IS pad-char

4.7.6.1  –  pad-char

  is a one-character nonnumeric literal or the data-name of a
  one-character data item.  The data-name can be qualified.

4.7.7  –  RECORD_DELIMITER

  The RECORD DELIMITER clause indicates the method of determining the
  length of a variable record on the external medium.  It is for
  documentation only.

  Format -

   RECORD DELIMITER IS STANDARD-1

4.7.8  –  RESERVE

  The RESERVE clause specifies the number of input-output buffers for
  a file.

  Format -

   RESERVE reserve-num [ AREA  ]
                       [ AREAS ]

4.7.8.1  –  reserve-num

  is an integer literal from 1 through 127.  It specifies the number
  of input-output areas for the file.

5  –  I-O-CONTROL

  The I-O-CONTROL paragraph specifies the input-output techniques to be
  used for a file.

  Format -

  I-O-CONTROL.

 [[      {| DEFERRED-WRITE                     |}                    ]
 [[      {| EXTENSION extend-amt               |}                    ]
 [[      {| FILL-SIZE                          |}                    ]
 [[      {| LOCK-HOLDING                       |}                    ]
 [[APPLY {| MASS-INSERT                        |} ON {file-name} ... ] ...
 [[      {|[CONTIGUOUS         ]
 [[      {|[CONTIGUOUS-BEST-TRY]
                      PREALLOCATION preall-amt |}                    ]
 [[      {| PRINT-CONTROL                      |}                    ]
 [[      {| WINDOW window-ptrs                 |}                    ]

  [     [ RECORD     ]                                               ]
  [SAME [ SORT       ]AREA FOR {same-area-file} {same-area-file} ... ] ...
  [     [ SORT-MERGE ]                                               ]

  [                           { { [END OF] { REEL } }             } ]
  [                           { {          { UNIT } } OF file-name} ]
  [RERUN [ON file-name] EVERY { { integer RECORDS   }             } ] ...
  [                           { integer CLOCK-UNITS               } ]
  [                           { condition-name                    } ]

  [MULTIPLE FILE TAPE CONTAINS {file-name [POSITION integer] } ... ] ...].]

5.1  –  extend-amt

  is an integer from 0 through 65535.  It specifies the number of blocks
  in each extension of a disk file.

5.2  –  preall-amt

  is an integer from 0 through 4,294,967,295.  It specifies the number
  of blocks to initially allocate when the program creates a disk file.

5.3  –  window-ptrs

  is an integer from 0 through 127.  Its value can also be 255.  It
  specifies the number of retrieval pointers in the window that maps the
  disk file.

5.4  –  file-name

  names a file described in a Data Division file description entry.

5.5  –  same-area-file

  names a file described in a Data Division File Description entry to
  share storage areas with every other same-area-file.
Close Help