MainframeMaster

COBOL Tutorial

DATA DIVISION Sections in COBOL

Progress0 of 0 lessons

FILE SECTION for File Description

The FILE SECTION contains the definition of all files used by the program, including their structure, size, and organization. Each file is defined with a File Description (FD) entry followed by the record structure that will be used to process the file.

FILE SECTION Basic Structure

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
DATA DIVISION. FILE SECTION. FD EMPLOYEE-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 80 CHARACTERS BLOCK CONTAINS 0 RECORDS. 01 EMPLOYEE-RECORD. 05 EMP-ID PIC 9(5). 05 EMP-NAME. 10 EMP-LAST-NAME PIC X(15). 10 EMP-FIRST-NAME PIC X(10). 05 EMP-POSITION PIC X(12). 05 EMP-SALARY PIC 9(7)V99. 05 EMP-DEPARTMENT PIC X(10). 05 FILLER PIC X(19).

The FD entry links the physical file (defined in the ENVIRONMENT DIVISION) to the record structure used in the program.

Key components of the FILE SECTION include:

  • FD (File Description) - Specifies a file's physical attributes
  • Record description - Defines the layout of records in the file
  • LABEL RECORDS - Indicates whether the file has standard or omitted labels
  • RECORD CONTAINS - Specifies the size of the records
  • BLOCK CONTAINS - Defines the physical blocking factor for the file

Note: The FILE SECTION is directly related to the SELECT statements in the ENVIRONMENT DIVISION's FILE-CONTROL paragraph. Each file described in the FILE SECTION must have a corresponding SELECT statement.

WORKING-STORAGE SECTION for Variables

The WORKING-STORAGE SECTION is where you define the program's internal variables, constants, work areas, and data structures. These items persist for the duration of the program and maintain their values between different invocations of the program.

WORKING-STORAGE Basic Examples

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
WORKING-STORAGE SECTION. 01 WS-COUNTERS. 05 WS-RECORD-COUNT PIC 9(5) VALUE ZEROS. 05 WS-ERROR-COUNT PIC 9(3) VALUE ZEROS. 05 WS-VALID-COUNT PIC 9(5) VALUE ZEROS. 01 WS-FLAGS. 05 WS-EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. 05 WS-VALID-RECORD PIC X VALUE 'Y'. 88 VALID-RECORD VALUE 'Y'. 88 INVALID-RECORD VALUE 'N'. 01 WS-CURRENT-DATE. 05 WS-YEAR PIC 9(4). 05 WS-MONTH PIC 9(2). 05 WS-DAY PIC 9(2).

WORKING-STORAGE items can be initialized with the VALUE clause, setting their starting values before the program begins execution.

The WORKING-STORAGE SECTION typically contains:

  • Individual data items - Simple variables used throughout the program
  • Group items - Structured data combining multiple related fields
  • Constants - Fixed values that don't change during program execution
  • Work areas - Temporary storage for data manipulation
  • Flags and switches - Often used with level 88 condition names for control flow
  • Tables (arrays) - Collections of similar items defined with the OCCURS clause

LOCAL-STORAGE SECTION (Modern COBOL)

The LOCAL-STORAGE SECTION was introduced in COBOL-85 and enhanced in later standards. It's similar to WORKING-STORAGE but with a key difference: LOCAL-STORAGE items are allocated when a program is called and deallocated when it returns, while WORKING-STORAGE items persist between calls.

LOCAL-STORAGE Example

cobol
1
2
3
4
5
6
7
8
9
10
11
LOCAL-STORAGE SECTION. 01 LS-COUNTER PIC 9(5) VALUE ZEROS. 01 LS-TEMP-AREA. 05 LS-TEMP-NAME PIC X(30). 05 LS-TEMP-DATE. 10 LS-TEMP-YEAR PIC 9(4). 10 LS-TEMP-MONTH PIC 9(2). 10 LS-TEMP-DAY PIC 9(2). 01 LS-CALCULATION-FIELDS. 05 LS-SUBTOTAL PIC 9(7)V99 VALUE ZEROS. 05 LS-TAX-AMOUNT PIC 9(5)V99 VALUE ZEROS.

Each time the program is called, these variables are initialized with their VALUE clauses. When the program ends, these variables are deallocated.

LOCAL-STORAGE is particularly useful for:

  • Recursive programs - Each recursion gets its own fresh copy of variables
  • Thread-safe programming - Avoids variable sharing between concurrent executions
  • Subprograms needing clean data - Ensures variables are reset to initial values on each call
  • Temporary work areas - Space that's only needed during a single program invocation

Important: LOCAL-STORAGE is not supported in all COBOL dialects and older compilers. Check your compiler documentation for support details.

LINKAGE SECTION for Parameter Passing

The LINKAGE SECTION is used to describe data that is passed to the program from a calling program. It defines the interface between programs, allowing them to share data without using files or other external storage.

LINKAGE SECTION Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
IDENTIFICATION DIVISION. PROGRAM-ID. CALCULATE-TAX. DATA DIVISION. LINKAGE SECTION. 01 LK-SALARY PIC 9(7)V99. 01 LK-TAX-RATE PIC V999. 01 LK-TAX-AMOUNT PIC 9(7)V99. PROCEDURE DIVISION USING LK-SALARY, LK-TAX-RATE, LK-TAX-AMOUNT. COMPUTE LK-TAX-AMOUNT = LK-SALARY * LK-TAX-RATE GOBACK.

This example shows a subprogram that receives a salary and tax rate, calculates the tax, and returns the result through the third parameter.

The LINKAGE SECTION has these key characteristics:

  • No physical storage allocation - Items are just "views" of data passed by the caller
  • No VALUE clause - Items cannot be initialized with the VALUE clause
  • Parameter order matching - Items must be listed in the PROCEDURE DIVISION USING statement in the same order as they appear in the CALL statement of the calling program
  • BY REFERENCE vs BY CONTENT - Parameters can be passed by reference (allowing modification) or by content (read-only)

Call Example from a Main Program

cobol
1
2
3
4
5
6
7
8
9
10
11
12
WORKING-STORAGE SECTION. 01 WS-EMPLOYEE-SALARY PIC 9(7)V99 VALUE 50000.00. 01 WS-TAX-RATE PIC V999 VALUE .250. 01 WS-TAX-AMOUNT PIC 9(7)V99. PROCEDURE DIVISION. CALL 'CALCULATE-TAX' USING WS-EMPLOYEE-SALARY, WS-TAX-RATE, WS-TAX-AMOUNT. DISPLAY 'Salary: ' WS-EMPLOYEE-SALARY. DISPLAY 'Tax Rate: ' WS-TAX-RATE. DISPLAY 'Tax Amount: ' WS-TAX-AMOUNT.

The calling program passes three items to the CALCULATE-TAX program. After the call, WS-TAX-AMOUNT will contain the calculated tax value.

REPORT SECTION for Report Generation

The REPORT SECTION is used for structured report generation. It defines the format and structure of printed reports, separating the report layout definition from the procedural code that processes the data.

REPORT 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
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
DATA DIVISION. FILE SECTION. FD PRINT-FILE REPORT IS EMPLOYEE-REPORT. REPORT SECTION. RD EMPLOYEE-REPORT CONTROLS ARE FINAL, DEPARTMENT-NO PAGE LIMIT IS 60 LINES HEADING 1 FIRST DETAIL 5 LAST DETAIL 54. 01 TYPE PAGE HEADING. 05 LINE 1. 10 COLUMN 1 PIC X(20) VALUE 'EMPLOYEE LISTING'. 10 COLUMN 110 PIC X(4) VALUE 'PAGE'. 10 COLUMN 115 PIC Z9 SOURCE PAGE-COUNTER. 01 TYPE CONTROL HEADING DEPARTMENT-NO. 05 LINE PLUS 2. 10 COLUMN 1 PIC X(10) VALUE 'DEPARTMENT'. 10 COLUMN 12 PIC 9(3) SOURCE DEPARTMENT-NO. 01 TYPE DETAIL. 05 LINE PLUS 1. 10 COLUMN 1 PIC X(20) SOURCE EMPLOYEE-NAME. 10 COLUMN 25 PIC 9(5) SOURCE EMPLOYEE-ID. 10 COLUMN 35 PIC $$$,$$$,$$9.99 SOURCE EMPLOYEE-SALARY. 01 TYPE CONTROL FOOTING DEPARTMENT-NO. 05 LINE PLUS 1. 10 COLUMN 1 PIC X(22) VALUE 'DEPARTMENT TOTAL:'. 10 COLUMN 35 PIC $$$,$$$,$$9.99 SUM EMPLOYEE-SALARY. 01 TYPE CONTROL FOOTING FINAL. 05 LINE PLUS 2. 10 COLUMN 1 PIC X(22) VALUE 'GRAND TOTAL:'. 10 COLUMN 35 PIC $$$,$$$,$$9.99 SUM EMPLOYEE-SALARY.

This example defines a report with page headers, department headers, detail lines, department totals, and a grand total.

The REPORT SECTION contains these key elements:

  • RD (Report Description) - Defines the overall report structure and page limits
  • CONTROLS - Specifies hierarchy levels for grouping and summarizing data
  • Report groups - Define different parts of the report (headings, detail, footings)
  • LINE and COLUMN clauses - Position report elements on the page
  • SOURCE clause - Specifies data sources for report fields
  • SUM clause - Automatically calculates totals

Note: To use the REPORT SECTION, you need to include REPORT IS clause in the FD for the print file, and you use INITIATE, GENERATE, and TERMINATE statements in the PROCEDURE DIVISION to produce the report.

The Report Writer feature automates many aspects of report generation, including:

  • Page breaks and numbering
  • Headers and footers
  • Group breaks based on control fields
  • Automatic summarization and totaling
  • Line spacing and positioning

Exercises

  1. Define a FILE SECTION for a customer file

    Create a complete FILE SECTION for a customer file with fields for customer ID, name (first and last), address (street, city, state, zip), phone number, and account balance.

  2. Create a WORKING-STORAGE SECTION for a payroll program

    Define a WORKING-STORAGE SECTION that includes counters, flags, and work areas needed for calculating employee payroll, including tax calculations.

  3. Write a subprogram using the LINKAGE SECTION

    Create a subprogram that calculates the average of an array of numbers passed from a main program. Define the LINKAGE SECTION and PROCEDURE DIVISION properly.

  4. Compare LOCAL-STORAGE and WORKING-STORAGE

    Write a short program that demonstrates the difference between LOCAL-STORAGE and WORKING-STORAGE when called multiple times. Include comments explaining the behavior.

  5. Design a simple REPORT SECTION

    Create a REPORT SECTION definition for a monthly sales report that includes page headers, detail lines showing sales by product, and totals by department and overall.

FAQ Section

Test Your Knowledge

1. Which DATA DIVISION section is used to describe the structure of records in files?

  • WORKING-STORAGE SECTION
  • FILE SECTION
  • LINKAGE SECTION
  • REPORT SECTION

2. What is the main purpose of the WORKING-STORAGE SECTION?

  • To define record layouts for files
  • To define variables and work areas used by the program
  • To describe the structure of printed reports
  • To define parameters passed between programs

3. What is the key difference between WORKING-STORAGE and LOCAL-STORAGE sections?

  • LOCAL-STORAGE can only contain level 77 items
  • WORKING-STORAGE allows for tables, LOCAL-STORAGE does not
  • LOCAL-STORAGE items are allocated each time a program is called and freed when it returns
  • There is no difference, they are synonyms

4. Which section would you use to access data passed to a subprogram from the calling program?

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

5. What does the REPORT SECTION primarily define?

  • Data storage areas for report processing
  • The layout and content of printed reports
  • Error reporting mechanisms
  • Documentation about the program