Control breaks detect changes in key fields and trigger subtotal calculations and report formatting. Learn to process grouped data hierarchically for business reports and summaries.
1234567891011121314151617181920WORKING-STORAGE SECTION. 01 PREVIOUS-DEPT PIC X(10) VALUE SPACES. 01 CURRENT-DEPT PIC X(10). 01 DEPT-TOTAL PIC 9(9)V99 VALUE 0. 01 GRAND-TOTAL PIC 9(9)V99 VALUE 0. PROCEDURE DIVISION. PERFORM UNTIL EOF READ EMPLOYEE-FILE AT END SET EOF TO TRUE NOT AT END MOVE EMP-DEPT TO CURRENT-DEPT IF CURRENT-DEPT NOT = PREVIOUS-DEPT PERFORM DEPT-BREAK END-IF ADD EMP-SALARY TO DEPT-TOTAL ADD EMP-SALARY TO GRAND-TOTAL MOVE CURRENT-DEPT TO PREVIOUS-DEPT END-READ END-PERFORM PERFORM FINAL-BREAK.
Compare current record key fields with previous values to detect changes. When a change occurs, process the control break (subtotals, headers, footers) before continuing with new group processing.
12345678910111213141516DEPT-BREAK. IF PREVIOUS-DEPT NOT = SPACES DISPLAY 'Department Total: ' PREVIOUS-DEPT ' = ' DEPT-TOTAL DISPLAY '----------------------------------------' END-IF DISPLAY 'Department: ' CURRENT-DEPT DISPLAY 'Employee Name Salary' DISPLAY '------------------- -------' MOVE 0 TO DEPT-TOTAL. FINAL-BREAK. IF PREVIOUS-DEPT NOT = SPACES DISPLAY 'Department Total: ' PREVIOUS-DEPT ' = ' DEPT-TOTAL DISPLAY '========================================' DISPLAY 'Grand Total: ' GRAND-TOTAL END-IF.
Process control breaks by printing subtotals, headers, and footers. Reset counters for the new group. Handle the final break to print the last group's totals and grand totals.
123456789101112131415WORKING-STORAGE SECTION. 01 PREVIOUS-REGION PIC X(10) VALUE SPACES. 01 PREVIOUS-DEPT PIC X(10) VALUE SPACES. 01 CURRENT-REGION PIC X(10). 01 CURRENT-DEPT PIC X(10). 01 REGION-TOTAL PIC 9(9)V99 VALUE 0. 01 DEPT-TOTAL PIC 9(9)V99 VALUE 0. 01 GRAND-TOTAL PIC 9(9)V99 VALUE 0. *> Check for breaks in hierarchical order IF CURRENT-REGION NOT = PREVIOUS-REGION PERFORM REGION-BREAK ELSE IF CURRENT-DEPT NOT = PREVIOUS-DEPT PERFORM DEPT-BREAK END-IF.
Implement multi-level control breaks for hierarchical reporting. Check breaks in order from highest to lowest level (region, then department). Process each level's subtotals and formatting.
123456789101112131415161718REGION-BREAK. IF PREVIOUS-REGION NOT = SPACES PERFORM DEPT-BREAK *> Process final dept break DISPLAY 'Region Total: ' PREVIOUS-REGION ' = ' REGION-TOTAL DISPLAY '========================================' END-IF DISPLAY 'REGION: ' CURRENT-REGION DISPLAY '========================================' MOVE 0 TO REGION-TOTAL. DEPT-BREAK. IF PREVIOUS-DEPT NOT = SPACES DISPLAY 'Department Total: ' PREVIOUS-DEPT ' = ' DEPT-TOTAL DISPLAY '----------------------------------------' END-IF DISPLAY 'Department: ' CURRENT-DEPT DISPLAY '----------------------------------------' MOVE 0 TO DEPT-TOTAL.
Create separate procedures for each control break level. Higher-level breaks should call lower-level breaks to ensure proper subtotal processing. Reset counters and print appropriate headers/footers.
12345678910INITIALIZE-CONTROL-BREAKS. MOVE SPACES TO PREVIOUS-REGION MOVE SPACES TO PREVIOUS-DEPT MOVE 0 TO REGION-TOTAL MOVE 0 TO DEPT-TOTAL MOVE 0 TO GRAND-TOTAL DISPLAY 'Sales Report by Region and Department' DISPLAY '=====================================' DISPLAY 'Region Department Employee Salary' DISPLAY '------ ---------- -------- ------'.
Initialize control break variables and print report headers before processing data. Set previous values to spaces and totals to zero. Print column headers for the report.
12345678910111213141516171819WORKING-STORAGE SECTION. 01 LINES-PER-PAGE PIC 9(3) VALUE 50. 01 LINE-COUNT PIC 9(3) VALUE 0. 01 PAGE-COUNT PIC 9(3) VALUE 0. DEPT-BREAK. ADD 3 TO LINE-COUNT *> Account for header lines IF LINE-COUNT > LINES-PER-PAGE PERFORM NEW-PAGE END-IF DISPLAY 'Department: ' CURRENT-DEPT DISPLAY 'Employee Name Salary' DISPLAY '------------------- -------'. NEW-PAGE. ADD 1 TO PAGE-COUNT DISPLAY 'Page ' PAGE-COUNT DISPLAY '========================================' MOVE 0 TO LINE-COUNT.
Combine control breaks with page control for professional reports. Track line counts and trigger page breaks when limits are exceeded. Print page numbers and maintain proper formatting.
123456789*> Validate data is sorted properly IF CURRENT-REGION < PREVIOUS-REGION DISPLAY 'Error: Data not sorted by region' PERFORM ERROR-HANDLING ELSE IF CURRENT-REGION = PREVIOUS-REGION AND CURRENT-DEPT < PREVIOUS-DEPT DISPLAY 'Error: Data not sorted by department within region' PERFORM ERROR-HANDLING END-IF.
Validate that input data is properly sorted for control break processing. Check that higher-level keys don't decrease and that lower-level keys are properly ordered within higher levels.