MainframeMaster

COBOL Tutorial

COBOL CONTROL and CONTROLS

Master system control and I/O management with CONTROL and CONTROLS. Learn how to implement control break processing, manage program flow, and create sophisticated reporting systems in your COBOL applications.

Overview

CONTROL and CONTROLS in COBOL refer to mechanisms for managing program flow, data processing, and system behavior based on changing field values or conditions. The most common application is control break processing, where programs monitor specific fields and perform special processing when these control fields change their values during sequential data processing.

Control break processing is fundamental to creating well-structured reports and data summaries. It allows programs to group related data together, calculate subtotals and totals, and present information in a hierarchical format that's easy to read and understand. This technique is essential for business reporting, financial statements, and data analysis applications.

Understanding control mechanisms is crucial for creating efficient, maintainable COBOL programs that process large volumes of data systematically. These techniques enable you to build robust applications that handle complex data relationships and produce professional-quality output.

Basic Control Break Processing

Single Control Field

The simplest form of control break processing involves monitoring a single control field and performing special processing when its value changes:

cobol
1
2
3
4
5
6
7
8
9
WORKING-STORAGE SECTION. 01 WS-CONTROL-FIELDS. 05 WS-CURRENT-DEPT PIC X(5). 05 WS-PREVIOUS-DEPT PIC X(5). 05 WS-FIRST-RECORD PIC X(1) VALUE 'Y'. 01 WS-TOTALS. 05 WS-DEPT-TOTAL PIC 9(7)V99 VALUE ZERO. 05 WS-GRAND-TOTAL PIC 9(9)V99 VALUE ZERO.

This structure defines the basic elements needed for control break processing: current and previous control field values, a first-record indicator, and accumulator fields for totals. The control logic compares current and previous values to detect when a break occurs.

Control Break Detection Logic

The core logic for detecting control breaks involves comparing the current record's control field with the previous value:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
PROCESS-EMPLOYEE-RECORD. MOVE EMP-DEPARTMENT TO WS-CURRENT-DEPT IF WS-FIRST-RECORD = 'Y' PERFORM INITIALIZE-CONTROL-PROCESSING ELSE IF WS-CURRENT-DEPT NOT = WS-PREVIOUS-DEPT PERFORM DEPARTMENT-BREAK-PROCESSING END-IF END-IF PERFORM PROCESS-DETAIL-RECORD MOVE WS-CURRENT-DEPT TO WS-PREVIOUS-DEPT.

This logic first handles the special case of the first record, then checks for control breaks on subsequent records. When a break is detected, special processing is performed before handling the current record. The previous control value is updated after processing each record.

Break Processing Routine

The break processing routine handles the end-of-group activities and prepares for the new group:

cobol
1
2
3
4
5
6
7
8
9
10
DEPARTMENT-BREAK-PROCESSING. PERFORM PRINT-DEPARTMENT-TOTAL PERFORM RESET-DEPARTMENT-COUNTERS PERFORM PRINT-DEPARTMENT-HEADER. PRINT-DEPARTMENT-TOTAL. MOVE WS-DEPT-TOTAL TO RPT-TOTAL-AMOUNT MOVE WS-PREVIOUS-DEPT TO RPT-DEPT-CODE WRITE REPORT-LINE FROM DEPARTMENT-TOTAL-LINE ADD WS-DEPT-TOTAL TO WS-GRAND-TOTAL.

Break processing typically involves printing totals for the completed group, resetting accumulators for the new group, and printing headers or other formatting for the new group. This creates clear visual separation between different groups in the output.

Multi-Level Control Processing

Hierarchical Control Fields

Complex reports often require multiple levels of control breaks, such as department within division, or product within category:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
01 WS-CONTROL-STRUCTURE. 05 WS-MAJOR-CONTROL. 10 WS-CURRENT-DIVISION PIC X(3). 10 WS-PREVIOUS-DIVISION PIC X(3). 05 WS-MINOR-CONTROL. 10 WS-CURRENT-DEPT PIC X(5). 10 WS-PREVIOUS-DEPT PIC X(5). 01 WS-HIERARCHICAL-TOTALS. 05 WS-DEPT-TOTAL PIC 9(7)V99. 05 WS-DIVISION-TOTAL PIC 9(8)V99. 05 WS-COMPANY-TOTAL PIC 9(9)V99.

Multi-level control requires separate tracking for each control level and corresponding total accumulators. The hierarchy must be maintained consistently throughout the processing, with higher-level breaks triggering lower-level break processing.

Multi-Level Break Detection

Detection logic for multi-level controls must check from highest to lowest level, as a major break implies minor breaks as well:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
CHECK-FOR-CONTROL-BREAKS. MOVE EMP-DIVISION TO WS-CURRENT-DIVISION MOVE EMP-DEPARTMENT TO WS-CURRENT-DEPT IF WS-CURRENT-DIVISION NOT = WS-PREVIOUS-DIVISION PERFORM DIVISION-BREAK-PROCESSING PERFORM DEPARTMENT-BREAK-PROCESSING ELSE IF WS-CURRENT-DEPT NOT = WS-PREVIOUS-DEPT PERFORM DEPARTMENT-BREAK-PROCESSING END-IF END-IF.

When a major control (division) breaks, both division and department break processing must occur. When only a minor control (department) breaks, only department processing is needed. This cascading approach ensures proper hierarchical handling of control breaks.

Hierarchical Total Processing

Multi-level totals require careful accumulation and rolling up of values through the hierarchy:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
DEPARTMENT-BREAK-PROCESSING. PERFORM PRINT-DEPT-TOTAL ADD WS-DEPT-TOTAL TO WS-DIVISION-TOTAL MOVE ZERO TO WS-DEPT-TOTAL. DIVISION-BREAK-PROCESSING. PERFORM PRINT-DIVISION-TOTAL ADD WS-DIVISION-TOTAL TO WS-COMPANY-TOTAL MOVE ZERO TO WS-DIVISION-TOTAL. PRINT-DEPT-TOTAL. MOVE WS-DEPT-TOTAL TO RPT-DEPT-AMOUNT WRITE REPORT-LINE FROM DEPT-TOTAL-LINE.

Each level accumulates its totals and rolls them up to the next higher level during break processing. This creates a complete hierarchy of subtotals and grand totals that provide comprehensive summary information.

Tutorial: Building a Sales Report System

Let's create a comprehensive sales reporting system that demonstrates advanced control break processing with multiple levels, complex totaling, and professional formatting. This tutorial will show you how to build a real-world reporting system that handles hierarchical data effectively.

Step 1: Define the Report Structure

First, we'll establish the data structures for our multi-level sales report:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
WORKING-STORAGE SECTION. 01 WS-SALES-CONTROL. 05 WS-REGION-CONTROL. 10 WS-CURRENT-REGION PIC X(10). 10 WS-PREVIOUS-REGION PIC X(10). 05 WS-SALESPERSON-CONTROL. 10 WS-CURRENT-SALESPERSON PIC X(20). 10 WS-PREVIOUS-SALESPERSON PIC X(20). 05 WS-PRODUCT-CONTROL. 10 WS-CURRENT-PRODUCT PIC X(15). 10 WS-PREVIOUS-PRODUCT PIC X(15). 01 WS-SALES-TOTALS. 05 WS-PRODUCT-TOTAL PIC 9(8)V99. 05 WS-SALESPERSON-TOTAL PIC 9(9)V99. 05 WS-REGION-TOTAL PIC 9(10)V99. 05 WS-COMPANY-TOTAL PIC 9(11)V99.

This structure supports three levels of control: region (major), salesperson (intermediate), and product (minor). Each level has current and previous value tracking, with corresponding total accumulators for comprehensive reporting.

Step 2: Implement Main Processing Loop

Next, we'll create the main processing loop that handles record reading and control break detection:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
MAIN-PROCESSING. PERFORM OPEN-FILES PERFORM READ-SALES-RECORD PERFORM UNTIL WS-EOF-FLAG = 'Y' PERFORM CHECK-CONTROL-BREAKS PERFORM PROCESS-SALES-DETAIL PERFORM ACCUMULATE-TOTALS PERFORM READ-SALES-RECORD END-PERFORM PERFORM FINAL-BREAK-PROCESSING PERFORM CLOSE-FILES.

The main loop reads records sequentially, checks for control breaks, processes detail information, accumulates totals, and handles end-of-file processing. This structure ensures all records are processed and all control breaks are properly handled.

Step 3: Implement Control Break Logic

Now we'll create the sophisticated control break detection and processing logic:

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
CHECK-CONTROL-BREAKS. MOVE SALES-REGION TO WS-CURRENT-REGION MOVE SALES-SALESPERSON TO WS-CURRENT-SALESPERSON MOVE SALES-PRODUCT TO WS-CURRENT-PRODUCT IF WS-FIRST-RECORD = 'Y' PERFORM INITIALIZE-CONTROL-FIELDS MOVE 'N' TO WS-FIRST-RECORD ELSE IF WS-CURRENT-REGION NOT = WS-PREVIOUS-REGION PERFORM PRODUCT-BREAK PERFORM SALESPERSON-BREAK PERFORM REGION-BREAK ELSE IF WS-CURRENT-SALESPERSON NOT = WS-PREVIOUS-SALESPERSON PERFORM PRODUCT-BREAK PERFORM SALESPERSON-BREAK ELSE IF WS-CURRENT-PRODUCT NOT = WS-PREVIOUS-PRODUCT PERFORM PRODUCT-BREAK END-IF END-IF END-IF END-IF PERFORM UPDATE-CONTROL-FIELDS.

This logic implements the cascading break detection pattern, where higher-level breaks automatically trigger all lower-level breaks. The first record is handled specially to initialize the control mechanism properly.

Step 4: Implement Break Processing Routines

Let's create the individual break processing routines for each control level:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
PRODUCT-BREAK. PERFORM PRINT-PRODUCT-TOTAL ADD WS-PRODUCT-TOTAL TO WS-SALESPERSON-TOTAL MOVE ZERO TO WS-PRODUCT-TOTAL. SALESPERSON-BREAK. PERFORM PRINT-SALESPERSON-TOTAL ADD WS-SALESPERSON-TOTAL TO WS-REGION-TOTAL MOVE ZERO TO WS-SALESPERSON-TOTAL. REGION-BREAK. PERFORM PRINT-REGION-TOTAL ADD WS-REGION-TOTAL TO WS-COMPANY-TOTAL MOVE ZERO TO WS-REGION-TOTAL.

Each break routine prints the appropriate total, rolls the amount up to the next level, and resets the accumulator for the new group. This creates a clean separation between groups and proper total accumulation.

Step 5: Implement Report Formatting

Finally, we'll create professional report formatting with proper headers and totals:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
PRINT-PRODUCT-TOTAL. MOVE SPACES TO REPORT-LINE MOVE 'Product Total:' TO RPT-DESCRIPTION MOVE WS-PREVIOUS-PRODUCT TO RPT-PRODUCT-NAME MOVE WS-PRODUCT-TOTAL TO RPT-AMOUNT WRITE REPORT-LINE PERFORM SKIP-LINE. PRINT-SALESPERSON-TOTAL. MOVE SPACES TO REPORT-LINE MOVE 'Salesperson Total:' TO RPT-DESCRIPTION MOVE WS-PREVIOUS-SALESPERSON TO RPT-PERSON-NAME MOVE WS-SALESPERSON-TOTAL TO RPT-AMOUNT WRITE REPORT-LINE PERFORM SKIP-TWO-LINES. PRINT-REGION-TOTAL. MOVE SPACES TO REPORT-LINE MOVE 'REGION TOTAL:' TO RPT-DESCRIPTION MOVE WS-PREVIOUS-REGION TO RPT-REGION-NAME MOVE WS-REGION-TOTAL TO RPT-AMOUNT WRITE REPORT-LINE PERFORM SKIP-THREE-LINES.

The formatting routines create visually distinct total lines with appropriate spacing and descriptive text. Different levels use different formatting to create a clear hierarchy in the printed report.

Advanced Control Techniques

Dynamic Control Field Selection

Advanced applications may need to change control fields dynamically based on runtime parameters or user selections:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
01 WS-CONTROL-PARAMETERS. 05 WS-CONTROL-TYPE PIC X(1). 88 CONTROL-BY-DEPT VALUE 'D'. 88 CONTROL-BY-REGION VALUE 'R'. 88 CONTROL-BY-PRODUCT VALUE 'P'. 05 WS-CURRENT-CONTROL PIC X(20). 05 WS-PREVIOUS-CONTROL PIC X(20). DETERMINE-CONTROL-FIELD. EVALUATE TRUE WHEN CONTROL-BY-DEPT MOVE RECORD-DEPARTMENT TO WS-CURRENT-CONTROL WHEN CONTROL-BY-REGION MOVE RECORD-REGION TO WS-CURRENT-CONTROL WHEN CONTROL-BY-PRODUCT MOVE RECORD-PRODUCT TO WS-CURRENT-CONTROL END-EVALUATE.

Dynamic control field selection allows the same program to produce different types of reports based on runtime parameters. This flexibility reduces code duplication and makes programs more maintainable.

Control Break with Conditions

Sometimes control breaks should only occur under certain conditions, such as when specific thresholds are met:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
CHECK-CONDITIONAL-BREAK. IF WS-CURRENT-DEPT NOT = WS-PREVIOUS-DEPT IF WS-DEPT-RECORD-COUNT > 5 PERFORM DEPARTMENT-BREAK-PROCESSING ELSE PERFORM MERGE-SMALL-DEPARTMENT END-IF END-IF. MERGE-SMALL-DEPARTMENT. MOVE 'MISCELLANEOUS' TO WS-CURRENT-DEPT ADD WS-DEPT-TOTAL TO WS-MISC-TOTAL.

Conditional breaks allow for more sophisticated reporting logic, such as combining small groups or applying different processing rules based on data characteristics or business requirements.

Performance Optimization

For large-volume processing, control break logic can be optimized for better performance:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
01 WS-OPTIMIZATION-FLAGS. 05 WS-BREAK-OCCURRED PIC X(1). 05 WS-SKIP-DETAIL-CHECK PIC X(1). OPTIMIZED-CONTROL-CHECK. MOVE 'N' TO WS-BREAK-OCCURRED IF WS-CURRENT-CONTROL NOT = WS-PREVIOUS-CONTROL MOVE 'Y' TO WS-BREAK-OCCURRED PERFORM CONTROL-BREAK-PROCESSING END-IF. PROCESS-RECORD-EFFICIENTLY. IF WS-BREAK-OCCURRED = 'N' PERFORM FAST-DETAIL-PROCESSING ELSE PERFORM FULL-DETAIL-PROCESSING END-IF.

Optimization techniques include using flags to skip unnecessary processing, minimizing field comparisons, and using different processing paths based on whether breaks have occurred. These techniques can significantly improve performance for high-volume applications.

Practical Exercises

Exercise 1: Customer Order Report

Create a customer order report with multiple control levels:

cobol
1
2
3
4
5
6
7
* Design a report with control breaks for: * - Customer (major control) * - Order Date (intermediate control) * - Product Category (minor control) * Include subtotals at each level * Add grand totals and summary statistics * Format professionally with headers and spacing

Solution Approach: Create a three-level hierarchy with proper cascading break logic. Implement total accumulation and rollup through all levels. Include professional formatting with clear visual separation between groups and comprehensive summary information.

Exercise 2: Financial Statement Generator

Build a financial statement generator with complex control processing:

cobol
1
2
3
4
5
6
7
* Create statements with control breaks for: * - Account Type (Assets, Liabilities, Equity) * - Account Category (Current, Fixed, etc.) * - Individual Accounts * Calculate running balances and percentages * Include variance analysis and comparisons * Generate multiple report formats

Solution Approach: Implement sophisticated control logic that handles different account types and categories. Include percentage calculations and variance analysis. Create multiple output formats using the same control break framework.

Exercise 3: Inventory Movement Report

Design an inventory movement report with dynamic control fields:

cobol
1
2
3
4
5
6
7
* Implement flexible reporting with controls for: * - Warehouse Location * - Product Category * - Movement Type (In, Out, Transfer) * Allow runtime selection of control fields * Include quantity and value summaries * Add exception reporting for unusual movements

Solution Approach: Create a flexible control framework that allows dynamic selection of control fields. Implement exception detection logic and comprehensive summary reporting. Include both quantity and value tracking with appropriate totaling.

Best Practices and Guidelines

Data Preparation

  • Always sort input data by all control fields in the correct sequence
  • Validate that input data is properly sorted before processing
  • Handle missing or null control field values appropriately
  • Consider using SORT statements to ensure proper data ordering
  • Document the required sort sequence clearly in program comments
  • Test with unsorted data to verify error handling

Control Logic Design

  • Use meaningful names for control fields and break routines
  • Implement proper initialization for the first record
  • Handle end-of-file processing to print final totals
  • Use consistent patterns for multi-level control breaks
  • Include error handling for unexpected control field values
  • Document the control break hierarchy clearly

Testing and Validation

  • Test with single records, empty files, and large datasets
  • Verify that all control breaks are detected correctly
  • Validate that totals roll up properly through all levels
  • Test edge cases like identical control field values
  • Verify that final totals match detail record sums
  • Test with various combinations of control field changes

Performance and Maintenance

Design control break logic for maintainability and performance. Use clear, consistent naming conventions and document the business logic behind control break decisions. Consider the volume of data being processed and optimize accordingly, but prioritize clarity and correctness over premature optimization.

Regular review and testing of control break logic ensures it continues to meet business requirements as data volumes and reporting needs evolve. Maintain comprehensive test data that covers all possible control break scenarios and edge cases.

Interactive Quiz

Test Your CONTROL and CONTROLS Knowledge

Question 1:

What happens when a major control field breaks in multi-level processing?

Answer: All lower-level control breaks are also triggered. When a major control breaks, it implies that all subordinate controls have also changed, so all lower-level break processing must occur.

Question 2:

What is the most important requirement for control break processing to work correctly?

Answer: Input data must be sorted by control fields. Control break processing depends on sequential processing of records where control field values change in a predictable order.

Question 3:

How should totals be handled during control break processing?

Answer: Print totals and roll up to the next higher level. Each control level should print its totals, add them to the next higher level's accumulator, then reset its own totals for the new group.

Frequently Asked Questions

Related Pages