MainframeMaster

COBOL Tutorial

Data Description Entries in COBOL

Progress0 of 0 lessons

Level Numbers (01-49, 66, 77, 88)

Level numbers define the hierarchy of data items in COBOL. They determine the relationship between data items and indicate which items are subdivided into more detailed components.

Level Numbers Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
DATA DIVISION. WORKING-STORAGE SECTION. 01 EMPLOYEE-RECORD. 05 EMPLOYEE-ID PIC 9(5). 05 EMPLOYEE-NAME. 10 FIRST-NAME PIC X(15). 10 MIDDLE-INITIAL PIC X. 10 LAST-NAME PIC X(20). 05 EMPLOYEE-ADDRESS. 10 STREET PIC X(25). 10 CITY PIC X(15). 10 STATE PIC XX. 10 ZIP-CODE PIC 9(5). 05 SALARY PIC 9(7)V99. 05 EMPLOYMENT-STATUS PIC X. 88 ACTIVE VALUE 'A'. 88 TERMINATED VALUE 'T'. 88 ON-LEAVE VALUE 'L'. 77 RECORD-COUNT PIC 9(5) VALUE ZERO. 66 EMPLOYEE-FULL-NAME RENAMES FIRST-NAME THRU LAST-NAME.

This example shows different level numbers in a COBOL data structure, including standard levels (01, 05, 10) and special levels (77, 66, 88).

COBOL uses different types of level numbers:

  • 01-49 (Standard level numbers) - Create hierarchical data structures
  • 66 (RENAMES clause) - Rename or regrouping of existing elementary items
  • 77 (Independent elementary items) - Standalone fields not part of a hierarchy
  • 88 (Condition names) - Define valid values for a data item for conditional testing

Note: The level number 01 always starts a new record definition. Lower level numbers (02-49) create a hierarchy, with higher numbers indicating subordination to the nearest preceding item with a lower level number.

Group Items and Elementary Items

COBOL data items are classified as either group items or elementary items, each serving different purposes in data organization.

Group and Elementary Items Example

cobol
1
2
3
4
5
6
01 CUSTOMER-RECORD. *> Group item 05 CUSTOMER-ID PIC 9(6). *> Elementary item 05 CUSTOMER-NAME. *> Group item 10 LAST-NAME PIC X(20). *> Elementary item 10 FIRST-NAME PIC X(15). *> Elementary item 05 ACCOUNT-BALANCE PIC S9(7)V99 COMP-3. *> Elementary item

In this example, CUSTOMER-RECORD and CUSTOMER-NAME are group items, while CUSTOMER-ID, LAST-NAME, FIRST-NAME, and ACCOUNT-BALANCE are elementary items.

Group Items:

  • Act as containers for other data items
  • Cannot have a PICTURE clause
  • Can have subordinate items (group or elementary items)
  • Can be moved as a whole unit to another group item of identical structure
  • Used to organize related data and create logical structures

Elementary Items:

  • Represent individual data fields
  • Cannot be subdivided further
  • Must have a PICTURE clause (with some exceptions)
  • Can have USAGE, VALUE, and other clauses
  • Represent the actual data storage at the lowest level

Important: When moving data between group items, no data conversion is performed—the data is moved as a whole block. When moving between elementary items, COBOL performs data type conversion as needed.

FILLER Items

FILLER items are unnamed storage areas within a record structure. They're used to reserve space that isn't directly referenced in the program but is needed to maintain the correct record layout.

FILLER Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
01 TRANSACTION-RECORD. 05 TRANS-ID PIC 9(6). 05 TRANS-DATE. 10 TRANS-YEAR PIC 9(4). 10 TRANS-MONTH PIC 9(2). 10 TRANS-DAY PIC 9(2). 05 TRANS-AMOUNT PIC 9(7)V99. 05 FILLER PIC X(10). *> Unused space 05 TRANS-DESCRIPTION PIC X(50). 01 REPORT-HEADER. 05 FILLER PIC X(20) VALUE 'TRANSACTION REPORT'. 05 FILLER PIC X(15) VALUE SPACES. 05 REPORT-DATE PIC 99/99/9999. 05 FILLER PIC X(10) VALUE SPACES. 05 FILLER PIC X(5) VALUE 'PAGE:'. 05 PAGE-NUMBER PIC Z9.

This example shows FILLER used for both unused space in a record layout and for fixed literal values in a report header.

FILLER items are commonly used for:

  • Reserving unused space in fixed-length records
  • Defining constant output values like headers or labels in report lines
  • Padding between fields for alignment
  • Accommodating reserved areas in record layouts defined by external systems
  • Creating space for future expansion of record structures

Note: The keyword FILLER is optional in most COBOL implementations—you can simply omit the data name to create an unnamed field. However, using the FILLER keyword explicitly makes the code more readable.

REDEFINES Clause

The REDEFINES clause allows you to define the same storage area in multiple ways. This is useful when the same data needs to be processed in different formats without duplicating the storage.

REDEFINES Clause Examples

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
01 TRANSACTION-AREA. 05 NUMERIC-TRANSACTION PIC 9(10). 05 CHARACTER-TRANSACTION REDEFINES NUMERIC-TRANSACTION PIC X(10). 01 DATE-RECORD. 05 DATE-YYYYMMDD PIC 9(8). 05 DATE-PARTS REDEFINES DATE-YYYYMMDD. 10 DATE-YYYY PIC 9(4). 10 DATE-MM PIC 9(2). 10 DATE-DD PIC 9(2). 01 EMPLOYEE-DATA. 05 EMPLOYEE-TYPE PIC X. 05 REGULAR-EMPLOYEE-DATA. 10 SALARY PIC 9(7)V99. 10 TAX-CODE PIC X(2). 10 YEARS-OF-SERVICE PIC 9(2). 05 CONTRACT-EMPLOYEE-DATA REDEFINES REGULAR-EMPLOYEE-DATA. 10 HOURLY-RATE PIC 9(3)V99. 10 CONTRACT-LENGTH PIC 9(3). 10 AGENCY-CODE PIC X(3).

These examples show different uses of REDEFINES: for data type conversion, breaking a single field into parts, and handling different data structures based on a record type.

Rules for using REDEFINES:

  • The redefined item and the redefining item must have the same level number
  • REDEFINES must follow the data-name of the redefining item
  • The redefining item cannot be larger than the item being redefined
  • You cannot use the VALUE clause with an item that has REDEFINES
  • REDEFINES cannot be used with level 01 items in the FILE SECTION
  • Multiple items can redefine the same area

Common uses for REDEFINES:

  • Viewing data in different formats (numeric vs. character)
  • Breaking a field into component parts
  • Creating unions or variant records that can hold different types of data
  • Handling different record layouts based on a record type indicator
  • Working with binary data that needs character-based processing

RENAMES Clause

The RENAMES clause (level 66) provides an alternative way to name elementary items within a record, allowing you to create alternative groupings of data without changing the underlying record structure.

RENAMES Clause Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(6). 05 FIRST-NAME PIC X(15). 05 MIDDLE-INITIAL PIC X. 05 LAST-NAME PIC X(20). 05 STREET-ADDRESS PIC X(30). 05 CITY PIC X(20). 05 STATE PIC XX. 05 ZIP-CODE PIC 9(5). 05 COUNTRY PIC X(15). 05 ACCOUNT-STATUS PIC X. 66 CUSTOMER-NAME RENAMES FIRST-NAME THRU LAST-NAME. 66 CUSTOMER-LOCATION RENAMES CITY THRU COUNTRY. 66 FULL-CUSTOMER-NAME RENAMES FIRST-NAME THRU MIDDLE-INITIAL.

This example shows how RENAMES creates alternative groupings of fields within the CUSTOMER-RECORD structure.

Key features of the RENAMES clause:

  • Only used with level 66 items
  • Can rename one or more contiguous elementary items
  • The THRU keyword specifies a range of items to be renamed
  • Renamed items must be at the same level within the same record
  • Cannot be used to rename other level 66 or 88 items
  • The renamed group can include parts of multiple groups from the original structure

Important: Unlike REDEFINES, RENAMES doesn't create a new data structure or allocate additional storage. It simply provides an alternative name for existing elementary items. The names created by RENAMES can be used anywhere the original field names could be used.

Differences between RENAMES and REDEFINES:

  • RENAMES provides alternative names for existing fields; REDEFINES defines alternative structures for the same storage area
  • RENAMES uses level 66; REDEFINES uses standard level numbers
  • RENAMES can only reference elementary items; REDEFINES can redefine group or elementary items
  • RENAMES can span multiple existing fields; REDEFINES creates a completely new view of the data
  • RENAMES is limited to contiguous items; REDEFINES has no such restriction

Exercises

  1. Create a customer record structure

    Design a COBOL data structure for a customer record with appropriate level numbers, including both group and elementary items. Include fields for personal information, contact details, and account information.

  2. Use FILLER for report formatting

    Create a report line structure that uses FILLER items to format a financial statement line with fixed text, spacing, and numeric values.

  3. Apply REDEFINES for date handling

    Create a data structure for a date field that can be accessed both as a single 8-digit number (YYYYMMDD) and as separate year, month, and day components using REDEFINES.

  4. Use level 88 condition names

    Define a status field with multiple level 88 condition names representing different states, and write a simple procedure to test these conditions.

  5. Create alternative groupings with RENAMES

    For an employee record structure, use the RENAMES clause to create alternative groupings of the elementary items that would be useful for different processing requirements.

FAQ Section

Test Your Knowledge

1. What is the valid range for standard level numbers in COBOL?

  • 01-49
  • 01-99
  • 01-50
  • 10-99

2. What is the purpose of a level 01 item in COBOL?

  • To define a condition name
  • To rename a data field
  • To define a record or a group item
  • To define a special elementary item

3. Which special level number is used to create condition names?

  • 01
  • 66
  • 77
  • 88

4. What is the purpose of the FILLER keyword?

  • To define unused space in a record
  • To fill in default values
  • To mark a field as required
  • To indicate a variable-length field

5. What does the REDEFINES clause allow you to do?

  • Create multiple alternate data definitions for the same memory area
  • Redefine a field from another program
  • Create a new copy of an existing field
  • Change a field's data type at runtime