MainframeMaster

COBOL Tutorial

COBOL DATA DIVISION

Progress0 of 0 lessons

DATA DIVISION Overview

The DATA DIVISION is the third division of a COBOL program and is used to describe all data items that the program will use. It defines the structure, characteristics, and relationships of data including files, working storage, and parameters.

What the DATA DIVISION Defines

The DATA DIVISION describes:

  1. File Records - Structure of data files and their records
  2. Working Storage - Temporary data items used during program execution
  3. Parameters - Data passed between programs or subprograms
  4. Local Variables - Local data items for subprograms
  5. Data Relationships - How data items are organized and related

Each section serves specific purposes in data management.

DATA DIVISION Structure

cobol
1
2
3
4
5
6
7
8
9
10
11
12
DATA DIVISION. FILE SECTION. [File descriptions and record layouts] WORKING-STORAGE SECTION. [Temporary data items and variables] LINKAGE SECTION. [Parameters and shared data] LOCAL-STORAGE SECTION. [Local variables for subprograms]

The DATA DIVISION consists of four main sections, each serving different purposes in data management.

DATA DIVISION Sections

SectionPurposeRequiredUse Case
FILE SECTIONDefine file records and structureOnly if using filesFile processing programs
WORKING-STORAGE SECTIONDefine temporary data itemsOptional but commonCounters, flags, calculations
LINKAGE SECTIONDefine parameters and shared dataOnly for subprogramsProgram communication
LOCAL-STORAGE SECTIONDefine local variablesOptionalSubprogram local data

FILE SECTION

The FILE SECTION defines the structure of files and their records. Each file used by the program must have a File Description (FD) entry followed by record layouts.

Basic FILE SECTION Structure

cobol
1
2
3
4
5
6
7
8
9
DATA DIVISION. FILE SECTION. FD file-name LABEL RECORDS ARE STANDARD RECORD CONTAINS n CHARACTERS. 01 record-name. 05 field-name-1 PIC 9(5). 05 field-name-2 PIC X(30). 05 field-name-3 PIC 9(7)V99.

Each file must have an FD entry that corresponds to a SELECT statement in the ENVIRONMENT DIVISION.

Complete FILE SECTION Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 10 RECORDS RECORD CONTAINS 80 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(35). 05 CUSTOMER-BALANCE PIC 9(7)V99. 05 FILLER PIC X(5). FD TRANSACTION-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 50 CHARACTERS. 01 TRANSACTION-RECORD. 05 TRANS-ID PIC 9(8). 05 TRANS-AMOUNT PIC 9(7)V99. 05 TRANS-DATE PIC 9(8). 05 TRANS-TYPE PIC X. 88 DEBIT VALUE "D". 88 CREDIT VALUE "C". 05 FILLER PIC X(26).

This example shows two files with their record structures, including condition names for transaction types.

FD Clauses

ClausePurposeExample
LABEL RECORDSSpecify file labelingLABEL RECORDS ARE STANDARD
RECORD CONTAINSSpecify record sizeRECORD CONTAINS 80 CHARACTERS
BLOCK CONTAINSSpecify blocking factorBLOCK CONTAINS 10 RECORDS
CODE-SETSpecify character encodingCODE-SET IS ASCII-ALPHABET

WORKING-STORAGE SECTION

The WORKING-STORAGE SECTION defines temporary data items that are used during program execution. These items are initialized when the program starts and retain their values throughout program execution.

Basic WORKING-STORAGE Structure

cobol
1
2
3
4
5
6
WORKING-STORAGE SECTION. 01 counter PIC 9(3) VALUE 0. 01 flag PIC X VALUE "N". 88 end-of-file VALUE "Y". 01 total-amount PIC 9(7)V99 VALUE 0. 01 output-message PIC X(50) VALUE SPACES.

WORKING-STORAGE items can have initial values and condition names.

Complex WORKING-STORAGE Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
WORKING-STORAGE SECTION. 01 PROGRAM-COUNTERS. 05 RECORD-COUNT PIC 9(5) VALUE 0. 05 ERROR-COUNT PIC 9(3) VALUE 0. 05 PROCESS-COUNT PIC 9(5) VALUE 0. 01 PROGRAM-FLAGS. 05 EOF-FLAG PIC X VALUE "N". 88 END-OF-FILE VALUE "Y". 88 NOT-END-OF-FILE VALUE "N". 05 ERROR-FLAG PIC X VALUE "N". 88 ERROR-OCCURRED VALUE "Y". 88 NO-ERROR VALUE "N". 01 CALCULATION-FIELDS. 05 TOTAL-AMOUNT PIC 9(9)V99 VALUE 0. 05 AVERAGE-AMOUNT PIC 9(7)V99 VALUE 0. 05 HIGHEST-AMOUNT PIC 9(7)V99 VALUE 0. 05 LOWEST-AMOUNT PIC 9(7)V99 VALUE 999999.99. 01 OUTPUT-FIELDS. 05 REPORT-HEADER PIC X(80) VALUE "CUSTOMER PROCESSING REPORT". 05 ERROR-MESSAGE PIC X(50) VALUE SPACES. 05 SUCCESS-MESSAGE PIC X(50) VALUE "Processing completed successfully".

This example shows organized WORKING-STORAGE with groups, condition names, and meaningful field names.

LINKAGE SECTION

The LINKAGE SECTION defines data items that are passed between programs or subprograms. It is essential for programs that receive parameters or communicate with other programs.

Basic LINKAGE SECTION Structure

cobol
1
2
3
4
5
6
LINKAGE SECTION. 01 input-parameter PIC 9(5). 01 output-parameter PIC X(30). 01 shared-data. 05 data-field-1 PIC 9(3). 05 data-field-2 PIC X(20).

LINKAGE SECTION items do not have initial values as they receive their values from the calling program.

Subprogram LINKAGE SECTION Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
IDENTIFICATION DIVISION. PROGRAM-ID. CALCULATE-TAX. LINKAGE SECTION. 01 INCOME-PARAMETER. 05 GROSS-INCOME PIC 9(7)V99. 05 DEDUCTIONS PIC 9(7)V99. 05 TAX-RATE PIC 9(3)V99. 01 RESULT-PARAMETER. 05 NET-INCOME PIC 9(7)V99. 05 TAX-AMOUNT PIC 9(7)V99. 05 RETURN-CODE PIC 9(2). PROCEDURE DIVISION USING INCOME-PARAMETER, RESULT-PARAMETER. MAIN-PROCESS. COMPUTE NET-INCOME = GROSS-INCOME - DEDUCTIONS COMPUTE TAX-AMOUNT = NET-INCOME * TAX-RATE / 100 MOVE 0 TO RETURN-CODE EXIT PROGRAM.

This example shows a subprogram that receives income parameters and returns calculated tax results.

LOCAL-STORAGE SECTION

The LOCAL-STORAGE SECTION defines local variables that are specific to a subprogram. These items are reinitialized each time the subprogram is called.

Basic LOCAL-STORAGE Structure

cobol
1
2
3
4
5
LOCAL-STORAGE SECTION. 01 local-counter PIC 9(3) VALUE 0. 01 temp-calculation PIC 9(7)V99 VALUE 0. 01 local-flag PIC X VALUE "N". 88 processing VALUE "Y".

LOCAL-STORAGE items are reinitialized on each subprogram call, unlike WORKING-STORAGE items.

LOCAL-STORAGE vs WORKING-STORAGE

AspectWORKING-STORAGELOCAL-STORAGE
InitializationOnce at program startEach subprogram call
PersistenceRetains valuesReinitialized each call
Use CaseProgram-wide dataSubprogram-specific data
MemoryStatic allocationDynamic allocation

PICTURE Clauses

The PICTURE clause (or PIC) defines the size, type, and format of a data item. It is one of the most important aspects of COBOL data definition.

Basic PICTURE Syntax

cobol
1
2
3
4
5
6
01 field-name PIC 9(5). * Numeric, 5 digits 01 field-name PIC X(30). * Alphanumeric, 30 characters 01 field-name PIC A(20). * Alphabetic, 20 characters 01 field-name PIC 9(7)V99. * Numeric with decimal 01 field-name PIC S9(5). * Signed numeric 01 field-name PIC 9(3)P. * Assumed decimal scaling

PICTURE and PIC are identical - PIC is an abbreviation of PICTURE.

PICTURE Symbols

SymbolPurposeExampleDescription
9Numeric digitPIC 9(5)5-digit number
XAny characterPIC X(30)30-character field
ALetters and spacesPIC A(20)20 alphabetic characters
SSignPIC S9(5)Signed 5-digit number
VImplied decimalPIC 9(5)V995 digits, 2 decimal places
PAssumed decimalPIC 9(3)P3 digits, assumed decimal scaling

Edited PICTURE Examples

cobol
1
2
3
4
5
6
7
01 EDITED-FIELDS. 05 ZERO-SUPPRESSED PIC ZZZ,ZZ9.99. * Suppress leading zeros 05 ASTERISK-FILL PIC ***,***9.99. * Fill with asterisks 05 CURRENCY-FORMAT PIC $ZZZ,ZZ9.99. * Currency format 05 DATE-FORMAT PIC 99/99/9999. * Date format 05 PHONE-FORMAT PIC 999-999-9999. * Phone number format 05 PERCENTAGE PIC 999.99%. * Percentage format

Edited PICTURE clauses format data for display with special characters and formatting.

Condition Names (88-Level Items)

Condition names are defined at the 88-level and represent specific values that another field can have. They make code more readable and maintainable.

Basic Condition Name Syntax

cobol
1
2
3
4
5
6
7
8
9
10
01 status-field PIC X. 88 active VALUE "A". 88 inactive VALUE "I". 88 suspended VALUE "S". 01 account-type PIC 9. 88 savings VALUE 1. 88 checking VALUE 2. 88 loan VALUE 3. 88 credit VALUE 4.

Condition names are used in IF statements and SET statements to make code more readable.

Condition Name Usage Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
WORKING-STORAGE SECTION. 01 CUSTOMER-STATUS PIC X VALUE "A". 88 ACTIVE VALUE "A". 88 INACTIVE VALUE "I". 88 SUSPENDED VALUE "S". 88 CLOSED VALUE "C". 01 ACCOUNT-TYPE PIC 9 VALUE 1. 88 SAVINGS VALUE 1. 88 CHECKING VALUE 2. 88 LOAN VALUE 3. 88 CREDIT VALUE 4. PROCEDURE DIVISION. MAIN-PROCESS. IF ACTIVE DISPLAY "Customer is active" END-IF IF SAVINGS DISPLAY "Account type is savings" END-IF SET INACTIVE TO TRUE SET CHECKING TO TRUE DISPLAY "Status: " CUSTOMER-STATUS DISPLAY "Type: " ACCOUNT-TYPE.

This example shows how condition names are defined and used in conditional statements and SET operations.

Tables and Arrays

Tables in COBOL are defined using the OCCURS clause. They allow you to store multiple values of the same type in a structured way.

Basic Table Definition

cobol
1
2
3
4
5
6
7
8
9
10
11
12
01 customer-table. 05 customer-entry OCCURS 100 TIMES. 10 customer-id PIC 9(5). 10 customer-name PIC X(30). 10 customer-balance PIC 9(7)V99. 01 product-table. 05 product-entry OCCURS 50 TIMES INDEXED BY product-index. 10 product-code PIC X(10). 10 product-name PIC X(40). 10 product-price PIC 9(5)V99.

Tables can be indexed for efficient access, and the OCCURS clause specifies the number of elements.

Variable-Length Tables

cobol
1
2
3
4
5
6
7
01 dynamic-table. 05 table-size PIC 9(3) VALUE 0. 05 table-entry OCCURS 1 TO 100 TIMES DEPENDING ON table-size INDEXED BY table-index. 10 entry-id PIC 9(5). 10 entry-data PIC X(50).

Variable-length tables use OCCURS DEPENDING ON to specify the actual number of elements at runtime.

Nested Tables

cobol
1
2
3
4
5
6
7
8
9
01 department-table. 05 department-entry OCCURS 10 TIMES. 10 dept-id PIC 9(3). 10 dept-name PIC X(20). 10 employee-list. 15 employee OCCURS 20 TIMES. 20 emp-id PIC 9(5). 20 emp-name PIC X(30). 20 emp-salary PIC 9(6)V99.

Tables can be nested to create complex data structures like departments containing employees.

Practical Examples

These examples demonstrate real-world applications of DATA DIVISION concepts for common business scenarios.

Example 1: Complete DATA DIVISION Structure

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-PROCESSING. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS FILE-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 100 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(40). 05 CUSTOMER-BALANCE PIC 9(7)V99. 05 CUSTOMER-STATUS PIC X. 88 ACTIVE VALUE "A". 88 INACTIVE VALUE "I". 88 SUSPENDED VALUE "S". 05 FILLER PIC X(23). WORKING-STORAGE SECTION. 01 PROGRAM-COUNTERS. 05 RECORD-COUNT PIC 9(5) VALUE 0. 05 ACTIVE-COUNT PIC 9(5) VALUE 0. 05 INACTIVE-COUNT PIC 9(5) VALUE 0. 01 PROGRAM-FLAGS. 05 EOF-FLAG PIC X VALUE "N". 88 END-OF-FILE VALUE "Y". 88 NOT-END-OF-FILE VALUE "N". 01 CALCULATION-FIELDS. 05 TOTAL-BALANCE PIC 9(9)V99 VALUE 0. 05 AVERAGE-BALANCE PIC 9(7)V99 VALUE 0. 01 OUTPUT-FIELDS. 05 REPORT-HEADER PIC X(80) VALUE "CUSTOMER PROCESSING REPORT". 05 ERROR-MESSAGE PIC X(50) VALUE SPACES. LINKAGE SECTION. 01 INPUT-PARAMETERS. 05 PROCESS-TYPE PIC X. 88 FULL-PROCESS VALUE "F". 88 SUMMARY-ONLY VALUE "S". 05 OUTPUT-FORMAT PIC X. 88 DETAILED VALUE "D". 88 SUMMARY VALUE "S". 01 OUTPUT-RESULTS. 05 PROCESS-STATUS PIC X. 88 SUCCESS VALUE "S". 88 ERROR VALUE "E". 05 RETURN-CODE PIC 9(2). PROCEDURE DIVISION USING INPUT-PARAMETERS, OUTPUT-RESULTS. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-CUSTOMERS UNTIL END-OF-FILE PERFORM FINALIZATION EXIT PROGRAM.

This example shows a complete DATA DIVISION structure with all sections and various data types.

Example 2: Table Processing

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
WORKING-STORAGE SECTION. 01 PRODUCT-TABLE. 05 PRODUCT-ENTRY OCCURS 10 TIMES INDEXED BY PRODUCT-INDEX. 10 PRODUCT-CODE PIC X(5). 10 PRODUCT-NAME PIC X(30). 10 PRODUCT-PRICE PIC 9(5)V99. 10 PRODUCT-STATUS PIC X. 88 AVAILABLE VALUE "A". 88 OUT-OF-STOCK VALUE "O". 88 DISCONTINUED VALUE "D". 01 TABLE-STATISTICS. 05 TOTAL-PRODUCTS PIC 9(2) VALUE 0. 05 AVAILABLE-COUNT PIC 9(2) VALUE 0. 05 TOTAL-VALUE PIC 9(8)V99 VALUE 0. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZE-TABLE PERFORM PROCESS-TABLE PERFORM DISPLAY-STATISTICS STOP RUN. INITIALIZE-TABLE. MOVE 1 TO PRODUCT-INDEX MOVE "P001" TO PRODUCT-CODE(PRODUCT-INDEX) MOVE "LAPTOP" TO PRODUCT-NAME(PRODUCT-INDEX) MOVE 999.99 TO PRODUCT-PRICE(PRODUCT-INDEX) SET AVAILABLE TO TRUE ADD 1 TO TOTAL-PRODUCTS SET PRODUCT-INDEX UP BY 1 MOVE "P002" TO PRODUCT-CODE(PRODUCT-INDEX) MOVE "MOUSE" TO PRODUCT-NAME(PRODUCT-INDEX) MOVE 25.50 TO PRODUCT-PRICE(PRODUCT-INDEX) SET OUT-OF-STOCK TO TRUE ADD 1 TO TOTAL-PRODUCTS.

This example shows table definition and processing with indexes and condition names.

Best Practices and Tips

Following these best practices ensures efficient and maintainable DATA DIVISION definitions.

DATA DIVISION Best Practices

  • Use meaningful field names that clearly describe the data
  • Organize data into logical groups using 01-level items
  • Use condition names (88-level items) for better code readability
  • Choose appropriate PICTURE clauses for data types and sizes
  • Use FILLER for unused positions in fixed-length records
  • Initialize WORKING-STORAGE items with appropriate default values
  • Use consistent naming conventions throughout the program
  • Document complex data structures with comments
  • Use appropriate USAGE clauses for performance optimization
  • Validate data sizes to ensure they match requirements

PICTURE Clause Best Practices

  • Use 9 for numeric data that will be used in calculations
  • Use X for alphanumeric data that may contain any characters
  • Use A for alphabetic data that contains only letters and spaces
  • Use V for implied decimal points in numeric fields
  • Use S for signed numbers when negative values are possible
  • Use edited PICTURE clauses for display formatting
  • Choose appropriate field sizes to avoid truncation
  • Consider storage efficiency when defining field sizes

Table Best Practices

  • Use INDEXED BY for efficient table access instead of subscripts
  • Initialize table counters before using tables
  • Check table bounds before accessing elements
  • Use meaningful table names that describe the data
  • Consider using OCCURS DEPENDING ON for variable-length tables
  • Document table structures with comments
  • Use nested tables carefully to avoid complexity

Common Pitfalls to Avoid

  • Incorrect PICTURE clauses for data types
  • Field size mismatches between files and programs
  • Not initializing WORKING-STORAGE items that need default values
  • Using wrong section for data items (e.g., WORKING-STORAGE vs LINKAGE)
  • Inconsistent naming conventions throughout the program
  • Not using condition names for better code readability
  • Incorrect table indexing leading to out-of-bounds access
  • Not documenting complex data structures for maintenance
  • Using inappropriate data types for the intended use
  • Not considering performance implications of data definitions

Performance Considerations

  • Use appropriate USAGE clauses (BINARY, PACKED-DECIMAL) for performance
  • Choose efficient field sizes to minimize memory usage
  • Use indexes for table access instead of subscripts for large tables
  • Consider alignment requirements for optimal performance
  • Use LOCAL-STORAGE for subprograms to avoid memory conflicts
  • Minimize REDEFINES usage unless necessary for memory optimization

Test Your Knowledge

1. What is the purpose of the DATA DIVISION in COBOL?

  • To define program logic and procedures
  • To describe all data items used by the program
  • To specify file connections and environment
  • To identify the program name and author

2. Which section of the DATA DIVISION is used to define data items that are shared between programs?

  • FILE SECTION
  • WORKING-STORAGE SECTION
  • LINKAGE SECTION
  • LOCAL-STORAGE SECTION

3. What does the PICTURE clause define?

  • The physical appearance of data
  • The size, type, and format of a data item
  • The location of data in memory
  • The relationship between data items

4. Which PICTURE symbol is used for numeric data?

  • X
  • 9
  • A
  • S

5. What is a condition name in COBOL?

  • A variable that stores conditions
  • An 88-level item that represents a specific value of another field
  • A file status code
  • A program name

Frequently Asked Questions