MainframeMaster

COBOL Tutorial

COBOL RECORDS Clause - Quick Reference

Progress0 of 0 lessons

Overview

The RECORDS clause is a subclause of BLOCK CONTAINS used in File Description (FD) entries to specify the number of logical records that are grouped into each physical block. This blocking factor is crucial for optimizing I/O performance in COBOL file processing.

Purpose and Usage

  • Blocking factor specification - Defines records per physical block
  • I/O performance optimization - Reduces number of I/O operations
  • Storage efficiency - Optimizes use of storage media
  • Memory management - Affects I/O buffer requirements
  • File organization - Influences how data is physically stored

Blocking Concept

Physical Block 1: [Record1][Record2][Record3][Record4][Record5]
Physical Block 2: [Record6][Record7][Record8][Record9][Record10]
Physical Block 3: [Record11][Record12][Record13][Record14][Record15]
BLOCK CONTAINS 5 RECORDS

Multiple logical records are grouped into single physical blocks for efficient I/O operations.

Syntax

The RECORDS clause follows specific syntax patterns within BLOCK CONTAINS specifications in File Description entries.

Basic Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
* Basic RECORDS clause syntax BLOCK CONTAINS n RECORDS * Examples BLOCK CONTAINS 10 RECORDS BLOCK CONTAINS 50 RECORDS BLOCK CONTAINS 1 RECORD * Complete FD entry example FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 20 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-SALARY PIC 9(7)V99.

The RECORDS clause is always used with BLOCK CONTAINS to specify the blocking factor.

Alternative Blocking Specifications

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
* Blocking by character count BLOCK CONTAINS 800 CHARACTERS * Blocking by word count BLOCK CONTAINS 200 WORDS * Variable blocking (range) BLOCK CONTAINS 100 TO 200 CHARACTERS * Mixed specifications FD DATA-FILE BLOCK CONTAINS 10 RECORDS RECORD CONTAINS 80 CHARACTERS. * Character-based blocking FD TEXT-FILE BLOCK CONTAINS 1600 CHARACTERS RECORD CONTAINS 80 CHARACTERS.

RECORDS is one of several ways to specify blocking; CHARACTERS and WORDS are alternatives.

Blocking Factor Guidelines

File TypeTypical Blocking FactorReasoning
Sequential Files10-50 recordsOptimize for sequential processing
Indexed Files5-20 recordsBalance I/O efficiency with index performance
Large Files50-100 recordsMaximize I/O efficiency for bulk processing
Small Files1-10 recordsMinimize memory usage
Tape Files20-100 recordsOptimize for tape I/O characteristics

Performance Impact

The RECORDS clause significantly affects file processing performance through its impact on I/O operations and memory usage.

I/O Performance Analysis

cobol
1
2
3
4
5
6
7
8
9
* Scenario 1: Small blocking factor FD FILE-1 BLOCK CONTAINS 1 RECORD RECORD CONTAINS 100 CHARACTERS. * Scenario 2: Large blocking factor FD FILE-2 BLOCK CONTAINS 50 RECORDS RECORD CONTAINS 100 CHARACTERS.

Impact on a file with 10,000 records of 100 characters each:

ScenarioBlock SizeBlocks RequiredI/O OperationsMemory per I/O
Small blocking100 bytes10,00010,000100 bytes
Large blocking5,000 bytes2002005,000 bytes

Large blocking reduces I/O operations by 98% but requires 50x more memory per operation.

Memory Considerations

  • I/O buffer size - Each block requires memory for I/O buffers
  • Multiple file buffers - Each open file needs its own buffer space
  • System limitations - Total buffer memory must fit in available RAM
  • Concurrent processing - Multiple programs may compete for buffer memory
  • Virtual memory impact - Large buffers may cause paging

Storage Medium Considerations

Storage TypeOptimal BlockingReasoning
Magnetic TapeLarge blocks (50-100 records)Minimize tape stops and starts
Hard DiskMedium blocks (10-50 records)Balance I/O efficiency with seek time
SSDSmaller blocks (5-20 records)SSDs have different I/O characteristics
Network StorageLarger blocks (20-100 records)Reduce network overhead

Practical Examples

These examples demonstrate how to use the RECORDS clause effectively in different file processing scenarios.

Customer Master File

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
IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-PROCESS. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTMAST.DAT" ORGANIZATION IS INDEXED ACCESS MODE IS SEQUENTIAL RECORD KEY IS CUSTOMER-ID FILE STATUS IS CUSTOMER-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 25 RECORDS RECORD CONTAINS 100 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(50). 05 CUSTOMER-STATUS PIC X. 05 FILLER PIC X(14). WORKING-STORAGE SECTION. 01 CUSTOMER-STATUS PIC XX. 01 RECORD-COUNT PIC 9(6) VALUE ZERO. 01 EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. PROCEDURE DIVISION. MAIN-PROCESS. OPEN INPUT CUSTOMER-FILE PERFORM READ-CUSTOMERS UNTIL END-OF-FILE CLOSE CUSTOMER-FILE DISPLAY "Total records processed: " RECORD-COUNT STOP RUN. READ-CUSTOMERS. READ CUSTOMER-FILE AT END MOVE 'Y' TO EOF-FLAG NOT AT END ADD 1 TO RECORD-COUNT PERFORM PROCESS-CUSTOMER END-READ.

This example uses BLOCK CONTAINS 25 RECORDS for efficient sequential processing of customer data.

Transaction Processing File

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
FD TRANSACTION-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 50 RECORDS RECORD CONTAINS 80 CHARACTERS. 01 TRANSACTION-RECORD. 05 TRANS-DATE PIC 9(8). 05 TRANS-TIME PIC 9(6). 05 TRANS-TYPE PIC X. 05 TRANS-AMOUNT PIC 9(7)V99. 05 ACCOUNT-NUMBER PIC 9(10). 05 TRANS-DESCRIPTION PIC X(40). 05 FILLER PIC X(6). * High-volume transaction processing benefits from larger blocking * 50 records per block optimizes I/O for bulk processing * Each block contains 4,000 characters (50 × 80)

High-volume transaction files use larger blocking factors for maximum I/O efficiency.

Report Output File

cobol
1
2
3
4
5
6
7
8
9
10
11
FD REPORT-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 10 RECORDS RECORD CONTAINS 132 CHARACTERS. 01 REPORT-RECORD. 05 REPORT-LINE PIC X(132). * Report files use smaller blocking for flexibility * 10 records per block allows for efficient line-by-line processing * Each block contains 1,320 characters (10 × 132) * Suitable for both sequential and random access patterns

Report files use moderate blocking factors to balance I/O efficiency with processing flexibility.

Best Practices and Tips

Following these best practices ensures optimal use of the RECORDS clause for file processing performance.

Blocking Factor Selection

  • Test different values - Performance test with various blocking factors
  • Consider access patterns - Sequential vs. random access requirements
  • Account for memory constraints - Ensure buffer memory is available
  • Match storage characteristics - Optimize for specific storage media
  • Consider file size - Larger files benefit from larger blocking
  • Balance I/O vs. memory - Find optimal trade-off for your environment

Common Pitfalls to Avoid

PitfallProblemSolution
Too small blockingExcessive I/O operationsUse at least 5-10 records per block
Too large blockingMemory pressure, poor random accessLimit to 50-100 records for most files
Ignoring storage mediumSuboptimal performanceMatch blocking to storage characteristics
No performance testingUnknown optimal valuesTest with realistic data volumes
Inconsistent blockingMaintenance complexityStandardize blocking across similar files

Performance Monitoring

  • Monitor I/O statistics - Track read/write operations and timing
  • Measure memory usage - Ensure buffers don't cause memory pressure
  • Test with production data - Use realistic file sizes and access patterns
  • Compare alternatives - Benchmark different blocking factors
  • Consider system load - Account for concurrent file processing
  • Document performance - Record optimal settings for future reference

RECORDS Clause Quick Reference

UsageSyntaxExample
Basic blockingBLOCK CONTAINS n RECORDSBLOCK CONTAINS 10 RECORDS
With RECORD CONTAINSBLOCK CONTAINS n RECORDS
RECORD CONTAINS m CHARACTERS
BLOCK CONTAINS 20 RECORDS
RECORD CONTAINS 80 CHARACTERS
Character blockingBLOCK CONTAINS n CHARACTERSBLOCK CONTAINS 800 CHARACTERS
Word blockingBLOCK CONTAINS n WORDSBLOCK CONTAINS 200 WORDS
Variable blockingBLOCK CONTAINS n TO m CHARACTERSBLOCK CONTAINS 100 TO 200 CHARACTERS

Test Your Knowledge

1. What is the primary purpose of the RECORDS clause in COBOL?

  • To define data types
  • To specify the number of logical records in a physical block
  • To control file operations
  • To perform calculations

2. In which context is the RECORDS clause most commonly used?

  • PROCEDURE DIVISION
  • FILE SECTION FD entries
  • WORKING-STORAGE SECTION
  • ENVIRONMENT DIVISION

3. What is the relationship between RECORDS and BLOCK CONTAINS?

  • They are the same thing
  • RECORDS is a subclause of BLOCK CONTAINS
  • BLOCK CONTAINS is a subclause of RECORDS
  • They are unrelated

4. What happens if you specify BLOCK CONTAINS 10 RECORDS?

  • The file will have exactly 10 records
  • Each physical block will contain up to 10 logical records
  • The file will be limited to 10 records
  • The program will process 10 records at a time

5. Which of the following is NOT a valid RECORDS specification?

  • BLOCK CONTAINS 5 RECORDS
  • BLOCK CONTAINS 100 CHARACTERS
  • BLOCK CONTAINS 10 TO 20 RECORDS
  • RECORDS CONTAINS 50 CHARACTERS

Frequently Asked Questions