Function
The level number indicates the position of a data item within the hierarchical structure of a logical record. It also identifies entries for data items within the WORKING-STORAGE, LOCAL-STORAGE and LINKAGE SECTION, as well as for condition-names and data-items in the RENAMES clause.
Format
level-number
Syntax rules
The level number is a special numeric literal consisting of one to two digits. A level number which is less than 10 may be written either as a single digit or with a leading zero.
Data description entries subordinate to an FD or SD entry must have level numbers with the values 01 to 49, 66, or 88.
Data description entries subordinate to an RD entry may have the level numbers 01 and 02 only.
The first element in every data description entry must be a level number.
General rules
Level number 01 identifies the first entry of each record description or report group description.
Special level numbers are assigned to certain kinds of entries for which there is no real concept of hierarchy. These numbers include:
Level number 66 is used to identify renaming entries. It may be used only as described in the RENAMES clause.
Level number 77 is used to identify structurally noncontiguous data items in the WORKING-STORAGE, LOCAL-STORAGE and LINKAGE SECTION. It may be used only as described under "77-level description entry".
Level number 88 refers to entries which define condition-names associated with a conditional variable. It may be used only as described in format 2 of the VALUE clause.
Multiple level-01 entries which are subordinate to a given level indicator (except RD) represent implicit redefinitions of the same area.
Example 7-2
01 ADDRESS. 02 NAME. 03 FIRST-NAME PIC X(18). 03 LAST-NAME PIC X(20). 02 STREET ADDRESS. 03 ZIP-CODE. 04 DIGIT-1 PIC 9. 04 DIGIT-2 PIC 9. 04 DIGIT-3 PIC 9. 04 DIGIT-4 PIC 9. 04 DIGIT-5 PIC 9. 03 CITY PIC X(19). 03 STREET PIC X(16). 03 HOUSE-NUMBER PIC XXX.
The statement
MOVE ADDRESS TO...
will move the entire group.
The statement
MOVE NAME TO...
will move the first and last names etc.