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.
The DATA DIVISION describes:
Each section serves specific purposes in data management.
123456789101112DATA 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.
Section | Purpose | Required | Use Case |
---|---|---|---|
FILE SECTION | Define file records and structure | Only if using files | File processing programs |
WORKING-STORAGE SECTION | Define temporary data items | Optional but common | Counters, flags, calculations |
LINKAGE SECTION | Define parameters and shared data | Only for subprograms | Program communication |
LOCAL-STORAGE SECTION | Define local variables | Optional | Subprogram local data |
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.
123456789DATA 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.
123456789101112131415161718192021222324DATA 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.
Clause | Purpose | Example |
---|---|---|
LABEL RECORDS | Specify file labeling | LABEL RECORDS ARE STANDARD |
RECORD CONTAINS | Specify record size | RECORD CONTAINS 80 CHARACTERS |
BLOCK CONTAINS | Specify blocking factor | BLOCK CONTAINS 10 RECORDS |
CODE-SET | Specify character encoding | CODE-SET IS ASCII-ALPHABET |
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.
123456WORKING-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.
123456789101112131415161718192021222324WORKING-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.
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.
123456LINKAGE 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.
1234567891011121314151617181920IDENTIFICATION 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.
The LOCAL-STORAGE SECTION defines local variables that are specific to a subprogram. These items are reinitialized each time the subprogram is called.
12345LOCAL-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.
Aspect | WORKING-STORAGE | LOCAL-STORAGE |
---|---|---|
Initialization | Once at program start | Each subprogram call |
Persistence | Retains values | Reinitialized each call |
Use Case | Program-wide data | Subprogram-specific data |
Memory | Static allocation | Dynamic allocation |
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.
12345601 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.
Symbol | Purpose | Example | Description |
---|---|---|---|
9 | Numeric digit | PIC 9(5) | 5-digit number |
X | Any character | PIC X(30) | 30-character field |
A | Letters and spaces | PIC A(20) | 20 alphabetic characters |
S | Sign | PIC S9(5) | Signed 5-digit number |
V | Implied decimal | PIC 9(5)V99 | 5 digits, 2 decimal places |
P | Assumed decimal | PIC 9(3)P | 3 digits, assumed decimal scaling |
123456701 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 are defined at the 88-level and represent specific values that another field can have. They make code more readable and maintainable.
1234567891001 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.
12345678910111213141516171819202122232425262728WORKING-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 in COBOL are defined using the OCCURS clause. They allow you to store multiple values of the same type in a structured way.
12345678910111201 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.
123456701 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.
12345678901 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.
These examples demonstrate real-world applications of DATA DIVISION concepts for common business scenarios.
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667IDENTIFICATION 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.
1234567891011121314151617181920212223242526272829303132333435363738WORKING-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.
Following these best practices ensures efficient and maintainable DATA DIVISION definitions.
1. What is the purpose of the DATA DIVISION in COBOL?
2. Which section of the DATA DIVISION is used to define data items that are shared between programs?
3. What does the PICTURE clause define?
4. Which PICTURE symbol is used for numeric data?
5. What is a condition name in COBOL?
Understanding different data types and PICTURE clauses in COBOL.
Detailed overview of all sections in the DATA DIVISION.
How to define files and records in the FILE SECTION.
How to work with tables and arrays in COBOL.
Understanding condition names and their usage.