VMS Help  —  COBOL  DATA_DIVISION
  The DATA DIVISION describes data the program creates, receives as input,
  manipulates, and produces as output.

  Format -

  [ DATA DIVISION.
  [SUB-SCHEMA SECTION.
   [subschema-entry [keeplist-entry] ... ] ]
  [FILE SECTION.
   [file-description-entry {record-description-entry} ... ] ...
   [report-file-description-entry] ...
   [sort-merge-file-description-entry {record-description-entry} ... ] ... ]
  [WORKING-STORAGE SECTION.
   [record-description-entry] ... ]
  [LINKAGE SECTION.
   [record-description-entry] ... ]
  [REPORT SECTION.
   [report-description-entry {report-group-description-entry} ... ] ... ]
  [SCREEN SECTION
   [screen-description-entry] ...] ... ] ]

1  –  rf_report-file-description-entry

  The report file description entry is Format 4 of the file description
  entry.  See FD_file-description-entry subtopic report_FD (Format 4) for
  details of the syntax.

2  –  FD file-description-entry

  A file description entry describes the physical structure,
  identification, record names, and names for sequential, relative,
  indexed, and report files.  It also specifies: (1) the internal or
  external attributes of a file connector, and (2) the local or global
  attributes of a file-name.

2.1  –  sequential FD

  A file description entry describes the physical structure,
  identification, record names, and names for sequential, relative,
  indexed, and report files.  It also specifies: (1) the internal or
  external attributes of a file connector, and (2) the local or global
  attributes of a file-name.

  Format 1 - Sequential File

  FD file-name
    [IS EXTERNAL]
    [IS GLOBAL]

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

  [RECORD { CONTAINS [shortest-rec TO] longest-rec CHARACTERS          }]
  [       { IS VARYING IN SIZE [FROM shortest-rec]
                                       [ TO longest-rec ]  CHARACTERS
                                       [ DEPENDING ON depending-item ] }]

  [LABEL { RECORDS ARE } { STANDARD } ]
  [      { RECORD IS   } { OMITTED  } ]

  [VALUE OF ID IS file-spec]

  [DATA { RECORDS ARE } {rec-name} ... ]
  [     { RECORD IS   }                ]

  [ LINAGE IS page-size LINES [ WITH FOOTING AT footing-line ]
          [ LINES AT TOP top-lines ] [ LINES AT BOTTOM bottom-lines ] ]

  [CODE-SET IS alphabet-name]

  [ [ ACCESS MODE IS ] SEQUENTIAL ]

  [FILE STATUS IS file-stat] .

2.2  –  relative FD

  A file description entry describes the physical structure,
  identification, record names, and names for sequential, relative,
  indexed, and report files.  It also specifies: (1) the internal or
  external attributes of a file connector, and (2) the local or global
  attributes of a file-name.

  Format 2 - Relative File

  FD file-name
    [IS EXTERNAL]
    [IS GLOBAL]

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

  [RECORD { CONTAINS [shortest-rec TO] longest-rec CHARACTERS          }]
  [       { IS VARYING IN SIZE [FROM shortest-rec]
                                       [ TO longest-rec ]  CHARACTERS
                                       [ DEPENDING ON depending-item ] }]

  [LABEL { RECORDS ARE } { STANDARD } ]
  [      { RECORD IS   } { OMITTED  } ]

  [VALUE OF ID IS file-spec]

  [DATA { RECORDS ARE } {rec-name} ... ]
  [     { RECORD IS   }                ]

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

  [FILE STATUS IS file-stat] .

2.3  –  indexed FD

  A file description entry describes the physical structure,
  identification, record names, and names for sequential, relative,
  indexed, and report files.  It also specifies: (1) the internal or
  external attributes of a file connector, and (2) the local or global
  attributes of a file-name.

  Format 3 - Indexed File

  FD file-name
    [IS EXTERNAL]
    [IS GLOBAL]

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

  [RECORD { CONTAINS [shortest-rec TO] longest-rec CHARACTERS          }]
  [       { IS VARYING IN SIZE [FROM shortest-rec]
                                       [ TO longest-rec ]  CHARACTERS
                                       [ DEPENDING ON depending-item ] }]

  [LABEL { RECORDS ARE } { STANDARD } ]
  [      { RECORD IS   } { OMITTED  } ]

  [VALUE OF ID IS file-spec]

  [DATA { RECORDS ARE } {rec-name} ... ]
  [     { RECORD IS   }                ]

  [               { 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] ] ...

  [FILE STATUS IS file-stat] .

2.4  –  report FD

  A file description entry describes the physical structure,
  identification, record names, and names for sequential, relative,
  indexed, and report files.  It also specifies: (1) the internal or
  external attributes of a file connector, and (2) the local or global
  attributes of a file-name.

  Format 4 - Report File

   FD file-name
     [IS EXTERNAL]
     [IS GLOBAL]

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

  [RECORD { CONTAINS [shortest-rec TO] longest-rec CHARACTERS          }]
  [       { IS VARYING IN SIZE [FROM shortest-rec]
                                       [ TO longest-rec ]  CHARACTERS
                                       [ DEPENDING ON depending-item ] }]

  [LABEL { RECORDS ARE } { STANDARD } ]
  [      { RECORD IS   } { OMITTED  } ]

  [VALUE OF ID IS file-spec]

  [ [ACCESS MODE IS] SEQUENTIAL]

  { REPORT IS   } {report-name} ...
  { REPORTS ARE }

  [CODE-SET IS alphabet-name]

  [FILE STATUS IS file-stat] .

3  –  SD sort-merge-file-description-entry

  A sort-merge file description entry describes a sort or merge file's
  physical structure, identification, and record names.

  Format -

  SD file-name

    [RECORD { CONTAINS [shortest-rec TO] longest-rec CHARACTERS        }]
    [       { IS VARYING IN SIZE [FROM shortest-rec] [TO longest-rec]
                              CHARACTERS [DEPENDING ON depending-item] }]

    [DATA { RECORDS ARE } {rec-name} ... ]
    [     { RECORD IS   }                ] .

4  –  DB subschema-entry

  The Subschema entry allows a program to access a subschema in the Common
  Data Dictionary/Repository under the schema name.

  Format -

   DB subschema-name WITHIN schema-name

      [ FOR database-name ] [ { THRU    } stream-name ]
                            [ { THROUGH }             ] .

4.1  –  subschema-name

  references a subschema name in the Common Data Dictionary/Repository
  (CDD/Repository) under the schema name.

4.2  –  schema-name

  references a schema name in the Common Data Dictionary/Repository.

4.3  –  database-name

  represents a complete or partial file specification defining the
  database occurrence.  A database occurrence is a root file.  At run
  time, database-name points the Database Control System (DBCS) to the
  root file.

4.4  –  stream-name

  represents the name of a stream. Signals the Data Base Control System
  (DBCS) that your run unit uses a stream, which allows access to
  multiple databases or subschemas.

5  –  RD report-description-entry

  The Report Description names a report, specifies any identifying
  characters to be prefixed to each print line in the report, and describes
  the physical structure and organization of that report.  It also
  determines whether a report-name is a local name or global name.

  Format -

   RD report-name

      [IS GLOBAL]

      [CODE report-code]

      [{ CONTROL IS   } { {control-name} ...       }]
      [{ CONTROLS ARE } { FINAL [control-name] ... }]

      [ PAGE [ LIMIT IS   ] page-size [ LINE  ]
             [ LIMITS ARE ]           [ LINES ]

          [ HEADING heading-line ]

          [ FIRST DETAIL first-detail-line ]

          [ LAST DETAIL last-detail-line ]

          [ FOOTING footing-line ] ] .

6  –  LD keeplist-entry

  The Keeplist Description entry names a keeplist.

  Format -

   LD keeplist-name [LIMIT IS integer] .

6.1  –  keeplist-name

  is a user-defined name.

6.2  –  integer

  is a positive integer.

7  –  dd_record-description-entry

  A data description entry specifies the characteristics of a data item.

7.1  –  1format

  A data description entry specifies the characteristics of a data item.

  Format 1 -

  level-number  [ data-name ]
                [ FILLER    ]

    [REDEFINES other-data-item]

    [IS EXTERNAL]

    [IS GLOBAL]

    [ { PICTURE } IS character-string ]
    [ { PIC     }                     ]

    [             { BINARY          } ]
    [             { COMPUTATIONAL   } ]
    [             { COMP            } ]
    [             { COMPUTATIONAL-1 } ]
    [             { COMP-1          } ]
    [             { COMPUTATIONAL-2 } ]
    [ [USAGE IS ] { COMP-2          } ]
    [             { COMPUTATIONAL-3 } ]
    [             { COMP-3          } ]
    [             { COMPUTATIONAL-5 } ]
    [             { COMP-5          } ]
    [             { COMPUTATIONAL-X } ]
    [             { COMP-X          } ]
    [             { DISPLAY         } ]
    [             { INDEX           } ]
    [             { PACKED-DECIMAL  } ]
    [             { POINTER         } ]
    [             { POINTER-64      } ]

    [ [SIGN IS ] { LEADING  } [ SEPARATE CHARACTER ] ]
    [            { TRAILING }                        ]

    [ OCCURS  table-size TIMES                                        ]
    [   [ { ASCENDING  } KEY IS {key-name} ... ] ...                  ]
    [   [ { DESCENDING }                       ]                      ]
    [                                                                 ]
    [     [INDEXED BY {ind-name} ... ]                                ]
    [                                                                 ]
    [ OCCURS min-times TO max-times TIMES DEPENDING ON depending-item ]
    [   [ { ASCENDING  } KEY IS {key-name} ... ] ...                  ]
    [   [ { DESCENDING }                       ]                      ]
    [                                                                 ]
    [     [INDEXED BY {ind-name} ... ]                                ]

    [ { SYNCHRONIZED } [ LEFT  ] ]
    [ { SYNC         } [ RIGHT ] ]

    [ { JUSTIFIED } RIGHT ]
    [ { JUST      }       ]

    [BLANK WHEN ZERO]

    [         { lit                    }]
    [VALUE IS { EXTERNAL external-name }] .
    [         { REFERENCE data-name    }]

7.2  –  2format_66

  A data description entry specifies the characteristics of a data item.

  Format 2 -

   66 new-name RENAMES rename-start [ { THRU    } rename-end ] .
                                    [ { THROUGH }            ]

7.3  –  3format_88

  A data description entry specifies the characteristics of a data item.

  Format 3 -

   88 condition-name { VALUE IS   } { { EXTERNAL external-name }
                     { VALUES ARE } { { REFERENCE data-name    }
                                    { { low-val                }

                       [ { THRU    } { EXTERNAL external-name } ] }
                       [ { THROUGH } { REFERENCE data-name    } ] } ... .
                       [             { high-val               } ] }

8  –  clauses

8.1  –  ACCESS_MODE

  The ACCESS MODE clause specifies the order of access for a file's
  records.

8.1.1  –  1format_sequential

  The ACCESS MODE clause specifies the order of access for a file's
  records.

  Format 1 - Sequential File

   [ ACCESS MODE IS ] SEQUENTIAL

8.1.2  –  2format_relative

  The ACCESS MODE clause specifies the order of access for a file's
  records.

  Format 2 - Relative File

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

8.1.2.1  –  rel-key

  is the file's RELATIVE KEY data item.

8.1.3  –  3format_indexed

  The ACCESS MODE clause specifies the order of access for a file's
  records.

  Format 3 - Indexed File

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

8.2  –  ALTERNATE_RECORD_KEY

  THE ALTERNATE RECORD KEY clause specifies an alternate access path to
  indexed file records.

  Format -

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

8.2.1  –  alt-key

  is the Alternate Record Key for the file. It is the data-name of a
  data item in a record description entry for the file. It can be
  qualified, but it cannot be a group item that contains a
  variable-occurrence data item.  The data item must be described as:
  (1) alphanumeric or alphabetic category, (2) a group item,
  (3) unsigned numeric display, (4) a COMP-3 integer, or (5) a COMP
  integer.

8.2.2  –  seg-key

  is the Alternate Record Key for the file. It is a segmented-key name
  that represents the concatenation of one or more (up to eight)
  occurrences of seg.

8.2.3  –  seg

  is the data-name of a data item in a record description entry for
  the file. It can be qualified, but it cannot be a group item that
  contains a variable-occurrence data item. The data item must be
  described as: (1) alphanumeric or alphabetic category,
  (2) a group item or (3) an unsigned numeric display item.

8.3  –  AUTO

  In the context of ACCEPT, the AUTO clause moves the cursor to the next
  field when the last character of an input or update field that was
  defined with the AUTO clause is entered.

  Format -

   AUTO

8.4  –  BACKGROUND-COLOR

  The BACKGROUND-COLOR clause specifies the background color for the
  screen item.

  Format -

   BACKGROUND-COLOR color-num

8.4.1  –  color-num

  is an integer in the range 0-7 specifying a color as follows:
     --------------------------------------------------------------
     COLOR           COLOR VALUE        COLOR           COLOR VALUE
     --------------------------------------------------------------
     Black                0             Red                  4
     Blue                 1             Magenta              5
     Green                2             Yellow/Brown         6
     Cyan                 3             White                7
     --------------------------------------------------------------

8.5  –  BELL

  The BELL clause sounds the workstation or terminal audio tone.

  Format -

   BELL

8.6  –  BLANK

  The BLANK clause clears a screen line or clears the entire screen
  before displaying the screen item.

  Format -

   BLANK { LINE   }
         { SCREEN }

8.7  –  BLANK_WHEN_ZERO

  THE BLANK WHEN ZERO clause replaces zeroes with spaces when a data
  item's value is zero.  In the context of the Screen Section, it
  displays spaces when the value of a screen item to be displayed on
  the screen is zero.

  Format -

   BLANK WHEN ZERO

8.8  –  BLINK

  The BLINK clause displays characters on the screen with the "blink on"
  characher attribute.

  Format -

   BLINK

8.9  –  CODE

  The CODE clause specifies a two-character literal that identifies each
  print line as belonging to a specific report.

  Format -

   CODE report-code

8.9.1  –  report-code

   must be a two-character nonnumeric literal.

8.10  –  COLUMN_NUMBER

  In a report group description, the COLUMN NUMBER clause identifies a
  printable item and specifies the position of the item on a print line.
  In a screen description, the COLUMN NUMBER clause specifies the
  horizontal screen coordinate for a screen item.

8.10.1  –  1format_report_description

  Format 1 - Report Description

   COLUMN NUMBER IS column-num

8.10.1.1  –  column-num

   is a positive integer greater than zero.

8.10.2  –  2format_screen_description

  Format 2 - Screen Description

   COLUMN NUMBER IS [PLUS] { identifier-1 }
                           { integer-1    }

8.10.2.1  –  identifier-1

  is an elementary unsigned numeric integer data item.  It cannot be
  subscripted.

8.10.2.2  –  integer-1

  is an unsigned integer value.

8.11  –  CONTROL

  The CONTROL clause establishes the levels of the control hierarchy for
  the report.

  Format -

   { CONTROL IS   } { {control-name} ...       }
   { CONTROLS ARE } { FINAL [control-name] ... }

8.11.1  –  control-name

  is any data-name in the File, Working-Storage, or Linkage
  Section.

8.12  –  Data-Name

  Data-name specifies a data item that your program can explicitly
  reference.  FILLER specifies an item that cannot be explicitly
  referenced.

  Format -

   [ data-name ]
   [ FILLER    ]

8.13  –  DATA_RECORDS

  The DATA RECORDS clause documents the names of a file's record
  description entries.

  Format -

   DATA  { RECORD IS   } {rec-name} ...
         { RECORDS ARE }

8.13.1  –  rec-name

  is the name of a data record.  It must be defined by a level 01 data
  description entry subordinate to the file description entry.

8.14  –  ERASE

  The ERASE clause clears from the starting cursor position to the end
  of either the line or the screen.

  Format -

   ERASE { EOL }
         { EOS }

8.15  –  EXTERNAL

  The EXTERNAL clause specifies that a data item or a file connector in
  a defining program is common to other programs in the run unit if the
  program defines it identically.  The group and elementary data items
  of an external data record and files associated with an external file
  connector are available to very program in the image that describes
  them.

  Format -

   IS EXTERNAL

8.16  –  FILE_STATUS

  The FILE STATUS clause names a data item that contains the status of
  an input/output operation.

  Format -

   FILE STATUS IS file-stat

8.16.1  –  file-stat

  is the data-name of a two-character alphanumeric Working-Storage
  Section or Linkage Section data item.  File-stat is the file's
  FILE STATUS data item.

8.17  –  FOREGROUND-COLOR

  The FOREGROUND-COLOR clause specifies the foreground color for the
  screen item.

  Format -

   FOREGROUND-COLOR color-num

8.17.1  –  color-num

  is an integer in the range 0-7 specifying a color as follows:
     --------------------------------------------------------------
     COLOR           COLOR VALUE        COLOR           COLOR VALUE
     --------------------------------------------------------------
     Black                0             Red                  4
     Blue                 1             Magenta              5
     Green                2             Yellow/Brown         6
     Cyan                 3             White                7
     --------------------------------------------------------------

8.18  –  FULL

  The FULL clause specifies that a screen item must be left either
  completely empty or it must be entirely filled with data.

  Format -

   FULL

8.19  –  GLOBAL

  The GLOBAL clause specifies that data-name or file-name is available
  to every program contained within the program that declares it.

  Format -

   IS GLOBAL

8.20  –  GROUP_INDICATE

  The GROUP INDICATE clause specifies that the associated printable item
  is presented only on the first occurrence of its DETAIL report group
  after a control break or page advance.

  Format -

   GROUP INDICATE

8.21  –  HIGHLIGHT

  The HIGHLIGHT clause specifies that the field is to appear on the
  screen with the highest intensity.

  Format -

   HIGHLIGHT

8.22  –  JUSTIFIED

  The JUSTIFIED clause specifies nonstandard data positioning in a
  screen item or another receiving item.

  Format -

   { JUSTIFIED } RIGHT
   { JUST      }

8.23  –  LABEL_RECORDS

  The LABEL RECORDS clause specifies the presence or absence of labels.

  Format -

   LABEL { RECORDS ARE } { STANDARD }
         { RECORD IS   } { OMITTED  }

8.24  –  Level-Number

  The level-number shows the position of a data item or screen item
  within the hierarchial structure of a logical record or a report
  group or a screen description.  It also identifies entries for
  condition-names and the RENAMES clause.

  Format -

   level-number

8.25  –  LINAGE

  The LINAGE clause specifies the number of lines on a logical page.  It
  can also specify the size of the logical page's top and bottom margins
  and the line where the footing area begins in the page body.

  Format -

   LINAGE IS {page-lines} LINES [ WITH FOOTING AT footing-line ]
      [ LINES AT TOP top-lines ] [ LINES AT BOTTOM bottom-lines ]

8.25.1  –  page-lines

  is a positive integer or the data-name of an elementary unsigned
  integer numeric data item.  Its value must be greater than zero.  It
  specifies the number of lines that can be written or spaced on the
  logical page.  If page-lines is a data-name, it can be qualified.

8.25.2  –  footing-line

  is a positive integer or the data-name of an elementary unsigned
  integer numeric data item.  Its value must be greater than zero, but
  cannot be greater than page-lines.  Footing-lines specifies the line
  number where the footing area begins in the page body.  If
  footing-line is a data-name, it can be qualified.

8.25.3  –  top-lines

  is an integer or the data-name of an elementary unsigned integer
  numeric data item.  Its value can be zero.  Top-lines specifies the
  number of lines in the top margin of the logical page.  If top-lines
  is a data-name, it can be qualified.

8.25.4  –  bottom-lines

  is an integer or the data-name of an elementary unsigned integer
  numeric data item.  Its value can be zero.  Bottom-lines specifies
  the number of lines in the bottom margin of the logical page.  If
  bottom-lines is a data-name, it can be qualified.

8.26  –  LINE_NUMBER

  The LINE NUMBER clause specifies vertical positioning information for
  a report group, or specifies the vertical screen coordinate for a
  screen item.

8.26.1  –  1format_report_description

  Format -

   LINE NUMBER IS { line-num [ON NEXT PAGE] }
                  { PLUS line-num-plus      }

8.26.1.1  –  line-num

  is a nonnegative integer.  Line-num represents an absolute line
  number on a logical page and establishes a print line for a Report
  Writer report group.

8.26.1.2  –  line-num-plus

  is a positive integer.  Line-num-plus represents a relative line
  number on a logical page and establishes a print line for a Report
  Writer report group.

8.26.2  –  2format_screen_description

  Format 2 - Screen Description

   LINE NUMBER IS [PLUS] { identifier-1 }
                         { integer-1    }

8.26.2.1  –  identifier-1

  is an elementary unsigned numeric integer data item.  It cannot be
  subscripted.

8.26.2.2  –  integer-1

  is an unsigned integer value.

8.27  –  LOWLIGHT

  The LOWLIGHT clause specifies that the field is to appear on the
  screen with the lowest intensity.  When only two levels of intensity
  are available, normal intensity and LOWLIGHT will be the same.

  Format -

   LOWLIGHT

8.28  –  NEXT_GROUP

  The NEXT GROUP clause specifies information for the vertical
  positioning of the next report group on a logical page following the
  presentation of the last line of a report group.

  Format -

                 { next-group-line-num           }
   NEXT GROUP IS { PLUS next-group-line-num-plus }
                 { NEXT PAGE                     }

8.28.1  –  next-group-line-num

  is a positive, one- to three-digit integer value greater than zero.
  It represents an absolute line number on a logical page and
  establishes a print line for the next Report Writer report group.

8.28.2  –  next-group-line-num-plus

  is a positive, one- to three-digit integer value.  It represents a
  relative line number on a logical page and establishes a print line
  for the next Report Writer report group.

8.29  –  OCCURS

  The OCCURS clause defines tables and provides the basis for
  subscripting and indexing.  It eliminates the need for separate
  entries for repeated data items.

8.29.1  –  1format_table-size

  The OCCURS clause defines tables and provides the basis for
  subscripting and indexing.  It eliminates the need for separate
  entries for repeated data items.

  Format 1 -

   OCCURS table-size TIMES

      [ { ASCENDING  } KEY IS {key-name} ... ] ...
      [ { DESCENDING }                       ]

      [ INDEXED BY {ind-name} ... ]

8.29.1.1  –  table-size

  is an integer that specifies the exact number of occurrences of a
  table element.

8.29.1.2  –  key-name

  is the data-name of an entry that contains the OCCURS clause or an
  entry subordinate to it.  Key-name can be qualified.  Each key-name
  after the first must name an entry subordinate to the entry that
  contains the OCCURS clause.  The values in each key-name are the
  basis of the ascending or descending arrangement of the table's
  repeated data.

8.29.1.3  –  ind-name

  is an index-name. It associates an index with the table and allows
  indexing in table element references.

8.29.2  –  2format DEPENDING

  The OCCURS clause defines tables and provides the basis for
  subscripting and indexing.  It eliminates the need for separate
  entries for repeated data items.

  Format 2 -

   OCCURS min-times TO max-times TIMES DEPENDING ON depending-item

      [ { ASCENDING  } KEY IS {key-name} ... ] ...
      [ { DESCENDING }                       ]

      [ INDEXED BY {ind-name} ... ]

8.29.2.1  –  min-times

  is an integer that specifies the minimum number of occurrences of a
  table element.  Its value must be greater than or equal to zero.

8.29.2.2  –  max-times

  is an integer that specifies the maximum number of occurrences of a
  table element.  Its value must be greater than min-times.

8.29.2.3  –  key-name

  is the data-name of an entry that contains the OCCURS clause or an
  entry subordinate to it.  Key-name can be qualified.  Each key-name
  after the first must name an entry subordinate to the entry that
  contains the OCCURS clause.  The values in each key-name are the
  basis of the ascending or descending arrangement of the table's
  repeated data.

8.29.2.4  –  ind-name

  is an index-name.  It associates an index with the table and allows
  indexing in table element references.

8.29.2.5  –  depending-item

  is the data-name of an elementary unsigned integer data item.  Its
  value specifies the current number of occurrences.  Depending-item
  can be qualified.

8.30  –  PAGE

  The PAGE clause defines the length of a logical page and the vertical
  subdivisions within which report groups are presented.

  Format -

   PAGE [ LIMIT IS   ] page-size [ LINE  ]
        [ LIMITS ARE ]           [ LINES ]

      [ HEADING heading-line ]

      [ FIRST DETAIL first-detail-line ]

      [ LAST DETAIL last-detail-line ]

      [ FOOTING footing-line ]

8.30.1  –  page-size

  is a one- to three-digit integer.  It defines the number of lines
  available on a logical page.

8.30.2  –  heading-line

  is a one- to three-digit integer.  It defines the first line number
  for a REPORT HEADING or PAGE HEADING report group on the logical
  page.

8.30.3  –  first-detail-line

  is a one- to three-digit integer.  It defines the first line number
  for a CONTROL HEADING, DETAIL, and CONTROL FOOTING report group on
  the logical page.

8.30.4  –  last-detail-line

  is a one- to three-digit integer.  It defines the last line number
  for a CONTROL HEADING or DETAIL report group on the logical page.

8.30.5  –  footing-line

  is a one- to three-digit integer.  It defines the last line number
  for a CONTROL FOOTING report group and the first line number for the
  PAGE FOOTING report group on the logical page.

8.31  –  PICTURE

  The PICTURE clause specifies the general characteristics and editing
  requirements of an elementary item, including an elementary screen
  item.

8.31.1  –  1format_general

  Format 1 -

    { PICTURE } IS character-string
    { PIC     }

8.31.1.1  –  PICTURE symbols

  The following symbols may be used in a PICTURE clause:

    A  B  P  S  V  X  Z  9  0  /  ,  .  +  -  CR  DB  *  cs

8.31.2  –  2format_screen_section

  Format 2 - Screen Section

                                   { USING identifier-3          }
   { PICTURE } IS character-string { {| FROM { identifier-4 } |} }
   { PIC     }                     { {|      { literal-1    } |} }
                                   { {| TO identiier-5        |} }

8.31.2.1  –  PICTURE symbols

  The following symbols may be used in a PICTURE clause:

    A  B  P  S  V  X  Z  9  0  /  ,  .  +  -  CR  DB  *  cs

8.32  –  RECORD

  The RECORD clause specifies: (1) the number of character positions in
  a fixed length record, (2) variable length record format, or (3) the
  minimum and maximum number of character positions in a variable
  length record.

8.32.1  –  1format CONTAINS

  The RECORD clause specifies: (1) the number of character positions in
  a fixed length record, (2) variable length record format, or (3) the
  minimum and maximum number of character positions in a variable
  length record.

  Format 1 -

   RECORD CONTAINS [shortest-rec TO] longest-rec CHARACTERS

8.32.1.1  –  shortest-rec

  is an integer that specifies the minimum number of character
  positions in a variable-length record.

8.32.1.2  –  longest-rec

  is an integer greater than shortest-rec.  It specifies the maximum
  number of character positions in a variable-length record or the
  size of a fixed-length record.

8.32.2  –  2format VARYING

  The RECORD clause specifies: (1) the number of character positions in
  a fixed length record, (2) variable length record format, or (3) the
  minimum and maximum number of character positions in a variable
  length record.

  Format 2 -

   RECORD IS VARYING IN SIZE [FROM shortest-rec] [TO longest-rec]
                             CHARACTERS [DEPENDING ON depending-item]

8.32.2.1  –  shortest-rec

  is an integer that specifies the minimum number of character
  positions in a variable-length record.

8.32.2.2  –  longest-rec

  is an integer greater than shortest-rec.  It specifies the maximum
  number of character positions in a variable-length record or the
  size of a fixed-length record.

8.32.2.3  –  depending-item

  is the identifier of an elementary unsigned integer data item in
  the Working-Storage or Linkage Section.  It specifies the number
  of character positions for an output operation, and it contains
  the number of character positions after a successful input
  operation.

8.33  –  RECORD_KEY

  The RECORD KEY clause specifies the Prime Record Key access path to
  indexed file records.

  Format -

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

8.33.1  –  rec-key

  is the Record Key for the file. It is the data-name of a data item
  in a record description entry for the file. It can be qualified, but
  it cannot be a group item that contains a variable-occurrence data
  item. The data item must be described as: (1) alphanumeric or
  alphabetic category, (2) a group item, (3) unsigned numeric display,
  (4) a COMP-3 integer, or (5) a COMP integer.

8.33.2  –  seg-key

  is the Record Key for the file. It is a segmented-key name that
  represents the concatenation of one or more (up to eight)
  occurrences of seg.

8.33.3  –  seg

  is the data-name of a data item in a record description entry for
  the file. It can be qualified, but it cannot be a group item that
  contains a variable-occurrence data item. The data item must be
  described as: (1) alphanumeric or alphabetic category,
  (2) a group item or (3) an unsigned numeric display item.

8.34  –  REDEFINES

  The REDEFINES clause allows different data description entries to
  describe the same storage area.

  Format -

   level-number [ identifier ] REDEFINES other-data-item
                [ FILLER    ]

8.34.1  –  other-data-item

  is an identifier.  It identifies the data description entry that
  first defines the storage area.

8.35  –  RENAMES

  The RENAMES clause groups elementary items in alternative or
  overlapping ways.

  Format -

    66  new-name RENAMES rename-start [ { THRU    } rename-end ]
                                      [ { THROUGH }            ]

8.35.1  –  new-name

  is the identifier of the item being described.  It identifies an
  alternate grouping of one or more items in a record.

8.35.2  –  rename-start

  is the identifier of the leftmost data item in the area.  It can be
  qualified.

8.35.3  –  rename-end

  is the identifier of the rightmost data item in the area.  It can be
  qualified.

8.36  –  REPORT

  The REPORT clause in a File Description entry (FD) specifies the Report
  Description (RD) report names that comprise a report file.

  Format -

   { REPORT IS   } { report-name } ...
   { REPORTS ARE }

8.37  –  REQUIRED

  The REQUIRED clause specifies that in the context of an ACCEPT
  statement, the user must enter at least one character in the input or
  update field.

  Format -

   REQUIRED

8.38  –  REVERSE-VIDEO

  The REVERSE-VIDEO clause specifies that the field is displayed with
  the default or specified foreground and background colors exchanged.

  Format -

   REVERSE-VIDEO

8.39  –  SECURE

  The SECURE clause suppresses the display of input character on the
  screen.

  Format -

   SECURE

8.40  –  SIGN

  The SIGN clause specifies the operational sign's position and type of
  representation.

8.40.1  –  1format Data Screen

  The SIGN clause specifies the operational sign's position and type of
  representation.

  Format 1 - Data Description and Screen Description Entries

   [ SIGN IS ] { LEADING  } [ SEPARATE CHARACTER ]
               { TRAILING }

8.40.2  –  2format Report Group Description

  The SIGN clause specifies the operational sign's position and type of
  representation.

  Format 2 - Report Group Description Entries

   [ SIGN IS ] { LEADING  } SEPARATE CHARACTER
               { TRAILING }

8.41  –  SOURCE

  The SOURCE clause identifies a data item to be sent to an associated
  printable item defined within a Report Group Description entry.

  Format -

   SOURCE IS source-id

8.41.1  –  source-id

  names an elementary item in the Data Division.

8.42  –  SUM

  The SUM clause establishes a Report Writer sum counter and names the
  data items to be summed.

  Format -

   {SUM {sum-name}...
       [UPON {detail-report-group-name} ... ]} ...

       [RESET ON { control-foot-name } ]
       [         { FINAL             } ]

8.42.1  –  sum-name

  names a numeric data item with an optional sign in the File,
  Working-Storage, and Linkage Sections, or another sum counter
  in the Report Section.

8.42.2  –  detail-report-group-name

  names a DETAIL report group.

8.42.3  –  control-foot-name

  must reference a control-name in the report's CONTROL clause.

8.43  –  SYNCHRONIZED

  The SYNCHRONIZED clause specifies elementary item alignment on word
  boundary offsets relative to a record's beginning.  These offsets are
  related to the size and usage of the item being stored.

  Format -

   [ { SYNCHRONIZED } [ LEFT  ] ]
   [ { SYNC         } [ RIGHT ] ]

8.44  –  TYPE

  The TYPE clause identifies the report group type and indicates when the
  Report Writer Control System (RWCS) is to process it.

  Format -

           { REPORT HEADING }                        }
           { RH             }                        }
           { PAGE HEADING }                          }
           { PH           }                          }
           { CONTROL HEADING } { control-head-name } }
           { CH              } { FINAL             } }
   TYPE IS { DETAIL }                                }
           { DE     }                                }
           { CONTROL FOOTING } { control-foot-name } }
           { CF              } { FINAL             } }
           { PAGE FOOTING }                          }
           { PF           }                          }
           { REPORT FOOTING }                        }
           { RF             }                        }

8.44.1  –  control-head-name

  names a control-name in the CONTROL clause.

8.44.2  –  control-foot-name

  names a control-name in the CONTROL clause.

8.45  –  UNDERLINE

  The UNDERLINE clause specifies that each character of the field is
  underlined when it is displayed on the screen.

  Format -

   UNDERLINE

8.46  –  USAGE

  The USAGE clause specifies the internal format of a data item or
  represents the address of data in a COBOL program.

  Format -

                { BINARY          }
                { COMPUTATIONAL   }
                { COMP            }
                { COMPUTATIONAL-1 }
                { COMP-1          }
                { COMPUTATIONAL-2 }
   [ USAGE IS ] { COMP-2          }
                { COMPUTATIONAL-3 }
                { COMP-3          }
                { DISPLAY         }
                { INDEX           }
                { PACKED-DECIMAL  }
                { POINTER         }
                { POINTER-64      }

8.47  –  VALUE_IS

  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, and to external
  constants, and the constant values of literal screen items.

8.47.1  –  1format_lit

  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, and to external
  constants, and the constant values of literal screen items.

  Format 1 -

   VALUE IS lit

8.47.1.1  –  lit

  is a numeric or nonumeric literal.  In a screen description entry,
  it is a nonnumeric literal.

8.47.2  –  2format THROUGH

  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, and to external
  constants.

  Format 2 -

   { VALUE IS   } { { EXTERNAL external-name }
   { VALUES ARE } { { REFERENCE data-name    }
                  { { low-val                }

                       [ { THRU    } { EXTERNAL external-name } ] }
                       [ { THROUGH } { REFERENCE data-name    } ] } ...
                                     { high-val               } ] }

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

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

8.47.2.3  –  data-name

  names a data item in the File or Working-Storage Section.
  Data-name may be qualified.

8.47.2.4  –  external-name

  names a COBOL link-time bound constant.  It must define a word or
  longword integer value.

8.47.3  –  3format REFERENCE

  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, and to external
  constants.

  Format 3 -

   VALUE IS { REFERENCE data-name }
            { numeric-integer-lit }

8.47.3.1  –  data-name

  names a data item in the File or Working-Storage Section.
  Data-name may be qualified.

8.47.3.2  –  numeric-integer-lit

  is a positive numeric integer literal.

8.47.4  –  4format EXTERNAL

  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, and to external
  constants.

  Format 4 -

   VALUE IS EXTERNAL external-name

8.47.4.1  –  external-name

  names a COBOL link-time bound constant.  It must define a word or
  longword integer value.

8.48  –  VALUE_OF_ID

  The VALUE OF ID clause specifies, replaces, or completes a file
  specification.

  Format -

   VALUE OF { ID      } IS { file-name }
            { FILE-ID }    { data-name }

8.48.1  –  file-name

  is a nonnumeric literal.  It contains the full or partial file
  specification.

8.48.2  –  data-name

  is the data-name of an alphanumeric Working-Storage data item.
  It contains the full or partial file specification.

9  –  rg_report-group-description-entry

  The Report Group Description entry specifies the characteristics of a
  report group and of the individual items within a report group.

9.1  –  1format_01

  The Report Group Description entry specifies the characteristics of a
  report group and of the individual items within a report group.

  Format 1 -

   01 [ group-data-name ]

      [ LINE NUMBER IS { line-num [ ON NEXT PAGE ] } ]
      [                { PLUS line-num-plus        } ]

      [               { next-group-line-num           } ]
      [ NEXT GROUP IS { PLUS next-group-line-num-plus } ]
      [               { NEXT PAGE                     } ]

      [         { REPORT HEADING }                        } ]
      [         { RH             }                        } ]
      [         { PAGE HEADING }                          } ]
      [         { PH           }                          } ]
      [         { CONTROL HEADING } { control-head-name } } ]
      [         { CH              } { FINAL             } } ]
      [ TYPE IS { DETAIL }                                } ]
      [         { DE     }                                } ]
      [         { CONTROL FOOTING } { control-foot-name } } ]
      [         { CF              } { FINAL             } } ]
      [         { PAGE FOOTING }                          } ]
      [         { PF           }                          } ]
      [         { REPORT FOOTING }                        } ]
      [         { RF             }                        } ]

      [ [ USAGE IS ] DISPLAY ] .

9.2  –  2format

  The Report Group Description entry specifies the characteristics of a
  report group and of the individual items within a report group.

  Format 2 -

   level-number [ group-data-name ]

      [ LINE NUMBER IS { line-num [ ON NEXT PAGE ] } ]
      [                { PLUS line-num-plus        } ]

      [ [ USAGE IS ] DISPLAY ] .

9.3  –  3format PIC

  The Report Group Description entry specifies the characteristics of a
  report group and of the individual items within a report group.

  Format 3 -

   level-number [ group-data-name ]

      [ BLANK WHEN ZERO ]

      [ COLUMN NUMBER IS column-num ]

      [ GROUP INDICATE ]

      [ { JUSTIFIED } RIGHT ]
      [ { JUST      }       ]

      [ LINE NUMBER IS { line-num [ ON NEXT PAGE ] } ]
      [                { PLUS line-num-plus        } ]

       { PICTURE } IS character-string
       { PIC     }

      [ [ SIGN IS ] { LEADING  } SEPARATE CHARACTER ]
      [             { TRAILING }                    ]

      { SOURCE IS source-name                                           }
      { VALUE IS lit                                                    }
      { {SUM {sum-name} ... [UPON {detail-report-group-name} ... ]} ... }
      {     [ RESET ON { control-foot-name } ]                          }
      {     [          { FINAL             } ]                          }

      [ [ USAGE IS ] DISPLAY ] .

10  –  ss_screen-description-entry

  A screen description entry describes a video form or a portion of a
  video form and specifies the attributes, behavior, size, and location
  of screen items within the video form.  The screen description entry
  is referenced in the Procedure Division by the ACCEPT and DISPLAY
  statements

10.1  –  1format_group_screen

  Format 1 - Group Screen Item

     level-number [ screen-name ]
                  [ FILLER      ]

          [ BLANK_SCREEN ]

          [ FOREGROUND-COLOR IS color-num-1 ]

          [ BACKGROUND-COLOR IS color-num-2 ]

          [ AUTO ]

          [ SECURE ]

          [ REQUIRED ]

          [ [ USAGE IS ] DISPLAY ]

          [ [ SIGN IS ] { LEADING  } [ SEPARATE CHARACTER ] ]
          [             { TRAILING }                        ]

          [ FULL ] .

10.2  –  2format_literal_elementary

  Format 2 - Elementary Screen Item

     level-number [ screen-name ]
                  [ FILLER      ]

          [ BLANK { LINE   } ]
          [       { SCREEN } ]

          [ BELL ]

          [ BLINK ]

          [ ERASE { EOL } ]
          [       { EOS } ]

          [ HIGHLIGHT ]
          [ LOWLIGHT  ]

          [ REVERSE-VIDEO ]

          [ UNDERLINE ]

          [ NUMBER IS [ PLUS ] { identifier-1 } ]
          [                    { integer-1    } ]

          [ NUMBER IS [ PLUS ] {identifier-2 } ]
          [                    { integer-2   } ]

          [ FOREGROUND-COLOR IS color-num-1 ]

          [ BACKGROUND-COLOR IS color-num-2 ]

          VALUE IS literal-1 .

10.3  –  3format_elementary

  Format 3 - Elementary Screen Item

     level-number [ screen-name ]
                  [ FILLER      ]

          [ BLANK { LINE   } ]
          [       { SCREEN } ]

          [ BELL ]

          [ BLINK ]

          [ ERASE { EOL  } ]
          [       { EOS  } ]

          [ HIGHLIGHT ]
          [ LOWLIGHT  ]

          [ REVERSE-VIDEO ]

          [ UNDERLINE ]

          [ NUMBER IS [ PLUS ] { identifier-1  } ]
          [                    { integer-1     } ]

          [ NUMBER IS [ PLUS ] { identifier-2  } ]
          [                    { integer-2     } ]

          [ FOREGROUND-COLOR IS color-num-1 ]

          [ BACKGROUND-COLOR IS color-num-2 ]

                                          { USING identifier-3          }
          { PICTURE } IS picture-string-1 { {| FROM { identifier-4 } |} }
          { PIC     }                     { {|      { literal-1    } |} }
                                          { {| TO identiier-5        |} }

          [ [ USAGE IS ] DISPLAY ]

          [ BLANK WHEN ZERO ]

          [ { JUSTIFIED } RIGHT ]
          [ { JUST      }       ]

          [ [ SIGN IS ] { LEADING  } [ SEPARATE CHARACTER ] ]
          [             { TRAILING }                        ]

          [ AUTO ]

          [ SECURE ]

          [ REQUIRED ]

          [ FULL ] .

11  –  miscellaneous_topics

11.1  –  data_division_entries

  A Data Division entry begins with a level indicator or level-number
  and is followed, in order, by:

    1)  A space
    2)  The name of a data item or file connector or a screen item
    3)  A sequence of independent descriptive clauses
    4)  A separator period

  The level indicators are:

    FD  (for file description entries)
    SD  (for sort-merge file description entries)
    RD  (for report file description entries)
    DB  (for sub-schema entries)
    LD  (for keeplist entries)

  Level indicators can begin anywhere to the right of Area A.

  Entries that begin with level-numbers are either called data
  description or screen description entries depending on their context.
  The level-number values for data description entries are 01 through
  49, 66, 77, and 88.  For screen description entries the level-number
  values are from 01 to 49.

11.2  –  record_alignment_boundaries

  The alignment boundaries for a record are shown in the following table.
  The boundary is the leftmost location of the one-, two-, four-, or
  eight-byte area.  All boundaries are relative to the beginning of the
  record.

  +-----------------------------------------------+
  |0 0 0 0 0 0 0 0 0 0 1 1 1 1 1 1 1 1 1 1 2 2 2 2|  SYNCHRONIZED clause
  |0 1 2 3 4 5 6 7 8 9 0 1 2 3 4 5 6 7 8 9 0 1 2 3|    affects these
  |-----------------------------------------------|      Data Types
  |B|B|B|B|B|B|B|B|B|B|B|B|B|B|B|B|B|B|B|B|B|B|B|B|  v--------v--------v
  |---+---+---+---+---+---+---+---+---+---+---+---|
  |2by|2by|2by|2by|2by|2by|2by|2by|2by|2by|2by|2by|COMP PIC 9 to 9(4)
  |-------+-------+-------+-------+-------+-------|
  |4-byte |4-byte |4-byte |4-byte |4-byte |4-byte |COMP PIC 9(5) to 9(9)
  |               |               |               |COMP-1  POINTER  INDEX
  |---------------+---------------+---------------|
  |8-byte         |8-byte         |8-byte         |<-----+
  +-----------------------------------------------+      |
                                                       COMP-2

                                                 COMP PIC 9(10) to 9(18)
Close Help