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.
123456789101112131415DATA 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:
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.
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.
1234567891011121314151617WORKING-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:
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.
1234567891011LOCAL-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:
Important: LOCAL-STORAGE is not supported in all COBOL dialects and older compilers. Check your compiler documentation for support details.
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.
12345678910111213IDENTIFICATION 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:
123456789101112WORKING-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.
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.
123456789101112131415161718192021222324252627282930313233343536373839404142DATA 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:
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:
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.
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.
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.
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.
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.
1. Which DATA DIVISION section is used to describe the structure of records in files?
2. What is the main purpose of the WORKING-STORAGE SECTION?
3. What is the key difference between WORKING-STORAGE and LOCAL-STORAGE sections?
4. Which section would you use to access data passed to a subprogram from the calling program?
5. What does the REPORT SECTION primarily define?
Understanding how COBOL programs are structured and organized
How data items are described and defined in COBOL
Breaking COBOL programs into manageable, reusable parts
Methods for sharing data between COBOL programs
How COBOL programs read and write data files