The FILE SECTION is a crucial part of the DATA DIVISION in COBOL programs that process files. Within the FILE SECTION, each file used by the program must have a File Description (FD) entry that defines the physical characteristics of the file and serves as a link between the physical file structure and the logical record layout.
The FILE SECTION begins with the header "FILE SECTION." followed by FD entries for each file. Each FD entry corresponds to a file that was defined with a SELECT statement in the ENVIRONMENT DIVISION.
12345678910111213141516171819202122DATA DIVISION. FILE SECTION. FD EMPLOYEE-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 10 RECORDS RECORD CONTAINS 80 CHARACTERS. 01 EMPLOYEE-RECORD. 05 EMPLOYEE-ID PIC 9(5). 05 EMPLOYEE-NAME PIC X(30). 05 EMPLOYEE-ADDRESS PIC X(35). 05 EMPLOYEE-SALARY PIC 9(7)V99. FD PAYROLL-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 50 CHARACTERS. 01 PAYROLL-RECORD. 05 PR-EMPLOYEE-ID PIC 9(5). 05 PR-PAY-DATE PIC 9(8). 05 PR-GROSS-PAY PIC 9(7)V99. 05 PR-DEDUCTIONS PIC 9(7)V99. 05 PR-NET-PAY PIC 9(7)V99. 05 FILLER PIC X(6).
This example shows a FILE SECTION with two FD entries, one for an employee file and one for a payroll file. Each FD is followed by a record description (01-level item) that defines the logical record structure.
Each FD entry must correspond to a file that was previously defined with a SELECT statement in the ENVIRONMENT DIVISION. The file name used in the FD entry must match the file name used in the SELECT statement.
1234567891011121314151617181920ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT EMPLOYEE-FILE ASSIGN TO EMPFILE ORGANIZATION IS INDEXED ACCESS MODE IS DYNAMIC RECORD KEY IS EMPLOYEE-ID FILE STATUS IS EMPLOYEE-FILE-STATUS. DATA DIVISION. FILE SECTION. FD EMPLOYEE-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 80 CHARACTERS. 01 EMPLOYEE-RECORD. 05 EMPLOYEE-ID PIC 9(5). 05 EMPLOYEE-NAME PIC X(30). 05 EMPLOYEE-ADDRESS PIC X(35). 05 EMPLOYEE-SALARY PIC 9(7)V99.
In this example, the file "EMPLOYEE-FILE" is defined in both the ENVIRONMENT DIVISION (with a SELECT statement) and the DATA DIVISION (with an FD entry). This connection links the physical file characteristics to the logical record layout.
An FD entry can be followed by multiple 01-level record descriptions, which is useful when a file contains different record types or when you need different views of the same data.
12345678910111213141516171819202122232425262728FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 100 CHARACTERS. 01 CUSTOMER-RECORD. 05 RECORD-TYPE PIC X. 88 CUSTOMER-HEADER VALUE "H". 88 CUSTOMER-DETAIL VALUE "D". 88 CUSTOMER-FOOTER VALUE "F". 05 CUSTOMER-DATA PIC X(99). 01 CUSTOMER-HEADER-RECORD REDEFINES CUSTOMER-RECORD. 05 HR-RECORD-TYPE PIC X. 05 HR-FILE-DATE PIC 9(8). 05 HR-RECORD-COUNT PIC 9(5). 05 HR-FILLER PIC X(86). 01 CUSTOMER-DETAIL-RECORD REDEFINES CUSTOMER-RECORD. 05 DR-RECORD-TYPE PIC X. 05 DR-CUSTOMER-ID PIC 9(5). 05 DR-CUSTOMER-NAME PIC X(30). 05 DR-CUSTOMER-ADDR PIC X(50). 05 DR-ACCOUNT-STATUS PIC X. 05 DR-FILLER PIC X(13). 01 CUSTOMER-FOOTER-RECORD REDEFINES CUSTOMER-RECORD. 05 FR-RECORD-TYPE PIC X. 05 FR-TOTAL-CUSTOMERS PIC 9(5). 05 FR-FILLER PIC X(94).
This example shows a file with three different record types (header, detail, and footer), each with its own record description. The REDEFINES clause indicates that each record layout is an alternative view of the same storage area.
The LABEL RECORDS clause in an FD entry historically specified whether the file had standard labels, user labels, or no labels. In modern COBOL, this clause is often optional or treated as syntax-only, as file labeling is typically handled by the operating system or file system.
1234567891011FD file-name LABEL RECORDS ARE STANDARD ... FD file-name LABEL RECORDS ARE OMITTED ... FD file-name LABEL RECORDS ARE data-name ...
The LABEL RECORDS clause dates back to the early days of COBOL when files were often stored on tapes or other sequential media. Labels provided information about the file, such as:
In modern systems, this information is typically managed by the file system or database management system, making the LABEL RECORDS clause less relevant. However, it is still required in some COBOL dialects for backward compatibility.
In contemporary COBOL applications, you'll typically see one of these approaches:
12345678910111213* Option 1: Include the clause with STANDARD FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD ... * Option 2: Omit the clause entirely (if your compiler allows) FD CUSTOMER-FILE ... * Option 3: Use a compiler directive to make it optional >>DEFINE LABEL-RECORDS-NOT-REQUIRED FD CUSTOMER-FILE ...
Most modern COBOL programs use Option 1 (LABEL RECORDS ARE STANDARD) for compatibility, even though the clause may not have a functional impact on the file processing.
The BLOCK CONTAINS clause specifies the size of physical blocks or the blocking factor for a file. Blocking is the process of grouping multiple logical records into a single physical record to improve I/O efficiency. This clause is particularly important for files on tape or other sequential storage media.
1234567891011121314151617* Specify number of records per block FD file-name BLOCK CONTAINS 10 RECORDS ... * Specify block size in characters or words FD file-name BLOCK CONTAINS 800 CHARACTERS ... FD file-name BLOCK CONTAINS 200 TO 400 CHARACTERS ... FD file-name BLOCK CONTAINS 100 WORDS ...
The blocking factor (number of records per block) affects I/O performance:
123456789* Scenario 1: Small blocking factor FD TRANSACTION-FILE-1 BLOCK CONTAINS 1 RECORD RECORD CONTAINS 100 CHARACTERS. * Scenario 2: Larger blocking factor FD TRANSACTION-FILE-2 BLOCK CONTAINS 50 RECORDS RECORD CONTAINS 100 CHARACTERS.
Impact of blocking on a file with 10,000 records of 100 characters each:
Scenario | Block Size | Blocks Required | I/O Operations |
---|---|---|---|
Small blocking | 100 bytes | 10,000 | 10,000 |
Large blocking | 5,000 bytes | 200 | 200 |
The second scenario requires significantly fewer I/O operations, potentially improving performance but requiring more memory for each I/O buffer.
In contemporary computing environments:
The RECORD CONTAINS clause specifies the size of logical records in a file. It defines how much data is processed as a single unit when reading from or writing to a file. This clause is essential for defining the record format, especially for fixed-length and variable-length record handling.
12345678910111213141516171819* Fixed-length records FD CUSTOMER-FILE RECORD CONTAINS 100 CHARACTERS ... * Variable-length records FD TRANSACTION-FILE RECORD IS VARYING IN SIZE FROM 50 TO 150 CHARACTERS DEPENDING ON RECORD-SIZE ... * Omitting the clause (size determined from record description) FD PRODUCT-FILE ... 01 PRODUCT-RECORD. 05 PRODUCT-ID PIC 9(5). 05 PRODUCT-NAME PIC X(30). 05 PRODUCT-PRICE PIC 9(5)V99. * Record size is implicitly 42 characters
When working with variable-length records, you must manage the record size field:
12345678910111213141516171819202122232425262728293031323334353637383940414243IDENTIFICATION DIVISION. PROGRAM-ID. VARLEN. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT VARIABLE-FILE ASSIGN TO "VARDATA.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS FILE-STATUS. DATA DIVISION. FILE SECTION. FD VARIABLE-FILE RECORD IS VARYING IN SIZE FROM 10 TO 100 CHARACTERS DEPENDING ON RECORD-SIZE. 01 VARIABLE-RECORD. 05 RECORD-TYPE PIC X. 05 DATA-FIELD PIC X(99). WORKING-STORAGE SECTION. 01 FILE-STATUS PIC XX. 01 RECORD-SIZE PIC 9(3). PROCEDURE DIVISION. MAIN-PROCESS. OPEN OUTPUT VARIABLE-FILE * Write a short record MOVE "A" TO RECORD-TYPE MOVE "SHORT DATA" TO DATA-FIELD MOVE 10 TO RECORD-SIZE WRITE VARIABLE-RECORD * Write a longer record MOVE "B" TO RECORD-TYPE MOVE "THIS IS A MUCH LONGER DATA RECORD WITH MORE INFORMATION" TO DATA-FIELD MOVE 50 TO RECORD-SIZE WRITE VARIABLE-RECORD CLOSE VARIABLE-FILE STOP RUN.
This example shows how to write variable-length records. The RECORD-SIZE field in WORKING-STORAGE is set before each WRITE operation to indicate the actual length of the current record.
Aspect | Fixed-Length | Variable-Length |
---|---|---|
Storage Efficiency | Less efficient - all records use maximum space | More efficient - only uses needed space |
Processing Complexity | Simpler to process | More complex - must track record sizes |
Random Access | Easy - can calculate record position | Difficult - cannot predict record position |
I/O Performance | Predictable, often faster | May be slower due to additional processing |
Use Case | Uniform data, indexed files | Diverse data sizes, space optimization |
The CODE-SET clause specifies the character code set used for a file. This is particularly important in environments where data might be exchanged between systems with different character encodings, such as EBCDIC (mainframes) and ASCII (most distributed systems).
12345678FD DATA-FILE CODE-SET IS ALPHABET-NAME ... * Example with a specific alphabet FD IMPORT-FILE CODE-SET IS ASCII-ALPHABET ...
The ALPHABET-NAME must be defined in the SPECIAL-NAMES paragraph of the ENVIRONMENT DIVISION.
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667IDENTIFICATION DIVISION. PROGRAM-ID. CODESET. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. ALPHABET ASCII-ALPHABET IS STANDARD-1 ALPHABET EBCDIC-ALPHABET IS STANDARD-2. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT ASCII-FILE ASSIGN TO "ASCIIDATA.TXT" ORGANIZATION IS LINE SEQUENTIAL FILE STATUS IS ASCII-STATUS. SELECT EBCDIC-FILE ASSIGN TO "EBCDICDATA.DAT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS EBCDIC-STATUS. DATA DIVISION. FILE SECTION. FD ASCII-FILE CODE-SET IS ASCII-ALPHABET RECORD CONTAINS 80 CHARACTERS. 01 ASCII-RECORD PIC X(80). FD EBCDIC-FILE CODE-SET IS EBCDIC-ALPHABET RECORD CONTAINS 80 CHARACTERS. 01 EBCDIC-RECORD PIC X(80). WORKING-STORAGE SECTION. 01 FILE-STATUSES. 05 ASCII-STATUS PIC XX. 05 EBCDIC-STATUS PIC XX. 01 EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-FILES UNTIL END-OF-FILE PERFORM FINALIZATION STOP RUN. INITIALIZATION. OPEN INPUT ASCII-FILE OPEN OUTPUT EBCDIC-FILE IF ASCII-STATUS NOT = "00" DISPLAY "Error opening ASCII file: " ASCII-STATUS MOVE "Y" TO EOF-FLAG END-IF. PROCESS-FILES. READ ASCII-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END MOVE ASCII-RECORD TO EBCDIC-RECORD WRITE EBCDIC-RECORD END-READ. FINALIZATION. CLOSE ASCII-FILE CLOSE EBCDIC-FILE DISPLAY "File conversion completed.".
This example reads data from an ASCII file and writes it to an EBCDIC file. The CODE-SET clause ensures that character code conversion happens automatically during file operations. The ALPHABETs are defined in the SPECIAL-NAMES paragraph.
Different computing environments use different character encodings:
Encoding | Common Environment | Characteristics |
---|---|---|
EBCDIC | IBM mainframes, AS/400 | 8-bit, non-ASCII compatible, multiple variants |
ASCII | UNIX, Linux, Windows, Mac | 7-bit standard, widely used in text files |
ANSI/Windows | Windows systems | 8-bit extension of ASCII with code pages |
UTF-8 | Modern web, cross-platform | Variable-length, Unicode compatible |
The CODE-SET clause is crucial when exchanging data between these different environments, particularly in mainframe-to-distributed system integration scenarios.
In contemporary COBOL environments:
Write an FD entry for a customer master file with the following requirements:
12345678910FD CUSTOMER-MASTER-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 20 RECORDS RECORD CONTAINS 200 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(9). 05 CUSTOMER-NAME PIC X(50). 05 CUSTOMER-ADDRESS PIC X(100). 05 CUSTOMER-STATUS PIC X. 05 FILLER PIC X(40).
Note that a FILLER field is added to pad the record to 200 characters.
Write the FILE SECTION for a program that processes transaction records with variable lengths ranging from 50 to 200 characters. The record length is stored in a field called TRANS-LENGTH. Include appropriate record descriptions.
12345678910111213FILE SECTION. FD TRANSACTION-FILE LABEL RECORDS ARE STANDARD RECORD IS VARYING IN SIZE FROM 50 TO 200 CHARACTERS DEPENDING ON TRANS-LENGTH. 01 TRANSACTION-RECORD. 05 TRANS-CODE PIC X(2). 05 TRANS-DATE PIC 9(8). 05 TRANS-AMOUNT PIC 9(7)V99. 05 TRANS-DESCRIPTION PIC X(181). WORKING-STORAGE SECTION. 01 TRANS-LENGTH PIC 9(3).
The TRANS-LENGTH field in WORKING-STORAGE will hold the actual length of each record and must be set before each WRITE operation.
Create a FILE SECTION for an inventory file that contains three types of records: header records (type 'H'), detail records (type 'D'), and trailer records (type 'T'). Each record is 100 characters long.
12345678910111213141516171819202122232425262728293031323334FILE SECTION. FD INVENTORY-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 100 CHARACTERS. 01 INVENTORY-RECORD. 05 RECORD-TYPE PIC X. 88 HEADER-RECORD VALUE 'H'. 88 DETAIL-RECORD VALUE 'D'. 88 TRAILER-RECORD VALUE 'T'. 05 RECORD-DATA PIC X(99). 01 HEADER-RECORD REDEFINES INVENTORY-RECORD. 05 HR-TYPE PIC X. 05 HR-FILE-DATE PIC 9(8). 05 HR-COMPANY-NAME PIC X(50). 05 HR-VERSION PIC 9(2). 05 HR-FILLER PIC X(39). 01 DETAIL-RECORD REDEFINES INVENTORY-RECORD. 05 DR-TYPE PIC X. 05 DR-ITEM-NUMBER PIC 9(10). 05 DR-ITEM-NAME PIC X(30). 05 DR-QUANTITY PIC 9(5). 05 DR-UNIT-PRICE PIC 9(5)V99. 05 DR-LOCATION PIC X(10). 05 DR-STATUS PIC X. 05 DR-FILLER PIC X(36). 01 TRAILER-RECORD REDEFINES INVENTORY-RECORD. 05 TR-TYPE PIC X. 05 TR-RECORD-COUNT PIC 9(10). 05 TR-TOTAL-ITEMS PIC 9(10). 05 TR-TOTAL-VALUE PIC 9(10)V99. 05 TR-FILLER PIC X(66).
This solution uses REDEFINES to provide different views of the same record area depending on the record type. Condition names (88-level items) make it easy to check record types in the procedure division.
1. What is the purpose of the FD entry in COBOL?
2. Where in a COBOL program would you find the FD entry?
3. What is the purpose of the LABEL RECORDS clause in an FD entry?
4. What does the BLOCK CONTAINS clause specify?
5. What is the relationship between a file defined with SELECT in the ENVIRONMENT DIVISION and its FD entry?
Understanding different file organizations in COBOL.
How to work with sequential files in COBOL.
Overview of all sections in the DATA DIVISION.
How files are defined in the ENVIRONMENT DIVISION.
Handling file operation errors in COBOL.