Progress0 of 0 lessons

COBOL Record Blocking

Record blocking is a fundamental concept in COBOL file processing that significantly impacts I/O performance and storage efficiency. Understanding the difference between physical records (blocks) and logical records, and how to specify blocking factors, is essential for optimizing file operations in mainframe environments. This guide covers physical and logical records, the BLOCK CONTAINS clause, blocking factors, and performance considerations.

What is Record Blocking?

Record blocking is the process of grouping multiple logical records into a single physical record (block) for storage and I/O operations. This technique:

Physical Records vs Logical Records

Understanding the distinction between physical and logical records is crucial for effective file processing:

Logical Records

A logical record is the unit of data that your COBOL program processes:

cobol
1
2
3
4
5
6
7
01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC X(8). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(50). 05 CUSTOMER-PHONE PIC X(12). *> This is a logical record - what your program processes

Physical Records (Blocks)

A physical record, also called a block, is what is actually stored on the storage device:

Visual Example

Consider a file with logical records of 80 characters each, blocked at 10 records per block:

Physical Block 1 (800 characters):
[Record 1: 80 chars][Record 2: 80 chars][Record 3: 80 chars]...
[Record 10: 80 chars]

Physical Block 2 (800 characters):
[Record 11: 80 chars][Record 12: 80 chars]...
[Record 20: 80 chars]

When your program reads Record 1, the system actually reads the entire first block (containing Records 1-10) into memory. Subsequent READ statements for Records 2-10 use the data already in memory, avoiding additional I/O operations.

The BLOCK CONTAINS Clause

The BLOCK CONTAINS clause in the File Description (FD) entry specifies how logical records are grouped into physical blocks. This clause is essential for optimizing I/O performance.

Syntax

cobol
1
2
3
4
5
FD file-name LABEL RECORDS ARE STANDARD BLOCK CONTAINS [integer-1] [TO integer-2] {RECORDS | CHARACTERS | WORDS} RECORD CONTAINS [integer-3] [TO integer-4] CHARACTERS.

Blocking by Records

The most common approach is to specify the number of logical records per physical block:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 20 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-SALARY PIC 9(7)V99. 05 FILLER PIC X(5). *> This creates blocks of 2,000 characters (20 × 100) *> Each physical I/O operation transfers 20 logical records

Blocking by Characters

You can also specify blocking by the total number of characters:

cobol
1
2
3
4
5
6
7
8
FD DATA-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 1600 CHARACTERS RECORD CONTAINS 80 CHARACTERS. *> This creates blocks of 1,600 characters *> With 80-character records, this equals 20 records per block *> (1600 ÷ 80 = 20)

Variable Blocking

For variable-length records, you can specify a range:

cobol
1
2
3
4
5
6
7
8
FD VARIABLE-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 100 TO 200 CHARACTERS RECORD CONTAINS 50 TO 100 CHARACTERS DEPENDING ON RECORD-LENGTH. *> Blocks can vary in size from 100 to 200 characters *> Each block contains one or more variable-length records

Unblocked Records

If you don't specify BLOCK CONTAINS, or specify BLOCK CONTAINS 0 RECORDS, each logical record becomes its own physical block:

cobol
1
2
3
4
5
6
7
8
FD UNBLOCKED-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 0 RECORDS RECORD CONTAINS 80 CHARACTERS. *> Each logical record is a separate physical block *> Maximum I/O operations (one per record) *> Used when random access is more important than sequential performance

Blocking Factor

The blocking factor is the number of logical records contained in each physical block. Choosing the right blocking factor is crucial for optimal performance.

Factors to Consider

Typical Blocking Factors

File TypeTypical Blocking FactorReasoning
Sequential Files10-50 recordsOptimize for sequential processing
Indexed Files (VSAM)5-20 recordsBalance I/O efficiency with index performance
Large Batch 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

Record blocking has a significant impact on file processing performance:

I/O Operations Reduction

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

Blocking FactorBlock SizeBlocks RequiredI/O Operations
1 (unblocked)100 bytes10,00010,000
10 records1,000 bytes1,0001,000 (90% reduction)
50 records5,000 bytes200200 (98% reduction)
100 records10,000 bytes100100 (99% reduction)

As you can see, increasing the blocking factor dramatically reduces the number of I/O operations, which directly improves performance.

Memory Considerations

While larger blocks reduce I/O operations, they also require more memory:

Practical Examples

Example 1: 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
48
49
50
IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-PROCESS. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTMAST.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS WS-CUST-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 WS-CUST-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 *> Each physical block contains 25 logical records (2,500 characters) *> Reading 25 records requires only 1 I/O operation instead of 25

Example 2: High-Volume Transaction File

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
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) *> Reduces I/O operations by 98% compared to unblocked records

Example 3: 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

Best Practices

1. Choose Appropriate Blocking Factors

2. Consider File Characteristics

3. Monitor Performance

4. Common Pitfalls to Avoid

Explain It Like I'm 5 Years Old

Imagine you're moving books from one bookshelf to another:

If you move books one at a time, you have to walk back and forth many times. That's like unblocked records - each record requires a separate I/O operation (walking to the bookshelf).

But if you use a box to carry many books at once, you make fewer trips. That's like record blocking - you put many logical records (books) into one physical block (box), so you make fewer I/O operations (trips).

The bigger the box (block), the fewer trips you make, but you need a stronger person (more memory) to carry it. So you need to find the right size box - not too small (too many trips) and not too big (too heavy to carry)!

Exercises

Exercise 1: Calculate Block Sizes

Calculate the physical block size for each scenario:

  • Record size: 80 characters, Blocking factor: 10 records
  • Record size: 100 characters, Blocking factor: 25 records
  • Record size: 200 characters, Blocking factor: 50 records

Answer: Block size = Record size × Blocking factor. So: 800 characters, 2,500 characters, and 10,000 characters respectively.

Exercise 2: Compare I/O Operations

A file contains 5,000 records of 120 characters each. Compare the number of I/O operations required for:

  • Unblocked records (blocking factor = 1)
  • Blocking factor of 20 records
  • Blocking factor of 50 records

Answer: Unblocked: 5,000 I/O operations. Blocking factor 20: 250 I/O operations (95% reduction). Blocking factor 50: 100 I/O operations (98% reduction).

Exercise 3: Write FD Entry

Write a File Description entry for a customer file with:

  • Record size: 150 characters
  • Blocking factor: 30 records per block
  • Standard labels

Hint: Use BLOCK CONTAINS 30 RECORDS and RECORD CONTAINS 150 CHARACTERS.

Exercise 4: Performance Analysis

Analyze the performance impact of different blocking factors:

  • File: 10,000 records, 100 characters each
  • Compare blocking factors: 1, 10, 25, 50, 100
  • Calculate I/O operations and block sizes for each
  • Consider memory requirements (assume 10KB buffer per block)

Quiz

Test Your Knowledge

1. What is the difference between a physical record and a logical record?

  • A) They are the same thing
  • B) A physical record is what the program processes, a logical record is what is stored
  • C) A logical record is what the program processes, a physical record (block) contains multiple logical records
  • D) Physical records are always larger than logical records

2. What does BLOCK CONTAINS 20 RECORDS mean?

  • A) The file will have exactly 20 records
  • B) Each physical block will contain up to 20 logical records
  • C) The program will process 20 records at a time
  • D) The file is limited to 20 records

3. Why is record blocking important for performance?

  • A) It makes records easier to read
  • B) It reduces the number of I/O operations by grouping multiple logical records into physical blocks
  • C) It makes programs run faster automatically
  • D) It reduces memory usage

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

  • A) The file will be empty
  • B) Each logical record becomes its own physical block (unblocked)
  • C) The file cannot be created
  • D) Records will be written randomly

5. Which blocking factor would be most appropriate for a large sequential batch file?

  • A) 1 record (unblocked)
  • B) 5 records
  • C) 50 records
  • D) 1000 records

6. What is the relationship between block size, record size, and blocking factor?

  • A) Block size = Record size + Blocking factor
  • B) Block size = Record size × Blocking factor
  • C) Block size = Record size ÷ Blocking factor
  • D) There is no relationship

Related Pages