MainframeMaster

COBOL Tutorial

COBOL CYCLE Statement

The CYCLE statement in COBOL is used within the Report Writer feature to manually force control breaks in report processing, allowing precise control over when control footings and headings are generated.

Syntax

cobol
1
CYCLE control-identifier

Where control-identifier is the name of a control field defined in the CONTROL clause of the RD entry.

Basic Report Control Example

The CYCLE statement is primarily used in report processing to create manual control breaks:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
REPORT SECTION. RD SALES-REPORT CONTROL IS FINAL, REGION-CODE, SALESMAN-ID. 01 DETAIL-LINE TYPE IS DETAIL. 05 COLUMN 10 PIC X(20) SOURCE CUSTOMER-NAME. 05 COLUMN 35 PIC ZZ,ZZ9.99 SOURCE SALE-AMOUNT. 01 REGION-FOOTING TYPE IS CONTROL FOOTING REGION-CODE. 05 COLUMN 25 PIC X(15) VALUE "REGION TOTAL:". 05 COLUMN 42 PIC ZZ,ZZ9.99 SUM SALE-AMOUNT. PROCEDURE DIVISION. PROCESS-SALES. *> Force a control break for region CYCLE REGION-CODE. *> Generate detail line GENERATE DETAIL-LINE.

Practical Implementation

Regional Sales Report with Manual Breaks

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
51
52
53
54
55
56
57
58
59
60
61
62
DATA DIVISION. FILE SECTION. FD SALES-FILE. 01 SALES-RECORD. 05 REGION-CODE PIC X(3). 05 SALESMAN-ID PIC X(5). 05 CUSTOMER-NAME PIC X(30). 05 SALE-AMOUNT PIC 9(7)V99. WORKING-STORAGE SECTION. 01 WS-RECORD-COUNT PIC 9(5) VALUE ZERO. 01 WS-PAGE-BREAK-COUNT PIC 9(3) VALUE 20. REPORT SECTION. RD REGIONAL-SALES-REPORT CONTROL IS FINAL, REGION-CODE. 01 REPORT-HEADING TYPE IS REPORT HEADING. 05 LINE 1 COLUMN 25 PIC X(30) VALUE "REGIONAL SALES ANALYSIS". 01 DETAIL-LINE TYPE IS DETAIL. 05 LINE PLUS 1. 05 COLUMN 1 PIC X(3) SOURCE REGION-CODE. 05 COLUMN 15 PIC X(20) SOURCE CUSTOMER-NAME. 05 COLUMN 40 PIC ZZ,ZZ9.99 SOURCE SALE-AMOUNT. 01 REGION-FOOTING TYPE IS CONTROL FOOTING REGION-CODE. 05 LINE PLUS 2. 05 COLUMN 25 PIC X(20) VALUE "REGION TOTAL:". 05 COLUMN 50 PIC ZZ,ZZ9.99 SUM SALE-AMOUNT. PROCEDURE DIVISION. MAIN-PROCESSING. OPEN INPUT SALES-FILE OPEN OUTPUT REPORT-FILE INITIATE REGIONAL-SALES-REPORT PERFORM PROCESS-SALES-RECORDS TERMINATE REGIONAL-SALES-REPORT CLOSE SALES-FILE REPORT-FILE STOP RUN. PROCESS-SALES-RECORDS. READ SALES-FILE AT END MOVE 'Y' TO EOF-FLAG END-READ PERFORM UNTIL EOF-FLAG = 'Y' ADD 1 TO WS-RECORD-COUNT *> Force page break every 20 records IF FUNCTION MOD(WS-RECORD-COUNT, WS-PAGE-BREAK-COUNT) = 0 CYCLE REGION-CODE END-IF GENERATE DETAIL-LINE READ SALES-FILE AT END MOVE 'Y' TO EOF-FLAG END-READ END-PERFORM.

This example shows how CYCLE forces region subtotals every 20 records, creating regular page breaks for better report readability.

Financial Report with Period-End Processing

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
DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-PERIOD-END-DATE PIC 9(8). 01 WS-TRANSACTION-COUNT PIC 9(7) VALUE ZERO. REPORT SECTION. RD FINANCIAL-REPORT CONTROL IS FINAL, ACCOUNT-NUMBER. 01 TRANSACTION-DETAIL TYPE IS DETAIL. 05 LINE PLUS 1. 05 COLUMN 1 PIC 9(8) SOURCE ACCOUNT-NUMBER. 05 COLUMN 12 PIC 99/99/9999 SOURCE TRANSACTION-DATE. 05 COLUMN 25 PIC X(2) SOURCE TRANSACTION-TYPE. 05 COLUMN 30 PIC -(9)9,999.99 SOURCE AMOUNT. 01 ACCOUNT-FOOTING TYPE IS CONTROL FOOTING ACCOUNT-NUMBER. 05 LINE PLUS 2. 05 COLUMN 20 PIC X(20) VALUE "ACCOUNT BALANCE:". 05 COLUMN 45 PIC -(9)9,999.99 SUM AMOUNT. PROCEDURE DIVISION. PROCESS-TRANSACTIONS. PERFORM UNTIL EOF-FLAG = 'Y' ADD 1 TO WS-TRANSACTION-COUNT *> Check for period-end date boundary IF TRANSACTION-DATE > WS-PERIOD-END-DATE CYCLE ACCOUNT-NUMBER MOVE TRANSACTION-DATE TO WS-PERIOD-END-DATE END-IF *> Force account summary every 50 transactions IF FUNCTION MOD(WS-TRANSACTION-COUNT, 50) = 0 CYCLE ACCOUNT-NUMBER END-IF GENERATE TRANSACTION-DETAIL READ TRANSACTION-FILE AT END MOVE 'Y' TO EOF-FLAG END-READ END-PERFORM.

This example demonstrates CYCLE usage for both time-based (period-end) and volume-based (every 50 transactions) control breaks.

Advanced CYCLE Techniques

Hierarchical Control Levels

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
REPORT SECTION. RD HIERARCHICAL-REPORT CONTROL IS FINAL, DIVISION-CODE, DEPARTMENT-CODE, EMPLOYEE-ID. *> When CYCLE DIVISION-CODE is executed: *> 1. EMPLOYEE-ID footings are generated *> 2. DEPARTMENT-CODE footings are generated *> 3. DIVISION-CODE footings are generated *> 4. New DIVISION-CODE headings are generated *> 5. New DEPARTMENT-CODE headings are generated *> 6. New EMPLOYEE-ID headings are generated PROCEDURE DIVISION. PROCESS-HIERARCHY. *> This will cycle all levels from DIVISION down CYCLE DIVISION-CODE. *> This will cycle only DEPARTMENT and EMPLOYEE levels CYCLE DEPARTMENT-CODE. *> This will cycle only EMPLOYEE level CYCLE EMPLOYEE-ID.

CYCLE affects all control levels from the specified level down to the detail level, maintaining proper hierarchical report structure.

Conditional CYCLE Processing

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
WORKING-STORAGE SECTION. 01 WS-BUSINESS-RULES. 05 WS-MIN-GROUP-SIZE PIC 9(3) VALUE 5. 05 WS-CURRENT-GROUP-SIZE PIC 9(3) VALUE ZERO. 05 WS-THRESHOLD-AMOUNT PIC 9(7)V99 VALUE 10000.00. 05 WS-PAGE-LINE-COUNT PIC 9(3) VALUE ZERO. 05 WS-MAX-LINES-PER-PAGE PIC 9(3) VALUE 55. PROCEDURE DIVISION. CONDITIONAL-CYCLE-PROCESSING. PERFORM UNTIL EOF-FLAG = 'Y' *> Check page overflow condition IF WS-PAGE-LINE-COUNT > WS-MAX-LINES-PER-PAGE CYCLE DEPARTMENT-CODE MOVE ZERO TO WS-PAGE-LINE-COUNT END-IF *> Check business rule for minimum group size IF WS-CURRENT-GROUP-SIZE >= WS-MIN-GROUP-SIZE AND SALE-AMOUNT > WS-THRESHOLD-AMOUNT CYCLE SALESMAN-ID MOVE ZERO TO WS-CURRENT-GROUP-SIZE END-IF GENERATE DETAIL-LINE ADD 1 TO WS-CURRENT-GROUP-SIZE ADD 1 TO WS-PAGE-LINE-COUNT READ SALES-FILE AT END MOVE 'Y' TO EOF-FLAG END-READ END-PERFORM.

This shows CYCLE with complex business logic including page overflow management, minimum group sizes, and threshold-based processing.

Best Practices and Performance

Performance Guidelines

  • Use CYCLE sparingly to avoid excessive processing overhead
  • Implement cycle counting to prevent infinite loops
  • Consider the impact on report readability and user experience
  • Test CYCLE logic thoroughly with various data scenarios
  • Document CYCLE usage for maintenance purposes

Error Handling Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
WORKING-STORAGE SECTION. 01 WS-CYCLE-CONTROL. 05 WS-CYCLE-COUNT PIC 9(5) VALUE ZERO. 05 WS-MAX-CYCLES PIC 9(5) VALUE 1000. 05 WS-CYCLE-ERROR-FLAG PIC X VALUE 'N'. PROCEDURE DIVISION. SAFE-CYCLE-PROCESSING. *> Validate before cycling IF WS-CYCLE-COUNT < WS-MAX-CYCLES ADD 1 TO WS-CYCLE-COUNT CYCLE DEPARTMENT-CODE ELSE MOVE 'Y' TO WS-CYCLE-ERROR-FLAG DISPLAY "ERROR: Maximum cycles exceeded" PERFORM ERROR-RECOVERY END-IF. ERROR-RECOVERY. DISPLAY "CYCLE limit reached at record: " WS-RECORD-COUNT. TERMINATE CURRENT-REPORT. MOVE 8 TO RETURN-CODE.

Related Topics

  • Report Writer Feature
  • Control Break Processing
  • GENERATE Statement
  • INITIATE and TERMINATE Statements

Frequently Asked Questions

What is the primary purpose of the CYCLE statement?

The CYCLE statement manually forces control breaks in report processing, triggering the generation of control footings and headings at specific points, independent of actual data changes.

How does CYCLE affect multiple control levels?

When CYCLE is executed for a specific control level, it affects all control levels from that level down to the detail level, generating footings from lowest to highest, then headings from highest to lowest.

Can CYCLE be used outside Report Writer?

No, CYCLE is specifically designed for COBOL's Report Writer feature and requires a properly defined Report Section with control hierarchies.