Function
Every user-defined name explicitly referenced in a COBOL compilation unit must be unique. A name is unique when there is no other name consisting of the same sequence of characters and hyphens, or the name occurs in a hierarchy of names, so that it can be referenced unambiguously. This occurs by specifying one or more names on a higher level of the hierarchy. The higher levels are called qualifiers, and the process that causes the name to be unique is called qualification. A name must be qualified sufficiently to be unique; however, it is not absolutely necessary to specify all levels of the hierarchy. Within the DATA DIVISION, all data names used for qualification purposes must be given a level number or a level identifier. Thus, two identical data names cannot be subordinate elements of a single group item, unless they can be uniquely qualified. In the PROCEDURE DIVISION, two identical paragraph names are only allowed to occur in the same section if they are not referenced. If a paragraph name is referenced, it must be unique, i.e. it must be qualified when it occurs in more than one section.
In conjunction with types, the uniqueness of names is guaranteed if a name occurs only within a type definition and this type definition is not used more than once for defining data. In all other cases qualification is required.
In the qualification hierarchy, the names belonging to a level identifier are the most important, followed by the names belonging to level 01, then those belonging to level 02 to 49. A section name is the only qualifier available for paragraph names. The uppermost name in the hierarchy must be unique, and cannot be qualified. Subscripted or indexed data names and conditional variables, as well as procedure names and data names, can be made unique by means of qualification. The name of a conditional variable can be used as a qualifier for each of its condition names.
Format 1
{data-name-1 | condition-name} {
{{IN | OF} data-name-2}... [{IN | OF} filename]
| {IN | OF} file-name
}
Format 2
paragraph-name {IN | OF} section-name
Format 3
text-name {IN | OF} library-name
Format 4
LINAGE-COUNTER {IN | OF} file-name
Format 5
{PAGE-COUNTER | LINE-COUNTER} {IN | OF} report-name
Format 6
data-name-1
{
{IN | OF} data-name-2 [{IN | OF} report-name
]
| {IN | OF} report-name
}
Syntax rules
Each qualifier must be of a successively higher level and within the same hierarchy as the name it qualifies.
The same name must not appear on more than one level of the hierarchy.
A data name must not be subscripted or indexed when used as a qualifier.
General rules
A data-name or a condition-name, if assigned to more than one data item within the compilation unit, must be qualified whenever it is referenced in the Procedure, Environment or Data Division (except in the REDEFINES clause, where qualification is not needed and may be used).
A paragraph-name is only allowed to occur more than once within a section if it is not referenced. If it is referenced, it is only allowed to occur once within a section, or must be qualified when it occurs in more than one section. When a paragraph-name is qualified by a section-name, the word SECTION must not be used. A paragraph-name, when referenced from within the same section, need not be qualified.
A name may be qualified even when qualification is not required; if uniqueness may be ensured by more than one combination of qualifiers, then each such combination is permitted. The total set of the qualifiers for a given data-name must not be identical to a subset of qualifiers for another data-name.
If more than one COBOL library is available to the compiler at compile time, then every time text-name is referenced it must be qualified by library-name.
If data-name is qualified in a contained or containing program of a nested program, the same data-name must not be used for a unit of data (record or data item) that is declared as external or global in one of the group of nested programs.