Teach Yourself COBOL in 21 days, Second Edition

Previous chapterNext chapterContents


- Bonus Day 1 -
Control Breaks

Control breaks, covered briefly on Day 21, "Selecting, Sorting, and Reporting," are an important part of reports. On this first bonus day, you learn how to use them more effectively. You also learn about the following topics:

Control breaks are important in reports and are used extensively for totaling and subtotaling. Recall that a control break is a break inserted into the normal processing of a program (usually a report program) to cause groups of records to be processed together as one unit. The interruption of the normal printing of a report program to print a total or subtotal is a control break or level break. In the example shown in Figure B1.1, the report breaks at the end of each vendor and prints a subtotal for that vendor, and then breaks at the end of the report and prints a total for the report.

Figure B1.1.
Control breaks for printing subtotals and a report total.

Using the definition of a control break, the subtotals for ABC Printing, Phone Co, and Moon Mountain Inc. are generated by treating all records with the same vendor as a unit. The report total is generated by treating all records in the file as a unit.

Control Break Variables

The actual records in the file might look something like the ones in Figure B1.2. The fields (name, date, and amount) have some space inserted between them so that you can see them more easily. The file has been sorted in vendor name order.

Figure B1.2.
The records used in Figure B1.1.

If you compare Figure B1.1 to the records in Figure B1.2, you will see immediately that in addition to the values in the record, you need variables to hold the subtotals for each vendor and the grand total for the report. The obvious choice would be totals for all needed values, as shown in Listing B1.1.

TYPE: Listing B1.1. The total for control breaks.

000500 77  ABC-TOTAL             PIC S9(6)V99.
000600 77  PHONE-TOTAL           PIC S9(6)V99.
000700 77  MOON-TOTAL            PIC S9(6)V99.
000800 77  GRAND-TOTAL           PIC S9(6)V99.

Unfortunately, when you're processing a file, you have no idea what values, which vendors, or how many vendors are in the file. You cannot create a separate variable to hold a subtotal for each vendor.

You need one variable that is filled and emptied over and over for each vendor, and one that fills just for the whole report, as shown in Listing B1.2.

TYPE: Listing B1.2. Just two variables for the control breaks.

000700 77  VENDOR-TOTAL          PIC S9(6)V99.
000800 77  GRAND-TOTAL           PIC S9(6)V99.

ANALYSIS: The VENDOR-TOTAL is set to zero at the start of each new vendor. As records are processed, the amount in the record is added to VENDOR-TOTAL. After the last record with that vendor name is processed, a line is formatted and the VENDOR-TOTAL is printed.

The Mechanics of a Control Break

Table B1.1 illustrates what is happening in a control break. The left column shows the record as it is read from the file. These are numbered in the figure for reference. The right column shows the steps being taken. The steps also are numbered for reference. The steps are only those connected with the control break, and they do not include the actions necessary to print each line of the report. Imagine the actions on the right being taken in response to each record read on the left.

Table B1.1. An idealized model of control breaking.

Record Action
1. MOVE ZERO TO GRAND-TOTAL
2. MOVE ZERO TO VENDOR-TOTAL
1. ABC Printing 19940123 00027.95 3. ADD 27.95 TO VENDOR-TOTAL
2. ABC Printing 19940131 00015.54 4. ADD 15.54 TO VENDOR-TOTAL
3. ABC Printing 19940216 00010.17 5. ADD 10.17 TO VENDOR-TOTAL
6. PRINT VENDOR-TOTAL
7. ADD VENDOR-TOTAL TO GRAND-TOTAL
8. MOVE ZERO TO VENDOR-TOTAL
4. Phone Co 19940117 00034.97 9. ADD 34.97 TO VENDOR-TOTAL
5. Phone Co 19940124 00017.54 10. ADD 17.54 TO VENDOR-TOTAL
6. Phone Co 19940131 00027.15 11. ADD 27.15 TO VENDOR-TOTAL
12. PRINT VENDOR-TOTAL
13. ADD VENDOR-TOTAL TO GRAND-TOTAL
14. MOVE ZERO TO VENDOR-TOTAL
7. Moon Mountain Inc. 19940106 00039.95 15. ADD 39.95 TO VENDOR-TOTAL
8. Moon Mountain Inc. 19940116 00047.55 16. ADD 47.55 TO VENDOR-TOTAL
17. PRINT VENDOR-TOTAL
18. ADD VENDOR-TOTAL TO GRAND-TOTAL
19. PRINT GRAND-TOTAL

This is an idealized model of control breaking. If you look at steps 6, 7, and 8 in the right column, you see that after the last ABC Printing record is read, the total for ABC Printing is printed and then added to the grand total for the report. These steps are sensible enough for a human being. You can scan up and down through the records and quickly establish the breaking points; but how would the computer know that ABC Printing was finished and that a new vendor was about to begin, unless it had already read the next record in the file? This makes the programming of control breaks somewhat tricky. It is necessary to read the file past the point that you want, and then execute the control break logic.

Table B1.2 shows a truer picture of what happens in a programmed control break.

Table B1.2. A truer picture of a programmed control break.

Record Action
1. ABC Printing 19940123 00027.95 1. MOVE ZERO TO GRAND-TOTAL
2. MOVE ZERO TO VENDOR-TOTAL
3. ADD 27.95 TO VENDOR-TOTAL
2. ABC Printing 19940131 00015.54 4. ADD 15.54 TO VENDOR-TOTAL
3. ABC Printing 19940216 00010.17 5. ADD 10.17 TO VENDOR-TOTAL
4. Phone Co 19940117 00034.97 6. PRINT VENDOR-TOTAL
7. ADD VENDOR-TOTAL TO GRAND-TOTAL
8. MOVE ZERO TO VENDOR-TOTAL
9. ADD 34.97 TO VENDOR-TOTAL
5. Phone Co 19940124 00017.54 10. ADD 17.54 TO VENDOR-TOTAL
6. Phone Co 19940131 00027.15 11. ADD 27.15 TO VENDOR-TOTAL
7. Moon Mountain Inc. 19940106 00039.95 12. PRINT VENDOR-TOTAL
13. ADD VENDOR-TOTAL TO GRAND-TOTAL
14. MOVE ZERO TO VENDOR-TOTAL
15. ADD 39.95 TO VENDOR-TOTAL
8. Moon Mountain Inc. 19940116 00047.55 16. ADD 47.55 TO VENDOR-TOTAL
9. END OF FILE 17. PRINT VENDOR-TOTAL
18. ADD VENDOR-TOTAL TO GRAND-TOTAL
19. PRINT GRAND-TOTAL

ANALYSIS: In the left column, the first record is read from the file. This triggers the start of a report, and step 1 moves zero to the GRAND-TOTAL. This first record also triggers the beginning of a vendor, and step 2 moves zeroes to the VENDOR-TOTAL.

Step 3 is the action taken based on the actual record. The value in the record is added to the VENDOR-TOTAL. Record 2 is read, causing step 4 to be taken. Record 3 is read, causing step 5 to be taken. When record 4 is read, the vendor name changes. The change of name signals the end of a vendor. Steps 6 and 7 print the VENDOR-TOTAL and add it to the GRAND-TOTAL. Record 4 also signals the beginning of a new vendor, and step 8 sets the VENDOR-TOTAL back to zero for the beginning of this new vendor.

Step 9 adds the value in the record to VENDOR-TOTAL, and the values read from records 5 and 6 also are added in steps 10 and 11. When record 7 is read, the vendor name changes again. This signals an end of a vendor, and steps 12 and 13 print the VENDOR-TOTAL and add it to the GRAND-TOTAL. Record 7 also signals a new vendor, and step 14 zeroes the VENDOR-TOTAL again. Steps 15 and 16 add the values for records 7 and 8.

The last read on the file (labeled record 9) does not retrieve a record but creates an end-of-file condition. This condition triggers the end of a vendor, and steps 17 and 18 print the VENDOR-TOTAL and add it to the GRAND-TOTAL. The end-of-file condition also triggers the end of the report and, finally, step 19 prints the GRAND-TOTAL.

Control Break Levels

Control breaks are usually thought of in terms of levels. In the example shown in Table B1.2, the senior, or highest, level is the level that includes all records in the file. The next level below that is the level that includes all records with the same vendor.

The senior level control break can be called the level-1 break. The vendor break would then be called the level-2 break. Any file processing can have more than two level breaks, but this example works with only two. There are several key parts to a control break.

New Term: The control break field or control field is the field in the record that causes a control break to occur when it changes. In Table B1.2, the vendor name is a control break field.

The control break field is the field on which the file is sorted. One special type of control break field is used at level 1. Level 1 is usually at the level of the complete file, or all records. The break on level 1 is not a field, but an end-of-file condition. The control break field for a level-1 break can be thought of as the whole file, and the condition that determines the break is that of no more records to process (end of file).

New Term: The control break current value or control current value is a field created in WORKING-STORAGE that holds a copy of the control break field. The control break current value is sometimes called the control break holding area or control holding area.

The control break current value is filled in at the beginning of a control break level with the value in the control break field. As the processing continues, the control break field is compared to the control break current value to determine whether a control break has occurred. In Table B1.2, a control break current value field was created in WORKING-STORAGE that is filled in with the vendor name from the record. When reading a record creates the condition that the control break field does not match the control break current value, the logic for that control break is executed.

New Term: Control break accumulators or control accumulators are any variables used for summing or counting values within a control break. In Table B1.2, there are two accumulators: a grand total accumulator, and a vendor accumulator.

Control Break Logic

The mechanics of a control break make it seem difficult, but the logic of a control break is quite easy to express. Listing B1.3 is a general statement of the logic of a control break. The example is for a level-2 control break. I have shown the pseudocode for a level-2 break because the level-1 break (all records) behaves slightly differently.

TYPE: Listing B1.3. Pseudocode for a control break.

process-level-2-control-break
    perform start-level-2-control-break
    perform process-level-3-control-break
        until file at end
           or level-2-control-field not = level-2-current-value
    perform end-level-2
start-level-2
    move level-2-control-field to level-2-current-value.
    move zeroes to level-2 accumulators.
    any other starting actions
end-level-2
    perform process-level-2-accumulators
    perform add-level-2 accumulators to level-1 accumulators
    any other ending actions

ANALYSIS: A control break starts by saving the control break field in the control break current value and zeroing the accumulators for that control level.

The body of the break performs the next lower-level control break until the file is at the end or the control break field no longer matches the control break value field.

The control break ends by processing the level accumulators. For a report program, this involves printing the subtotals. Finally, it adds the accumulators for this level to the next higher level.

Listing B1.4 is the pseudocode for a level-1 (all records) control break.

TYPE: Listing B1.4. A level-1 control break.

process-level-1-control-break
    perform start-level-1
    perform process-level-2-control-break
        until file-at-end
    perform end-level-1
start-level-1
    read first valid record
    move zeroes to level-1-accumulators.
    any other starting actions
end-level-1
    perform process-level-1-accumulators
    any other ending actions

ANALYSIS: A level-1 break varies from any other break because there is no true control break current value; the start-level-1 logic starts by executing a read first valid record.

The body of the level-1 break performs level 2 until the file is at end. The end of a level-1 break does not add accumulators to the next higher level because there is no next higher level.

Using Control Breaks for Totals

A good way to get a feel for control breaks is to see them in action. Figure B1.3 is a printer spacing chart for a Bills by Vendor report. This report produces a level-1 break for the complete file and a level-2 break for each vendor.

Figure B1.3.
A printer layout chart for
blbyvn01.cbl.

Listing B1.5 is blbyvn01.cbl, the report program. It sorts on the vendor number, prints subtotals for each vendor, and prints a grand total at the end of the report.

TYPE: Listing B1.5. More control breaks.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. BLBYVN01.
000300*--------------------------------
000400* Bills Report by vendor
000500*--------------------------------
000600 ENVIRONMENT DIVISION.
000700 INPUT-OUTPUT SECTION.
000800 FILE-CONTROL.
000900
001000     COPY "SLVOUCH.CBL".
001100
001200     COPY "SLVND02.CBL".
001300
001400     COPY "SLSTATE.CBL".
001500
001600     SELECT WORK-FILE
001700         ASSIGN TO "WORK"
001800         ORGANIZATION IS SEQUENTIAL.
001900
002000     SELECT SORT-FILE
002100         ASSIGN TO "SORT".
002200
002300     SELECT PRINTER-FILE
002400         ASSIGN TO PRINTER
002500         ORGANIZATION IS LINE SEQUENTIAL.
002600
002700 DATA DIVISION.
002800 FILE SECTION.
002900
003000     COPY "FDVOUCH.CBL".
003100
003200     COPY "FDVND04.CBL".
003300
003400     COPY "FDSTATE.CBL".
003500
003600 FD  WORK-FILE
003700     LABEL RECORDS ARE STANDARD.
003800 01  WORK-RECORD.
003900     05  WORK-NUMBER           PIC 9(5).
004000     05  WORK-VENDOR           PIC 9(5).
004100     05  WORK-INVOICE          PIC X(15).
004200     05  WORK-FOR              PIC X(30).
004300     05  WORK-AMOUNT           PIC S9(6)V99.
004400     05  WORK-DATE             PIC 9(8).
004500     05  WORK-DUE              PIC 9(8).
004600     05  WORK-DEDUCTIBLE       PIC X.
004700     05  WORK-SELECTED         PIC X.
004800     05  WORK-PAID-AMOUNT      PIC S9(6)V99.
004900     05  WORK-PAID-DATE        PIC 9(8).
005000     05  WORK-CHECK-NO         PIC 9(6).
005100
005200 SD  SORT-FILE.
005300
005400 01  SORT-RECORD.
005500     05  SORT-NUMBER           PIC 9(5).
005600     05  SORT-VENDOR           PIC 9(5).
005700     05  SORT-INVOICE          PIC X(15).
005800     05  SORT-FOR              PIC X(30).
005900     05  SORT-AMOUNT           PIC S9(6)V99.
006000     05  SORT-DATE             PIC 9(8).
006100     05  SORT-DUE              PIC 9(8).
006200     05  SORT-DEDUCTIBLE       PIC X.
006300     05  SORT-SELECTED         PIC X.
006400     05  SORT-PAID-AMOUNT      PIC S9(6)V99.
006500     05  SORT-PAID-DATE        PIC 9(8).
006600     05  SORT-CHECK-NO         PIC 9(6).
006700
006800 FD  PRINTER-FILE
006900     LABEL RECORDS ARE OMITTED.
007000 01  PRINTER-RECORD             PIC X(80).
007100
007200 WORKING-STORAGE SECTION.
007300
007400 77  OK-TO-PROCESS         PIC X.
007500
007600     COPY "WSCASE01.CBL".
007700
007800 01  DETAIL-LINE.
007900     05  PRINT-NAME        PIC X(30).
008000     05  FILLER            PIC X(1) VALUE SPACE.
008100     05  PRINT-NUMBER      PIC ZZZZ9.
008200     05  FILLER            PIC X(3) VALUE SPACE.
008300     05  PRINT-DUE-DATE    PIC Z9/99/9999.
008400     05  FILLER            PIC X(1) VALUE SPACE.
008500     05  PRINT-AMOUNT      PIC ZZZ,ZZ9.99.
008600     05  FILLER            PIC X(1) VALUE SPACE.
008700     05  PRINT-INVOICE     PIC X(15).
008800
008900 01  VENDOR-TOTAL-LITERAL.
009000     05  FILLER            PIC X(18) VALUE SPACE.
009100     05  FILLER            PIC X(12) VALUE "VENDOR TOTAL".
009200
009300 01  GRAND-TOTAL-LITERAL.
009400     05  FILLER            PIC X(25) VALUE SPACE.
009500     05  FILLER            PIC X(5) VALUE "TOTAL".
009600
009700 01  COLUMN-LINE.
009800     05  FILLER         PIC X(6) VALUE "VENDOR".
009900     05  FILLER         PIC X(23) VALUE SPACE.
010000     05  FILLER         PIC X(7)  VALUE "VOUCHER".
010100     05  FILLER         PIC X(5)  VALUE SPACE.
010200     05  FILLER         PIC X(8)  VALUE "DUE DATE".
010300     05  FILLER         PIC X(1)  VALUE SPACE.
010400     05  FILLER         PIC X(10) VALUE "AMOUNT DUE".
010500     05  FILLER         PIC X(1)  VALUE SPACE.
010600     05  FILLER         PIC X(7)  VALUE "INVOICE".
010700
010800 01  TITLE-LINE.
010900     05  FILLER              PIC X(25) VALUE SPACE.
011000     05  FILLER              PIC X(22)
011100         VALUE "BILLS REPORT BY VENDOR".
011200     05  FILLER              PIC X(11) VALUE SPACE.
011300     05  FILLER              PIC X(5) VALUE "PAGE:".
011400     05  FILLER              PIC X(1) VALUE SPACE.
011500     05  PRINT-PAGE-NUMBER   PIC ZZZ9.
011600
011700 77  WORK-FILE-AT-END     PIC X.
011800 77  VENDOR-RECORD-FOUND     PIC X.
011900
012000 77  LINE-COUNT              PIC 999 VALUE ZERO.
012100 77  PAGE-NUMBER             PIC 9999 VALUE ZERO.
012200 77  MAXIMUM-LINES           PIC 999 VALUE 55.
012300
012400 77  RECORD-COUNT            PIC 9999 VALUE ZEROES.
012500
012600* Control break current value for vendor
012700 77  CURRENT-VENDOR          PIC 9(5).
012800
012900* Control break accumulators
013000* GRAND TOTAL is the level 1 accumulator for the whole file
013100* VENDOR TOTAL is the level 2 accumulator
013200 77  GRAND-TOTAL            PIC S9(6)V99.
013300 77  VENDOR-TOTAL           PIC S9(6)V99.
013400
013500     COPY "WSDATE01.CBL".
013600
013700 PROCEDURE DIVISION.
013800 PROGRAM-BEGIN.
013900
014000     PERFORM OPENING-PROCEDURE.
014100     PERFORM MAIN-PROCESS.
014200     PERFORM CLOSING-PROCEDURE.
014300
014400 PROGRAM-EXIT.
014500     EXIT PROGRAM.
014600
014700 PROGRAM-DONE.
014800     STOP RUN.
014900
015000 OPENING-PROCEDURE.
015100     OPEN I-O VENDOR-FILE.
015200
015300     OPEN OUTPUT PRINTER-FILE.
015400
015500 MAIN-PROCESS.
015600     PERFORM GET-OK-TO-PROCESS.
015700     PERFORM PROCESS-THE-FILE
015800         UNTIL OK-TO-PROCESS = "N".
015900
016000 CLOSING-PROCEDURE.
016100     CLOSE VENDOR-FILE.
016200     CLOSE PRINTER-FILE.
016300
016400 GET-OK-TO-PROCESS.
016500     PERFORM ACCEPT-OK-TO-PROCESS.
016600     PERFORM RE-ACCEPT-OK-TO-PROCESS
016700         UNTIL OK-TO-PROCESS = "Y" OR "N".
016800
016900 ACCEPT-OK-TO-PROCESS.
017000     DISPLAY "PRINT BILLS BY VENDOR (Y/N)?".
017100     ACCEPT OK-TO-PROCESS.
017200     INSPECT OK-TO-PROCESS
017300       CONVERTING LOWER-ALPHA
017400       TO         UPPER-ALPHA.
017500
017600 RE-ACCEPT-OK-TO-PROCESS.
017700     DISPLAY "YOU MUST ENTER YES OR NO".
017800     PERFORM ACCEPT-OK-TO-PROCESS.
017900
018000 PROCESS-THE-FILE.
018100     PERFORM START-THE-FILE.
018200     PERFORM PRINT-ONE-REPORT.
018300     PERFORM END-THE-FILE.
018400
018500*    PERFORM GET-OK-TO-PROCESS.
018600     MOVE "N" TO OK-TO-PROCESS.
018700
018800 START-THE-FILE.
018900     PERFORM SORT-DATA-FILE.
019000     OPEN INPUT WORK-FILE.
019100
019200 END-THE-FILE.
019300     CLOSE WORK-FILE.
019400
019500 SORT-DATA-FILE.
019600     SORT SORT-FILE
019700         ON ASCENDING KEY SORT-VENDOR
019800          USING VOUCHER-FILE
019900          GIVING WORK-FILE.
020000
020100* LEVEL 1 CONTROL BREAK
020200 PRINT-ONE-REPORT.
020300     PERFORM START-ONE-REPORT.
020400     PERFORM PROCESS-ALL-VENDORS
020500         UNTIL WORK-FILE-AT-END = "Y".
020600     PERFORM END-ONE-REPORT.
020700
020800 START-ONE-REPORT.
020900     PERFORM READ-FIRST-VALID-WORK.
021000     MOVE ZEROES TO GRAND-TOTAL.
021100
021200     PERFORM START-NEW-REPORT.
021300
021400 START-NEW-REPORT.
021500     MOVE SPACE TO DETAIL-LINE.
021600     MOVE ZEROES TO LINE-COUNT PAGE-NUMBER.
021700     PERFORM START-NEW-PAGE.
021800
021900 END-ONE-REPORT.
022000     IF RECORD-COUNT = ZEROES
022100         MOVE "NO RECORDS FOUND" TO PRINTER-RECORD
022200         PERFORM WRITE-TO-PRINTER
022300     ELSE
022400         PERFORM PRINT-GRAND-TOTAL.
022500
022600     PERFORM END-LAST-PAGE.
022700
022800 PRINT-GRAND-TOTAL.
022900     MOVE GRAND-TOTAL TO PRINT-AMOUNT.
023000     MOVE GRAND-TOTAL-LITERAL TO PRINT-NAME.
023100     MOVE DETAIL-LINE TO PRINTER-RECORD.
023200     PERFORM WRITE-TO-PRINTER.
023300     PERFORM LINE-FEED 2 TIMES.
023400     MOVE SPACE TO DETAIL-LINE.
023500
023600* LEVEL 2 CONTROL BREAK
023700 PROCESS-ALL-VENDORS.
023800     PERFORM START-ONE-VENDOR.
023900
024000     PERFORM PROCESS-ALL-VOUCHERS
024100         UNTIL WORK-FILE-AT-END = "Y"
024200            OR WORK-VENDOR NOT = CURRENT-VENDOR.
024300
024400     PERFORM END-ONE-VENDOR.
024500
024600 START-ONE-VENDOR.
024700     MOVE WORK-VENDOR TO CURRENT-VENDOR.
024800     MOVE ZEROES TO VENDOR-TOTAL.
024900
025000 END-ONE-VENDOR.
025100     PERFORM PRINT-VENDOR-TOTAL.
025200     ADD VENDOR-TOTAL TO GRAND-TOTAL.
025300
025400 PRINT-VENDOR-TOTAL.
025500     MOVE VENDOR-TOTAL TO PRINT-AMOUNT.
025600     MOVE VENDOR-TOTAL-LITERAL TO PRINT-NAME.
025700     MOVE DETAIL-LINE TO PRINTER-RECORD.
025800     PERFORM WRITE-TO-PRINTER.
025900     PERFORM LINE-FEED.
026000     MOVE SPACE TO DETAIL-LINE.
026100
026200* PROCESS ONE RECORD LEVEL
026300 PROCESS-ALL-VOUCHERS.
026400     PERFORM PROCESS-THIS-VOUCHER.
026500     ADD WORK-AMOUNT TO VENDOR-TOTAL.
026600     ADD 1 TO RECORD-COUNT.
026700     PERFORM READ-NEXT-VALID-WORK.
026800
026900 PROCESS-THIS-VOUCHER.
027000     IF LINE-COUNT > MAXIMUM-LINES
027100         PERFORM START-NEXT-PAGE.
027200     PERFORM PRINT-THE-RECORD.
027300
027400 PRINT-THE-RECORD.
027500     MOVE WORK-NUMBER TO PRINT-NUMBER.
027600
027700     PERFORM LOAD-VENDOR-NAME.
027800
027900     MOVE WORK-DUE TO DATE-CCYYMMDD.
028000     PERFORM CONVERT-TO-MMDDCCYY.
028100     MOVE DATE-MMDDCCYY TO PRINT-DUE-DATE.
028200
028300     MOVE WORK-AMOUNT TO PRINT-AMOUNT.
028400     MOVE WORK-INVOICE TO PRINT-INVOICE.
028500
028600     MOVE DETAIL-LINE TO PRINTER-RECORD.
028700     PERFORM WRITE-TO-PRINTER.
028800     MOVE SPACE TO DETAIL-LINE.
028900
029000 LOAD-VENDOR-NAME.
029100     MOVE WORK-VENDOR TO VENDOR-NUMBER.
029200     PERFORM READ-VENDOR-RECORD.
029300     IF VENDOR-RECORD-FOUND = "Y"
029400         MOVE VENDOR-NAME TO PRINT-NAME
029500     ELSE
029600         MOVE "*VENDOR NOT ON FILE*" TO PRINT-NAME.
029700
029800* PRINTING ROUTINES
029900 WRITE-TO-PRINTER.
030000     WRITE PRINTER-RECORD BEFORE ADVANCING 1.
030100     ADD 1 TO LINE-COUNT.
030200
030300 LINE-FEED.
030400     MOVE SPACE TO PRINTER-RECORD.
030500     PERFORM WRITE-TO-PRINTER.
030600
030700 START-NEXT-PAGE.
030800     PERFORM END-LAST-PAGE.
030900     PERFORM START-NEW-PAGE.
031000
031100 START-NEW-PAGE.
031200     ADD 1 TO PAGE-NUMBER.
031300     MOVE PAGE-NUMBER TO PRINT-PAGE-NUMBER.
031400     MOVE TITLE-LINE TO PRINTER-RECORD.
031500     PERFORM WRITE-TO-PRINTER.
031600     PERFORM LINE-FEED.
031700     MOVE COLUMN-LINE TO PRINTER-RECORD.
031800     PERFORM WRITE-TO-PRINTER.
031900     PERFORM LINE-FEED.
032000
032100 END-LAST-PAGE.
032200     PERFORM FORM-FEED.
032300     MOVE ZERO TO LINE-COUNT.
032400
032500 FORM-FEED.
032600     MOVE SPACE TO PRINTER-RECORD.
032700     WRITE PRINTER-RECORD BEFORE ADVANCING PAGE.
032800
032900*--------------------------------
033000* Read first, read next routines
033100*--------------------------------
033200 READ-FIRST-VALID-WORK.
033300     PERFORM READ-NEXT-VALID-WORK.
033400
033500 READ-NEXT-VALID-WORK.
033600     PERFORM READ-NEXT-WORK-RECORD.
033700     PERFORM READ-NEXT-WORK-RECORD
033800         UNTIL WORK-FILE-AT-END = "Y"
033900            OR WORK-PAID-DATE = ZEROES.
034000
034100 READ-NEXT-WORK-RECORD.
034200     MOVE "N" TO WORK-FILE-AT-END.
034300     READ WORK-FILE NEXT RECORD
034400         AT END MOVE "Y" TO WORK-FILE-AT-END.
034500
034600*--------------------------------
034700* Other File IO routines
034800*--------------------------------
034900 READ-VENDOR-RECORD.
035000     MOVE "Y" TO VENDOR-RECORD-FOUND.
035100     READ VENDOR-FILE RECORD
035200         INVALID KEY
035300         MOVE "N" TO VENDOR-RECORD-FOUND.
035400
035500*--------------------------------
035600* Utility Routines
035700*--------------------------------
035800     COPY "PLDATE01.CBL".
035900

The output of the Bills by Vendor report provides subtotals for each vendor and a grand total at the end of the report:

OUTPUT:

                         BILLS REPORT BY VENDOR           PAGE:    1
VENDOR                       VOUCHER     DUE DATE AMOUNT DUE INVOICE
AERIAL SIGNS                      14    1/17/1994   1,046.97 FA1234
VENDOR TOTAL                      1,046.97
ABC PRINTING                       4    2/07/1994     104.19 CX-5055
ABC PRINTING                       7    2/22/1994      48.97 CX-1407
ABC PRINTING                       8    1/27/1994      48.97 CX-1566
VENDOR TOTAL                        202.13
CHARLES SMITH AND SONS             3    2/22/1994      27.76 5057
CHARLES SMITH AND SONS            16    1/16/1994      25.97 5098
VENDOR TOTAL                         53.73
MA BELL                           13    1/23/1994      94.96 50577
MA BELL                           19    1/23/1994      34.95 50577
VENDOR TOTAL                        129.91
RANIER GRAPHICS                   20    2/25/1994   2,057.07 ZO-1515
VENDOR TOTAL                      2,057.07
ABERCROMBIE AND OTHERS            15    1/31/1994     657.19 MONTHLY
VENDOR TOTAL                        657.19
TOTAL                      4,147.00

ANALYSIS: The program has two control level breaks: level 1 at file level (all records) and level 2 at vendor-number level.

The control break field for level 1 is the entire WORK-RECORD. When there are no more work records, the level 1 break is completed. The control break current value for this level is really the WORK-FILE-AT-END flag defined at line 011700.

The control break field for level 2 is WORK-VENDOR, defined in the work file at line 004000. The control break current value for the vendor level is defined at line 012700, a CURRENT-VENDOR that will hold the value of the vendor that is currently undergoing processing.

The control break accumulators are GRAND-TOTAL and VENDOR-TOTAL, defined at lines 013200 and 013300, respectively. The RECORD-COUNT defined at line 012400 also is used as a control break accumulator because it counts all the records processed by the report portion of the program.

The program starts by asking the user whether to proceed with the report. This logic is handled in MAIN-PROCESS at line 015500 by performing GET-OK-TO-PROCESS. This routine at line 016400 requires that the user enter yes or no and place "Y" or "N" in OK-TO-PROCESS. MAIN-PROCESS then performs the main loop, PROCESS-THE-FILE, until OK-TO-PROCESS = "N".

When the user has agreed to print the report, PROCESS-THE-FILE at line 018000 starts by performing START-THE-FILE. This routine at line 018800 sorts the voucher file on the vendor number into a work file and opens the work file ready for processing. The actual sort routine is at line 019500. PROCESS-THE-FILE continues by printing the report and then performing END-THE-FILE, which closes the work file. The last action of PROCESS-THE-FILE is to decide whether to process again. The code includes two solutions at lines 018500 and 018600. One possibility at line 018500 is to ask the user whether to print the report again. This option is commented out. The second option at line 018600 moves "N" to OK-TO-PROCESS. Either one of these will resolve the main loop condition that will PROCESS-THE-FILE UNTIL OK-TO-PROCESS = "N". The first enables the user to decide, and the second forces no further processing.

The sort step is important because the file must be in vendor number order for a control break to work correctly on the vendor number.

The level-1 (all records) control break, PRINT-ONE-REPORT, and related routines are at lines 020100 through 023400. The logic follows a pattern similar to the pseudocode in Listing B1.4 for a level-1 control break. The additional start level actions in START-NEW-REPORT at line 021400 include setting up a report ready to be printed.

END-ONE-REPORT at line 021900 prints either a grand total or a "NO RECORDS FOUND" message and then ends the report by performing END-LAST-PAGE to issue a final form feed to the printer.

The level-2 control logic, PROCESS-ALL-VENDORS, and related routines are found at lines 023600 through 026100. This logic follows Listing B1.3, pseudocode for standard level break.

The level that processes single records, PROCESS-ALL-VOUCHERS at line 026300, performs a routine to PROCESS-THIS-VOUCHER. When this is done, the WORK-AMOUNT is added to the VENDOR-TOTAL, and the RECORD-COUNT is increased by 1. The last action of PROCESS-ALL-VOUCHERS is READ-NEXT-VALID-WORK.

The printing-level routine, PROCESS-THIS-VOUCHER, performs fairly routine actions to print a single record. One routine worth noting at line 029000 is LOAD-VENDOR-NAME, which is used to look up the WORK-VENDOR in the VENDOR-FILE and print the vendor name instead of the vendor number.

Using Control Breaks for Formatting

In blbyvn01.cbl, the control breaking logic was used to create additional lines to print with vendor subtotals and grand totals. Control breaking also is frequently used to eliminate the repetition of a control field on a report. Figure B1.4 is a printer-spacing chart for a modified version of blbyvn01.cbl.

Figure B1.4.
A printer layout chart for blbyvn02.cbl.

In this version, the vendor name is printed on only the first line of a group of records with the same vendor. This prevents the vendor name from repeating on each line.

Listing B1.6, blbyvn02.cbl, implements this change by removing the vendor name from the detail line printing and moving it up to become part of START-ONE-VENDOR.

TYPE: Listing B1.6. Another control break problem.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. BLBYVN02.
000300*--------------------------------
000400* Bills Report by vendor
000500*--------------------------------
000600 ENVIRONMENT DIVISION.
000700 INPUT-OUTPUT SECTION.
000800 FILE-CONTROL.
000900
001000     COPY "SLVOUCH.CBL".
001100
001200     COPY "SLVND02.CBL".
001300
001400     COPY "SLSTATE.CBL".
001500
001600     SELECT WORK-FILE
001700         ASSIGN TO "WORK"
001800         ORGANIZATION IS SEQUENTIAL.
001900
002000     SELECT SORT-FILE
002100         ASSIGN TO "SORT".
002200
002300     SELECT PRINTER-FILE
002400         ASSIGN TO PRINTER
002500         ORGANIZATION IS LINE SEQUENTIAL.
002600
002700 DATA DIVISION.
002800 FILE SECTION.
002900
003000     COPY "FDVOUCH.CBL".
003100
003200     COPY "FDVND04.CBL".
003300
003400     COPY "FDSTATE.CBL".
003500
003600 FD  WORK-FILE
003700     LABEL RECORDS ARE STANDARD.
003800 01  WORK-RECORD.
003900     05  WORK-NUMBER           PIC 9(5).
004000     05  WORK-VENDOR           PIC 9(5).
004100     05  WORK-INVOICE          PIC X(15).
004200     05  WORK-FOR              PIC X(30).
004300     05  WORK-AMOUNT           PIC S9(6)V99.
004400     05  WORK-DATE             PIC 9(8).
004500     05  WORK-DUE              PIC 9(8).
004600     05  WORK-DEDUCTIBLE       PIC X.
004700     05  WORK-SELECTED         PIC X.
004800     05  WORK-PAID-AMOUNT      PIC S9(6)V99.
004900     05  WORK-PAID-DATE        PIC 9(8).
005000     05  WORK-CHECK-NO         PIC 9(6).
005100
005200 SD  SORT-FILE.
005300
005400 01  SORT-RECORD.
005500     05  SORT-NUMBER           PIC 9(5).
005600     05  SORT-VENDOR           PIC 9(5).
005700     05  SORT-INVOICE          PIC X(15).
005800     05  SORT-FOR              PIC X(30).
005900     05  SORT-AMOUNT           PIC S9(6)V99.
006000     05  SORT-DATE             PIC 9(8).
006100     05  SORT-DUE              PIC 9(8).
006200     05  SORT-DEDUCTIBLE       PIC X.
006300     05  SORT-SELECTED         PIC X.
006400     05  SORT-PAID-AMOUNT      PIC S9(6)V99.
006500     05  SORT-PAID-DATE        PIC 9(8).
006600     05  SORT-CHECK-NO         PIC 9(6).
006700
006800 FD  PRINTER-FILE
006900     LABEL RECORDS ARE OMITTED.
007000 01  PRINTER-RECORD             PIC X(80).
007100
007200 WORKING-STORAGE SECTION.
007300
007400 77  OK-TO-PROCESS         PIC X.
007500
007600     COPY "WSCASE01.CBL".
007700
007800 01  DETAIL-LINE.
007900     05  PRINT-NAME        PIC X(30).
008000     05  FILLER            PIC X(1) VALUE SPACE.
008100     05  PRINT-NUMBER      PIC ZZZZ9.
008200     05  FILLER            PIC X(3) VALUE SPACE.
008300     05  PRINT-DUE-DATE    PIC Z9/99/9999.
008400     05  FILLER            PIC X(1) VALUE SPACE.
008500     05  PRINT-AMOUNT      PIC ZZZ,ZZ9.99.
008600     05  FILLER            PIC X(1) VALUE SPACE.
008700     05  PRINT-INVOICE     PIC X(15).
008800
008900 01  VENDOR-TOTAL-LITERAL.
009000     05  FILLER            PIC X(18) VALUE SPACE.
009100     05  FILLER            PIC X(12) VALUE "VENDOR TOTAL".
009200
009300 01  GRAND-TOTAL-LITERAL.
009400     05  FILLER            PIC X(25) VALUE SPACE.
009500     05  FILLER            PIC X(5) VALUE "TOTAL".
009600
009700 01  COLUMN-LINE.
009800     05  FILLER         PIC X(6) VALUE "VENDOR".
009900     05  FILLER         PIC X(23) VALUE SPACE.
010000     05  FILLER         PIC X(7)  VALUE "VOUCHER".
010100     05  FILLER         PIC X(5)  VALUE SPACE.
010200     05  FILLER         PIC X(8)  VALUE "DUE DATE".
010300     05  FILLER         PIC X(1)  VALUE SPACE.
010400     05  FILLER         PIC X(10) VALUE "AMOUNT DUE".
010500     05  FILLER         PIC X(1)  VALUE SPACE.
010600     05  FILLER         PIC X(7)  VALUE "INVOICE".
010700
010800 01  TITLE-LINE.
010900     05  FILLER              PIC X(25) VALUE SPACE.
011000     05  FILLER              PIC X(22)
011100         VALUE "BILLS REPORT BY VENDOR".
011200     05  FILLER              PIC X(11) VALUE SPACE.
011300     05  FILLER              PIC X(5) VALUE "PAGE:".
011400     05  FILLER              PIC X(1) VALUE SPACE.
011500     05  PRINT-PAGE-NUMBER   PIC ZZZ9.
011600
011700 77  WORK-FILE-AT-END     PIC X.
011800 77  VENDOR-RECORD-FOUND     PIC X.
011900
012000 77  LINE-COUNT              PIC 999 VALUE ZERO.
012100 77  PAGE-NUMBER             PIC 9999 VALUE ZERO.
012200 77  MAXIMUM-LINES           PIC 999 VALUE 55.
012300
012400 77  RECORD-COUNT            PIC 9999 VALUE ZEROES.
012500
012600* Control break current value for vendor
012700 77  CURRENT-VENDOR          PIC 9(5).
012800
012900* Control break accumulators
013000* GRAND TOTAL is the level 1 accumulator for the whole file
013100* VENDOR TOTAL is the level 2 accumulator
013200 77  GRAND-TOTAL            PIC S9(6)V99.
013300 77  VENDOR-TOTAL           PIC S9(6)V99.
013400
013500     COPY "WSDATE01.CBL".
013600
013700 PROCEDURE DIVISION.
013800 PROGRAM-BEGIN.
013900
014000     PERFORM OPENING-PROCEDURE.
014100     PERFORM MAIN-PROCESS.
014200     PERFORM CLOSING-PROCEDURE.
014300
014400 PROGRAM-EXIT.
014500     EXIT PROGRAM.
014600
014700 PROGRAM-DONE.
014800     STOP RUN.
014900
015000 OPENING-PROCEDURE.
015100     OPEN I-O VENDOR-FILE.
015200
015300     OPEN OUTPUT PRINTER-FILE.
015400
015500 MAIN-PROCESS.
015600     PERFORM GET-OK-TO-PROCESS.
015700     PERFORM PROCESS-THE-FILE
015800         UNTIL OK-TO-PROCESS = "N".
015900
016000 CLOSING-PROCEDURE.
016100     CLOSE VENDOR-FILE.
016200     CLOSE PRINTER-FILE.
016300
016400 GET-OK-TO-PROCESS.
016500     PERFORM ACCEPT-OK-TO-PROCESS.
016600     PERFORM RE-ACCEPT-OK-TO-PROCESS
016700         UNTIL OK-TO-PROCESS = "Y" OR "N".
016800
016900 ACCEPT-OK-TO-PROCESS.
017000     DISPLAY "PRINT BILLS BY VENDOR (Y/N)?".
017100     ACCEPT OK-TO-PROCESS.
017200     INSPECT OK-TO-PROCESS
017300       CONVERTING LOWER-ALPHA
017400       TO         UPPER-ALPHA.
017500
017600 RE-ACCEPT-OK-TO-PROCESS.
017700     DISPLAY "YOU MUST ENTER YES OR NO".
017800     PERFORM ACCEPT-OK-TO-PROCESS.
017900
018000 PROCESS-THE-FILE.
018100     PERFORM START-THE-FILE.
018200     PERFORM PRINT-ONE-REPORT.
018300     PERFORM END-THE-FILE.
018400
018500*    PERFORM GET-OK-TO-PROCESS.
018600     MOVE "N" TO OK-TO-PROCESS.
018700
018800 START-THE-FILE.
018900     PERFORM SORT-DATA-FILE.
019000     OPEN INPUT WORK-FILE.
019100
019200 END-THE-FILE.
019300     CLOSE WORK-FILE.
019400
019500 SORT-DATA-FILE.
019600     SORT SORT-FILE
019700         ON ASCENDING KEY SORT-VENDOR
019800          USING VOUCHER-FILE
019900          GIVING WORK-FILE.
020000
020100* LEVEL 1 CONTROL BREAK
020200 PRINT-ONE-REPORT.
020300     PERFORM START-ONE-REPORT.
020400     PERFORM PROCESS-ALL-VENDORS
020500         UNTIL WORK-FILE-AT-END = "Y".
020600     PERFORM END-ONE-REPORT.
020700
020800 START-ONE-REPORT.
020900     PERFORM READ-FIRST-VALID-WORK.
021000     MOVE ZEROES TO GRAND-TOTAL.
021100
021200     PERFORM START-NEW-REPORT.
021300
021400 START-NEW-REPORT.
021500     MOVE SPACE TO DETAIL-LINE.
021600     MOVE ZEROES TO LINE-COUNT PAGE-NUMBER.
021700     PERFORM START-NEW-PAGE.
021800
021900 END-ONE-REPORT.
022000     IF RECORD-COUNT = ZEROES
022100         MOVE "NO RECORDS FOUND" TO PRINTER-RECORD
022200         PERFORM WRITE-TO-PRINTER
022300     ELSE
022400         PERFORM PRINT-GRAND-TOTAL.
022500
022600     PERFORM END-LAST-PAGE.
022700
022800 PRINT-GRAND-TOTAL.
022900     MOVE GRAND-TOTAL TO PRINT-AMOUNT.
023000     MOVE GRAND-TOTAL-LITERAL TO PRINT-NAME.
023100     MOVE DETAIL-LINE TO PRINTER-RECORD.
023200     PERFORM WRITE-TO-PRINTER.
023300     PERFORM LINE-FEED 2 TIMES.
023400     MOVE SPACE TO DETAIL-LINE.
023500
023600* LEVEL 2 CONTROL BREAK
023700 PROCESS-ALL-VENDORS.
023800     PERFORM START-ONE-VENDOR.
023900
024000     PERFORM PROCESS-ALL-VOUCHERS
024100         UNTIL WORK-FILE-AT-END = "Y"
024200            OR WORK-VENDOR NOT = CURRENT-VENDOR.
024300
024400     PERFORM END-ONE-VENDOR.
024500
024600 START-ONE-VENDOR.
024700     MOVE WORK-VENDOR TO CURRENT-VENDOR.
024800     MOVE ZEROES TO VENDOR-TOTAL.
024900
025000     PERFORM LOAD-VENDOR-NAME.
025100
025200 LOAD-VENDOR-NAME.
025300     MOVE WORK-VENDOR TO VENDOR-NUMBER.
025400     PERFORM READ-VENDOR-RECORD.
025500     IF VENDOR-RECORD-FOUND = "Y"
025600         MOVE VENDOR-NAME TO PRINT-NAME
025700     ELSE
025800         MOVE "*VENDOR NOT ON FILE*" TO PRINT-NAME.
025900
026000 END-ONE-VENDOR.
026100     PERFORM PRINT-VENDOR-TOTAL.
026200     ADD VENDOR-TOTAL TO GRAND-TOTAL.
026300
026400 PRINT-VENDOR-TOTAL.
026500     MOVE VENDOR-TOTAL TO PRINT-AMOUNT.
026600     MOVE VENDOR-TOTAL-LITERAL TO PRINT-NAME.
026700     MOVE DETAIL-LINE TO PRINTER-RECORD.
026800     PERFORM WRITE-TO-PRINTER.
026900     PERFORM LINE-FEED.
027000     MOVE SPACE TO DETAIL-LINE.
027100
027200* PROCESS ONE RECORD LEVEL
027300 PROCESS-ALL-VOUCHERS.
027400     PERFORM PROCESS-THIS-VOUCHER.
027500     ADD WORK-AMOUNT TO VENDOR-TOTAL.
027600     ADD 1 TO RECORD-COUNT.
027700     PERFORM READ-NEXT-VALID-WORK.
027800
027900 PROCESS-THIS-VOUCHER.
028000     IF LINE-COUNT > MAXIMUM-LINES
028100         PERFORM START-NEXT-PAGE.
028200     PERFORM PRINT-THE-RECORD.
028300
028400 PRINT-THE-RECORD.
028500     MOVE WORK-NUMBER TO PRINT-NUMBER.
028600
028700     MOVE WORK-DUE TO DATE-CCYYMMDD.
028800     PERFORM CONVERT-TO-MMDDCCYY.
028900     MOVE DATE-MMDDCCYY TO PRINT-DUE-DATE.
029000
029100     MOVE WORK-AMOUNT TO PRINT-AMOUNT.
029200     MOVE WORK-INVOICE TO PRINT-INVOICE.
029300
029400     MOVE DETAIL-LINE TO PRINTER-RECORD.
029500     PERFORM WRITE-TO-PRINTER.
029600     MOVE SPACE TO DETAIL-LINE.
029700
029800* PRINTING ROUTINES
029900 WRITE-TO-PRINTER.
030000     WRITE PRINTER-RECORD BEFORE ADVANCING 1.
030100     ADD 1 TO LINE-COUNT.
030200
030300 LINE-FEED.
030400     MOVE SPACE TO PRINTER-RECORD.
030500     PERFORM WRITE-TO-PRINTER.
030600
030700 START-NEXT-PAGE.
030800     PERFORM END-LAST-PAGE.
030900     PERFORM START-NEW-PAGE.
031000
031100 START-NEW-PAGE.
031200     ADD 1 TO PAGE-NUMBER.
031300     MOVE PAGE-NUMBER TO PRINT-PAGE-NUMBER.
031400     MOVE TITLE-LINE TO PRINTER-RECORD.
031500     PERFORM WRITE-TO-PRINTER.
031600     PERFORM LINE-FEED.
031700     MOVE COLUMN-LINE TO PRINTER-RECORD.
031800     PERFORM WRITE-TO-PRINTER.
031900     PERFORM LINE-FEED.
032000
032100 END-LAST-PAGE.
032200     PERFORM FORM-FEED.
032300     MOVE ZERO TO LINE-COUNT.
032400
032500 FORM-FEED.
032600     MOVE SPACE TO PRINTER-RECORD.
032700     WRITE PRINTER-RECORD BEFORE ADVANCING PAGE.
032800
032900*--------------------------------
033000* Read first, read next routines
033100*--------------------------------
033200 READ-FIRST-VALID-WORK.
033300     PERFORM READ-NEXT-VALID-WORK.
033400
033500 READ-NEXT-VALID-WORK.
033600     PERFORM READ-NEXT-WORK-RECORD.
033700     PERFORM READ-NEXT-WORK-RECORD
033800         UNTIL WORK-FILE-AT-END = "Y"
033900            OR WORK-PAID-DATE = ZEROES.
034000
034100 READ-NEXT-WORK-RECORD.
034200     MOVE "N" TO WORK-FILE-AT-END.
034300     READ WORK-FILE NEXT RECORD
034400         AT END MOVE "Y" TO WORK-FILE-AT-END.
034500
034600*--------------------------------
034700* Other File IO routines
034800*--------------------------------
034900 READ-VENDOR-RECORD.
035000     MOVE "Y" TO VENDOR-RECORD-FOUND.
035100     READ VENDOR-FILE RECORD
035200         INVALID KEY
035300         MOVE "N" TO VENDOR-RECORD-FOUND.
035400
035500*--------------------------------
035600* Utility Routines
035700*--------------------------------
035800     COPY "PLDATE01.CBL".
035900

The output of blbyvn02.cbl prints the vendor name only once for each group of vouchers attached to the same vendor:

OUTPUT:

                         BILLS REPORT BY VENDOR           PAGE:    1
VENDOR                       VOUCHER     DUE DATE AMOUNT DUE INVOICE
AERIAL SIGNS                      14    1/17/1994   1,046.97 FA1234
VENDOR TOTAL                      1,046.97
ABC PRINTING                       4    2/07/1994     104.19 CX-5055
7    2/22/1994      48.97 CX-1407
8    1/27/1994      48.97 CX-1566
VENDOR TOTAL                        202.13
CHARLES SMITH AND SONS             3    2/22/1994      27.76 5057
16    1/16/1994      25.97 5098
VENDOR TOTAL                         53.73
MA BELL                           13    1/23/1994      94.96 50577
19    1/23/1994      34.95 50577
VENDOR TOTAL                        129.91
RANIER GRAPHICS                   20    2/25/1994   2,057.07 ZO-1515
VENDOR TOTAL                      2,057.07
ABERCROMBIE AND OTHERS            15    1/31/1994     657.19 MONTHLY
VENDOR TOTAL                        657.19
TOTAL                      4,147.00

ANALYSIS: START-ONE-VENDOR at line 024600 is identical to the same paragraph in blbyvn01.cbl (shown in Listing B1.5), but it adds logic to perform LOAD-VENDOR-NAME. This routine originally was performed in PRINT-THE-RECORD, which begins at line 028400 in this version of the program. The vendor name is loaded into the detail line only once at the beginning of each new vendor.

Multilevel Control Breaks

The logic of a multilevel control breaking program is quite easy to express. Listing B1.7 is a general statement of control breaking in a file-processing program down to four levels. Level 1 is the all-records level and the level-1-accumulators will be the grand totals for the whole file.

TYPE: Listing B1.7. A general logic flow for control breaks.

process-the-file
    perform start-the-file
    perform process-level-1-control-break
    perform end-the-file
start-the-file
    create-the-file
    open the file
create-the-file
    sort the file on
        level-2-control-field
        level-3-control-field
        level-4-control-field
end-the-file
    close the file
process-level-1-control-break
    perform start-level-1
    perform process-level-2-control-break
        until file-at-end
    perform end-level-1
start-level-1
    read first valid record
    move zeroes to level-1-accumulators
    any other starting actions
end-level-1
    perform process-level-1-accumulators
    any other ending actions
process-level-2-control-break
    perform start-level-2
    perform process-level-3-control-break
        until file-at-end
           or level-2-control-field not = level-2-current-value
    perform end-level-2
start-level-2
    move level-2-control-field to level-2-current-value
    move zeroes to level-2-accumulators
    any other starting actions
end-level-2
    perform process-level-2-accumulators
    perform add-level-2-accumulators to level-1-accumulators
    any other ending actions
process-level-3-control-break
    perform start-level-3
    perform process-level-4-control-break
        until file-at-end
           or level-2-control-field not = level-2-current-value
           or level-3-control-field not = level-3-current-value
    perform end-level-3
start-level-3
    move level-3-control-field to level-3-current-value
    move zeroes to level-3-accumulators
    any other starting actions
end-level-3
    perform process-level-3-accumulators
    perform add-level-3-accumulators to level-2-accumulators
    any other ending actions
process-level-4-control-break
    perform start-level-4
    perform process-one-record
        until file-at-end
           or level-2-control-field not = level-2-current-value
           or level-3-control-field not = level-3-current-value
           or level-4-control-field not = level-4-current-value
    perform end-level-4
start-level-4
    move level-4-control-field to level-4-current-value
    move zeroes to level-4-accumulators
    any other starting actions
end-level-4
    perform process-level-4-accumulators
    perform add-level-4-accumulators to level-3-accumulators
    any other ending actions
process-one-record
    perform process-this-record
    add record-values to level-4-accumulators
    read next valid record

This example carries the control breaking to four levels, and this can be repeated for as many levels as necessary as long as the file is sorted on each of the control break fields.

Remember that the level-1 break is controlled by the end of the file, and notice that the conditions that cause level breaks are cumulative as you descend to lower levels.

Using Multilevel Control Breaks

In order to illustrate a multilevel control breaking report, it is necessary to create a test file with multiple levels in it.

For this example, you create a chain of six retail stores that sell sporting goods. All of the goods are divided into 12 categories. The categories are allocated to departments, and the departments fall under three main divisions. Table B1.3 shows the breakdown of divisions, departments, and categories.

Table B1.3. Divisions, departments, and categories of a hypothetical sporting goods store.

Div. Dep. Division Name Cat. Department Category Name Name
01 Athletics 01 Exercise 01 Weights
02 Machines
02 Miscellaneous 03 Sunglasses
04 Vitamins
02 Sporting Goods 03 Sport Clothes 05 Men's Clothes
06 Women's Clothes
04 Equipment 07 Tennis
08 Soccer
03 Camping 05 Camp Equipment 09 Tents
10 Sleeping Bags
06 Camping Clothes 11 Clothing
12 Hiking Boots

Each day, the six stores send in their sales figures by category. A program looks up the division and department and creates a temporary file of sales information that includes the store number, division number, department number, category number, and sales figures. Listings B1.8 and B1.9 are the SELECT and FD for this temporary file. The file is not indexed because it is used only for reporting.

TYPE: Listing B1.8. The SELECT statement for the sales file.

000100*--------------------------------
000200* SLSALES.CBL
000300*--------------------------------
000400     SELECT SALES-FILE
000500         ASSIGN TO "SALES"
000600         ORGANIZATION IS SEQUENTIAL.
000700

TYPE: Listing B1.9. The FD for the sales file.

000100*--------------------------------
000200* FDSALES.CBL
000400* Temporary daily sales file.
000600*--------------------------------
000700 FD  SALES-FILE
000800     LABEL RECORDS ARE STANDARD.
000900 01  SALES-RECORD.
001000     05  SALES-STORE              PIC 9(2).
001100     05  SALES-DIVISION           PIC 9(2).
001200     05  SALES-DEPARTMENT         PIC 9(2).
001300     05  SALES-CATEGORY           PIC 9(2).
001400     05  SALES-AMOUNT             PIC S9(6)V99.
001500

Because you do not actually have a retail chain at your disposal, you have to create a test file containing random sales figures. Listing B1.10, slsgen01.cbl, generates a collection of random sales records for all stores and all categories.

TYPE: Listing B1.10. Generating test sales data.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. SLSGEN01.
000300*--------------------------------
000400* Generate test sales data
000500*--------------------------------
000600 ENVIRONMENT DIVISION.
000700 INPUT-OUTPUT SECTION.
000800 FILE-CONTROL.
000900
001000*--------------------------------
001100* SLSALES.CBL
001200*--------------------------------
001300     SELECT SALES-FILE
001400         ASSIGN TO "SALES"
001500         ORGANIZATION IS SEQUENTIAL.
001600
001700 DATA DIVISION.
001800 FILE SECTION.
001900
002000*--------------------------------
002100* FDSALES.CBL
002200* Temporary daily sales file.
002300*--------------------------------
002400 FD  SALES-FILE
002500     LABEL RECORDS ARE STANDARD.
002600 01  SALES-RECORD.
002700     05  SALES-STORE              PIC 9(2).
002800     05  SALES-DIVISION           PIC 9(2).
002900     05  SALES-DEPARTMENT         PIC 9(2).
003000     05  SALES-CATEGORY           PIC 9(2).
003100     05  SALES-AMOUNT             PIC S9(6)V99.
003200
003300 WORKING-STORAGE SECTION.
003400
003500 77  THE-STORE                    PIC 99.
003600 77  THE-DIVISION                 PIC 99.
003700 77  THE-DEPARTMENT               PIC 99.
003800 77  THE-CATEGORY                 PIC 99.
003900
004000 77  THE-AMOUNT                   PIC S9(6)V99.
004100
004200 PROCEDURE DIVISION.
004300 PROGRAM-BEGIN.
004400     PERFORM OPENING-PROCEDURE.
004500     PERFORM MAIN-PROCESS.
004600     PERFORM CLOSING-PROCEDURE.
004700
004800 PROGRAM-EXIT.
004900     EXIT PROGRAM.
005000
005100 PROGRAM-DONE.
005200     STOP RUN.
005300
005400 OPENING-PROCEDURE.
005500     OPEN OUTPUT SALES-FILE.
005600
005700 CLOSING-PROCEDURE.
005800     CLOSE SALES-FILE.
005900
006000 MAIN-PROCESS.
006100     MOVE ZEROES TO THE-AMOUNT.
006200     PERFORM GENERATE-STORE-SALES
006300         VARYING THE-STORE FROM 1 BY 1
006400           UNTIL THE-STORE > 6.
006500
006600 GENERATE-STORE-SALES.
006700     PERFORM GENERATE-CATEGORY-SALES
006800         VARYING THE-CATEGORY FROM 1 BY 1
006900           UNTIL THE-CATEGORY > 12.
007000
007100 GENERATE-CATEGORY-SALES.
007200     ADD 237.57 TO THE-AMOUNT.
007300     IF THE-AMOUNT > 800
007400         SUBTRACT 900 FROM THE-AMOUNT.
007500
007600     MOVE THE-AMOUNT TO SALES-AMOUNT.
007700     MOVE THE-STORE TO SALES-STORE.
007800     MOVE THE-CATEGORY TO SALES-CATEGORY.
007900
008000     PERFORM GENERATE-THE-DEPARTMENT.
008100     PERFORM GENERATE-THE-DIVISION.
008200
008300     WRITE SALES-RECORD.
008400
008500 GENERATE-THE-DEPARTMENT.
008600     ADD 1 TO THE-CATEGORY.
008700     DIVIDE THE-CATEGORY BY 2
008800         GIVING THE-DEPARTMENT.
008900     MOVE THE-DEPARTMENT TO SALES-DEPARTMENT.
009000     SUBTRACT 1 FROM THE-CATEGORY.
009100
009200 GENERATE-THE-DIVISION.
009300     ADD 1 TO THE-DEPARTMENT
009400     DIVIDE THE-DEPARTMENT BY 2
009500         GIVING THE-DIVISION.
009600     MOVE THE-DIVISION TO SALES-DIVISION.
009700

ANALYSIS: The OPENING-PROCEDURE opens the file in output mode so that it is created.

The main process starts by moving zeroes to THE-AMOUNT at line 006100. This field will be used to create some random sales numbers. MAIN-PROCESS then performs GENERATE-STORE-SALES for each of the six stores at line 006200.

The GENERATE-STORE-SALES routine at line 006600 performs GENERATE-CATEGORY-SALES for each of the 12 categories of goods.

The GENERATE-CATEGORY-SALES starts at line 007100. It uses some tricks to generate amounts at lines 007200 through 007400. On each entry to GENERATE-CATEGORY-SALES, 237.57 is added to THE-AMOUNT. If THE-AMOUNT has exceeded 800, 900 is subtracted from THE-AMOUNT. This method was chosen as an arbitrary way of creating random sales figures for each category. Subtracting 900 when the number exceeds 800 allows some categories to be negative (because of refunds).

At lines 007600 through 007800, THE-AMOUNT, THE-STORE, and THE-CATEGORY are moved into the SALES-RECORD.

Another trick is used to determine the department number for each category. From Table B1.3, you see that department 1 includes categories 1 and 2, and department 2 includes categories 3 and 4. If you add 1 to the category and divide it by 2, the result (ignoring fractions) will be the department number. This is just a convenient trick that gets the department number quickly. This logic is taken care of in GENERATE-THE-DEPARTMENT, which starts at line 008500. After 1 is added to the category, it is divided by 2 and the result is placed directly in THE-DEPARTMENT. THE-DEPARTMENT has no decimal, so any decimal result of the division is truncated. Finally, THE-DEPARTMENT is moved to SALES-DEPARTMENT. Because THE-CATEGORY is being used as a loop-control variable (in lines 006700 through 006900), it is necessary to subtract 1 from it to return it to its original value.

A similar trick is used in GENERATE-THE-DIVISION, which starts at line 009200 to generate the division number from the department number.

After the department number and division number are filled in, all fields of the record are filled in, and at line 008300 the program writes the SALES-RECORD.

Code, compile, and run slsgen01.cbl. It should create 72 test records, one for each of 12 departments in six stores.

Now that you have the test data that you need, you can build a multilevel control breaking report that reports sales titles by store, division, department, and category.

Figure B1.5 is the printer spacing chart for slsrpt01.cbl. Line 7 is a detail line. Line 8 also is a detail line, but because the division and department have not changed, they are not printed again on this line. Line 9 is an example of a department subtotal. Line 15 is an example of a division subtotal. Lines 27 and 29 are store and grand totals. Each store will start on a new page. This report is an example of several of the types of problems encountered when working on control breaking reports.

Figure B1.5.
Printer layout chart for
slsrpt01.cbl.

Listing B1.11 is the report program that will generate the report using the test sales file that has been created.

TYPE: Listing B1.11. A report with multiple control breaks.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. SLSRPT01.
000300*--------------------------------
000400* Print test sales data
000500*--------------------------------
000600 ENVIRONMENT DIVISION.
000700 INPUT-OUTPUT SECTION.
000800 FILE-CONTROL.
000900
001000*--------------------------------
001100* SLSALES.CBL
001200*--------------------------------
001300     SELECT SALES-FILE
001400         ASSIGN TO "SALES"
001500         ORGANIZATION IS SEQUENTIAL.
001600
001700     SELECT WORK-FILE
001800         ASSIGN TO "WORK"
001900         ORGANIZATION IS SEQUENTIAL.
002000
002100     SELECT SORT-FILE
002200         ASSIGN TO "SORT".
002300
002400     SELECT PRINTER-FILE
002500         ASSIGN TO PRINTER
002600         ORGANIZATION IS LINE SEQUENTIAL.
002700
002800 DATA DIVISION.
002900 FILE SECTION.
003000
003100*--------------------------------
003200* FDSALES.CBL
003300* Temporary daily sales file.
003400*--------------------------------
003500 FD  SALES-FILE
003600     LABEL RECORDS ARE STANDARD.
003700 01  SALES-RECORD.
003800     05  SALES-STORE              PIC 9(2).
003900     05  SALES-DIVISION           PIC 9(2).
004000     05  SALES-DEPARTMENT         PIC 9(2).
004100     05  SALES-CATEGORY           PIC 9(2).
004200     05  SALES-AMOUNT             PIC S9(6)V99.
004300
004400 FD  WORK-FILE
004500     LABEL RECORDS ARE STANDARD.
004600 01  WORK-RECORD.
004700     05  WORK-STORE              PIC 9(2).
004800     05  WORK-DIVISION           PIC 9(2).
004900     05  WORK-DEPARTMENT         PIC 9(2).
005000     05  WORK-CATEGORY           PIC 9(2).
005100     05  WORK-AMOUNT             PIC S9(6)V99.
005200
005300 SD  SORT-FILE
005400     LABEL RECORDS ARE STANDARD.
005500 01  SORT-RECORD.
005600     05  SORT-STORE              PIC 9(2).
005700     05  SORT-DIVISION           PIC 9(2).
005800     05  SORT-DEPARTMENT         PIC 9(2).
005900     05  SORT-CATEGORY           PIC 9(2).
006000     05  SORT-AMOUNT             PIC S9(6)V99.
006100
006200 FD  PRINTER-FILE
006300     LABEL RECORDS ARE OMITTED.
006400 01  PRINTER-RECORD              PIC X(80).
006500
006600 WORKING-STORAGE SECTION.
006700
006800 77  OK-TO-PROCESS         PIC X.
006900
007000     COPY "WSCASE01.CBL".
007100
007200 01  LEGEND-LINE.
007300     05  FILLER            PIC X(6) VALUE "STORE:".
007400     05  FILLER            PIC X(1) VALUE SPACE.
007500     05  PRINT-STORE       PIC Z9.
007600
007700 01  DETAIL-LINE.
007800     05  FILLER            PIC X(3) VALUE SPACE.
007900     05  PRINT-DIVISION    PIC Z9.
008000     05  FILLER            PIC X(4) VALUE SPACE.
008100     05  FILLER            PIC X(3) VALUE SPACE.
008200     05  PRINT-DEPARTMENT  PIC Z9.
008300     05  FILLER            PIC X(6) VALUE SPACE.
008400     05  FILLER            PIC X(3) VALUE SPACE.
008500     05  PRINT-CATEGORY    PIC Z9.
008600     05  FILLER            PIC X(4) VALUE SPACE.
008700     05  PRINT-AMOUNT      PIC ZZZ,ZZ9.99-.
008800
008900 01  COLUMN-LINE.
009000     05  FILLER         PIC X(8)  VALUE "DIVISION".
009100     05  FILLER         PIC X(1)  VALUE SPACE.
009200     05  FILLER         PIC X(10) VALUE "DEPARTMENT".
009300     05  FILLER         PIC X(1)  VALUE SPACE.
009400     05  FILLER         PIC X(8)  VALUE "CATEGORY".
009500     05  FILLER         PIC X(1)  VALUE SPACE.
009600     05  FILLER         PIC X(4)  VALUE SPACE.
009700     05  FILLER         PIC X(6)  VALUE "AMOUNT".
009800
009900 01  TITLE-LINE.
010000     05  FILLER              PIC X(30) VALUE SPACE.
010100     05  FILLER              PIC X(12)
010200         VALUE "SALES REPORT".
010300     05  FILLER              PIC X(16) VALUE SPACE.
010400     05  FILLER              PIC X(5) VALUE "PAGE:".
010500     05  FILLER              PIC X(1) VALUE SPACE.
010600     05  PRINT-PAGE-NUMBER   PIC ZZZ9.
010700
010800 01  TOTAL-LINE.
010900     05  FILLER              PIC X(11) VALUE SPACE.
011000     05  TOTAL-TYPE          PIC X(8).
011100     05  FILLER              PIC X(1) VALUE SPACE.
011200     05  TOTAL-NUMBER        PIC Z9.
011300     05  FILLER              PIC X(1) VALUE SPACE.
011400     05  TOTAL-LITERAL       PIC X(5) VALUE "TOTAL".
011500     05  FILLER              PIC X(1) VALUE SPACE.
011600     05  PRINT-TOTAL         PIC ZZZ,ZZ9.99-.
011700
011800 77  GRAND-TOTAL-LITERAL      PIC X(8) VALUE "   GRAND".
011900 77  STORE-TOTAL-LITERAL      PIC X(8) VALUE "   STORE".
012000 77  DIVISION-TOTAL-LITERAL   PIC X(8) VALUE "DIVISION".
012100 77  DEPARTMENT-TOTAL-LITERAL PIC X(8) VALUE "    DEPT".
012200
012300 77  WORK-FILE-AT-END        PIC X.
012400
012500 77  LINE-COUNT              PIC 999 VALUE ZERO.
012600 77  PAGE-NUMBER             PIC 9999 VALUE ZERO.
012700 77  MAXIMUM-LINES           PIC 999 VALUE 55.
012800
012900 77  RECORD-COUNT            PIC 9999 VALUE ZEROES.
013000
013100* Control break current values for store, division
013200* department.
013300 77  CURRENT-STORE          PIC 99.
013400 77  CURRENT-DIVISION       PIC 99.
013500 77  CURRENT-DEPARTMENT     PIC 99.
013600
013700* Control break accumulators
013800* GRAND TOTAL is the level 1 accumulator for the whole file
013900* STORE TOTAL is the level 2 accumulator
014000* DIVISION TOTAL is the level 3 accumulator
014100* DEPARTMENT TOTAL is the level 4 accumulator.
014200 77  GRAND-TOTAL            PIC S9(6)V99.
014300 77  STORE-TOTAL            PIC S9(6)V99.
014400 77  DIVISION-TOTAL         PIC S9(6)V99.
014500 77  DEPARTMENT-TOTAL       PIC S9(6)V99.
014600
014700 PROCEDURE DIVISION.
014800 PROGRAM-BEGIN.
014900
015000     PERFORM OPENING-PROCEDURE.
015100     PERFORM MAIN-PROCESS.
015200     PERFORM CLOSING-PROCEDURE.
015300
015400 PROGRAM-EXIT.
015500     EXIT PROGRAM.
015600
015700 PROGRAM-DONE.
015800     STOP RUN.
015900
016000 OPENING-PROCEDURE.
016100
016200     OPEN OUTPUT PRINTER-FILE.
016300
016400 MAIN-PROCESS.
016500     PERFORM GET-OK-TO-PROCESS.
016600     PERFORM PROCESS-THE-FILE
016700         UNTIL OK-TO-PROCESS = "N".
016800
016900 CLOSING-PROCEDURE.
017000     CLOSE PRINTER-FILE.
017100
017200 GET-OK-TO-PROCESS.
017300     PERFORM ACCEPT-OK-TO-PROCESS.
017400     PERFORM RE-ACCEPT-OK-TO-PROCESS
017500         UNTIL OK-TO-PROCESS = "Y" OR "N".
017600
017700 ACCEPT-OK-TO-PROCESS.
017800     DISPLAY "PRINT SALES REPORT (Y/N)?".
017900     ACCEPT OK-TO-PROCESS.
018000     INSPECT OK-TO-PROCESS
018100       CONVERTING LOWER-ALPHA
018200       TO         UPPER-ALPHA.
018300
018400 RE-ACCEPT-OK-TO-PROCESS.
018500     DISPLAY "YOU MUST ENTER YES OR NO".
018600     PERFORM ACCEPT-OK-TO-PROCESS.
018700
018800 PROCESS-THE-FILE.
018900     PERFORM START-THE-FILE.
019000     PERFORM PRINT-ONE-REPORT.
019100     PERFORM END-THE-FILE.
019200
019300*    PERFORM GET-OK-TO-PROCESS.
019400     MOVE "N" TO OK-TO-PROCESS.
019500
019600 START-THE-FILE.
019700     PERFORM SORT-DATA-FILE.
019800     OPEN INPUT WORK-FILE.
019900
020000 END-THE-FILE.
020100     CLOSE WORK-FILE.
020200
020300 SORT-DATA-FILE.
020400     SORT SORT-FILE
020500         ON ASCENDING KEY SORT-STORE
020600            ASCENDING KEY SORT-DIVISION
020700            ASCENDING KEY SORT-DEPARTMENT
020800            ASCENDING KEY SORT-CATEGORY
020900          USING SALES-FILE
021000          GIVING WORK-FILE.
021100
021200* LEVEL 1 CONTROL BREAK
021300 PRINT-ONE-REPORT.
021400     PERFORM START-ONE-REPORT.
021500     PERFORM PROCESS-ALL-STORES
021600         UNTIL WORK-FILE-AT-END = "Y".
021700     PERFORM END-ONE-REPORT.
021800
021900 START-ONE-REPORT.
022000     PERFORM READ-FIRST-VALID-WORK.
022100     MOVE ZEROES TO GRAND-TOTAL.
022200
022300     PERFORM START-NEW-REPORT.
022400
022500 START-NEW-REPORT.
022600     MOVE SPACE TO DETAIL-LINE.
022700     MOVE ZEROES TO LINE-COUNT PAGE-NUMBER.
022800
022900 END-ONE-REPORT.
023000     IF RECORD-COUNT = ZEROES
023100         MOVE "NO RECORDS FOUND" TO PRINTER-RECORD
023200         PERFORM WRITE-TO-PRINTER
023300     ELSE
023400         PERFORM PRINT-GRAND-TOTAL.
023500
023600     PERFORM END-LAST-PAGE.
023700
023800 PRINT-GRAND-TOTAL.
023900     MOVE SPACE TO TOTAL-LINE.
024000     MOVE GRAND-TOTAL TO PRINT-TOTAL.
024100     MOVE GRAND-TOTAL-LITERAL TO TOTAL-TYPE.
024200     MOVE "TOTAL" TO TOTAL-LITERAL.
024300     MOVE TOTAL-LINE TO PRINTER-RECORD.
024400     PERFORM WRITE-TO-PRINTER.
024500     PERFORM LINE-FEED 2 TIMES.
024600     MOVE SPACE TO DETAIL-LINE.
024700
024800* LEVEL 2 CONTROL BREAK
024900 PROCESS-ALL-STORES.
025000     PERFORM START-ONE-STORE.
025100
025200     PERFORM PROCESS-ALL-DIVISIONS
025300         UNTIL WORK-FILE-AT-END = "Y"
025400            OR WORK-STORE NOT = CURRENT-STORE.
025500
025600     PERFORM END-ONE-STORE.
025700
025800 START-ONE-STORE.
025900     MOVE WORK-STORE TO CURRENT-STORE.
026000     MOVE ZEROES TO STORE-TOTAL.
026100     MOVE WORK-STORE TO PRINT-STORE.
026200
026300     PERFORM START-NEXT-PAGE.
026400
026500 END-ONE-STORE.
026600     PERFORM PRINT-STORE-TOTAL.
026700     ADD STORE-TOTAL TO GRAND-TOTAL.
026800
026900 PRINT-STORE-TOTAL.
027000     MOVE SPACE TO TOTAL-LINE.
027100     MOVE STORE-TOTAL TO PRINT-TOTAL.
027200     MOVE CURRENT-STORE TO TOTAL-NUMBER.
027300     MOVE STORE-TOTAL-LITERAL TO TOTAL-TYPE.
027400     MOVE "TOTAL" TO TOTAL-LITERAL.
027500     MOVE TOTAL-LINE TO PRINTER-RECORD.
027600     PERFORM WRITE-TO-PRINTER.
027700     PERFORM LINE-FEED.
027800     MOVE SPACE TO DETAIL-LINE.
027900
028000* LEVEL 3 CONTROL BREAK
028100 PROCESS-ALL-DIVISIONS.
028200     PERFORM START-ONE-DIVISION.
028300
028400     PERFORM PROCESS-ALL-DEPARTMENTS
028500         UNTIL WORK-FILE-AT-END = "Y"
028600            OR WORK-STORE NOT = CURRENT-STORE
028700            OR WORK-DIVISION NOT = CURRENT-DIVISION.
028800
028900     PERFORM END-ONE-DIVISION.
029000
029100 START-ONE-DIVISION.
029200     MOVE WORK-DIVISION TO CURRENT-DIVISION.
029300     MOVE ZEROES TO DIVISION-TOTAL.
029400     MOVE WORK-DIVISION TO PRINT-DIVISION.
029500
029600 END-ONE-DIVISION.
029700     PERFORM PRINT-DIVISION-TOTAL.
029800     ADD DIVISION-TOTAL TO STORE-TOTAL.
029900
030000 PRINT-DIVISION-TOTAL.
030100     MOVE SPACE TO TOTAL-LINE.
030200     MOVE DIVISION-TOTAL TO PRINT-TOTAL.
030300     MOVE CURRENT-DIVISION TO TOTAL-NUMBER.
030400     MOVE DIVISION-TOTAL-LITERAL TO TOTAL-TYPE.
030500     MOVE "TOTAL" TO TOTAL-LITERAL.
030600     MOVE TOTAL-LINE TO PRINTER-RECORD.
030700     PERFORM WRITE-TO-PRINTER.
030800     PERFORM LINE-FEED.
030900     MOVE SPACE TO DETAIL-LINE.
031000
031100* LEVEL 4 CONTROL BREAK
031200 PROCESS-ALL-DEPARTMENTS.
031300     PERFORM START-ONE-DEPARTMENT.
031400
031500     PERFORM PROCESS-ALL-CATEGORIES
031600         UNTIL WORK-FILE-AT-END = "Y"
031700            OR WORK-STORE NOT = CURRENT-STORE
031800            OR WORK-DIVISION NOT = CURRENT-DIVISION
031900            OR WORK-DEPARTMENT NOT = CURRENT-DEPARTMENT.
032000
032100     PERFORM END-ONE-DEPARTMENT.
032200
032300 START-ONE-DEPARTMENT.
032400     MOVE WORK-DEPARTMENT TO CURRENT-DEPARTMENT.
032500     MOVE ZEROES TO DEPARTMENT-TOTAL.
032600     MOVE WORK-DEPARTMENT TO PRINT-DEPARTMENT.
032700
032800 END-ONE-DEPARTMENT.
032900     PERFORM PRINT-DEPARTMENT-TOTAL.
033000     ADD DEPARTMENT-TOTAL TO DIVISION-TOTAL.
033100
033200 PRINT-DEPARTMENT-TOTAL.
033300     MOVE SPACE TO TOTAL-LINE.
033400     MOVE DEPARTMENT-TOTAL TO PRINT-TOTAL.
033500     MOVE CURRENT-DEPARTMENT TO TOTAL-NUMBER.
033600     MOVE DEPARTMENT-TOTAL-LITERAL TO TOTAL-TYPE.
033700     MOVE "TOTAL" TO TOTAL-LITERAL.
033800     MOVE TOTAL-LINE TO PRINTER-RECORD.
033900     PERFORM WRITE-TO-PRINTER.
034000     PERFORM LINE-FEED.
034100     MOVE SPACE TO DETAIL-LINE.
034200
034300* PROCESS ONE RECORD LEVEL
034400 PROCESS-ALL-CATEGORIES.
034500     PERFORM PROCESS-THIS-CATEGORY.
034600     ADD WORK-AMOUNT TO DEPARTMENT-TOTAL.
034700     ADD 1 TO RECORD-COUNT.
034800     PERFORM READ-NEXT-VALID-WORK.
034900
035000 PROCESS-THIS-CATEGORY.
035100     IF LINE-COUNT > MAXIMUM-LINES
035200         PERFORM START-NEXT-PAGE.
035300     PERFORM PRINT-THE-RECORD.
035400
035500 PRINT-THE-RECORD.
035600     MOVE WORK-CATEGORY TO PRINT-CATEGORY.
035700
035800     MOVE WORK-AMOUNT TO PRINT-AMOUNT.
035900
036000     MOVE DETAIL-LINE TO PRINTER-RECORD.
036100     PERFORM WRITE-TO-PRINTER.
036200     MOVE SPACE TO DETAIL-LINE.
036300
036400* PRINTING ROUTINES
036500 WRITE-TO-PRINTER.
036600     WRITE PRINTER-RECORD BEFORE ADVANCING 1.
036700     ADD 1 TO LINE-COUNT.
036800
036900 LINE-FEED.
037000     MOVE SPACE TO PRINTER-RECORD.
037100     PERFORM WRITE-TO-PRINTER.
037200
037300 START-NEXT-PAGE.
037400     PERFORM END-LAST-PAGE.
037500     PERFORM START-NEW-PAGE.
037600
037700 START-NEW-PAGE.
037800     ADD 1 TO PAGE-NUMBER.
037900     MOVE PAGE-NUMBER TO PRINT-PAGE-NUMBER.
038000     MOVE TITLE-LINE TO PRINTER-RECORD.
038100     PERFORM WRITE-TO-PRINTER.
038200     PERFORM LINE-FEED.
038300     MOVE LEGEND-LINE TO PRINTER-RECORD.
038400     PERFORM WRITE-TO-PRINTER.
038500     PERFORM LINE-FEED.
038600     MOVE COLUMN-LINE TO PRINTER-RECORD.
038700     PERFORM WRITE-TO-PRINTER.
038800     PERFORM LINE-FEED.
038900
039000 END-LAST-PAGE.
039100     IF PAGE-NUMBER > 0
039200         PERFORM FORM-FEED.
039300     MOVE ZERO TO LINE-COUNT.
039400
039500 FORM-FEED.
039600     MOVE SPACE TO PRINTER-RECORD.
039700     WRITE PRINTER-RECORD BEFORE ADVANCING PAGE.
039800
039900*--------------------------------
040000* Read first, read next routines
040100*--------------------------------
040200 READ-FIRST-VALID-WORK.
040300     PERFORM READ-NEXT-VALID-WORK.
040400
040500 READ-NEXT-VALID-WORK.
040600     PERFORM READ-NEXT-WORK-RECORD.
040700
040800 READ-NEXT-WORK-RECORD.
040900     MOVE "N" TO WORK-FILE-AT-END.
041000     READ WORK-FILE NEXT RECORD
041100         AT END MOVE "Y" TO WORK-FILE-AT-END.
041200

The output of slsrpt01 shows four levels of control breaks: all records, store, division, and department:

OUTPUT:

SALES REPORT                PAGE:    1
STORE:  1
DIVISION DEPARTMENT CATEGORY     AMOUNT
1        1          1        237.57
2        475.14
DEPT  1 TOTAL     712.71
2          3        712.71
4         50.28
DEPT  2 TOTAL     762.99
DIVISION  1 TOTAL   1,475.70
2        3          5        287.85
6        525.42
DEPT  3 TOTAL     813.27
4          7        762.99
8        100.56
DEPT  4 TOTAL     863.55
DIVISION  2 TOTAL   1,676.82
3        5          9        338.13
10        575.70
DEPT  5 TOTAL     913.83
6         11         86.73-
12        150.84
DEPT  6 TOTAL      64.11
DIVISION  3 TOTAL     977.94
STORE  1 TOTAL   4,130.46
SALES REPORT               PAGE:    2
STORE:  2
DIVISION DEPARTMENT CATEGORY     AMOUNT
1        1          1        388.41
2        625.98
DEPT  1 TOTAL   1,014.39
2          3         36.45-
4        201.12
DEPT  2 TOTAL     164.67
DIVISION  1 TOTAL   1,179.06
2        3          5        438.69
6        676.26
DEPT  3 TOTAL   1,114.95
4          7         13.83
8        251.40
DEPT  4 TOTAL     265.23
DIVISION  2 TOTAL   1,380.18
3        5          9        488.97
10        726.54
DEPT  5 TOTAL   1,215.51
6         11         64.11
12        301.68
DEPT  6 TOTAL     365.79
DIVISION  3 TOTAL   1,581.30
STORE  2 TOTAL   4,140.54
SALES REPORT               PAGE:    3
STORE:  3
DIVISION DEPARTMENT CATEGORY     AMOUNT
1        1          1        539.25
2        776.82
DEPT  1 TOTAL   1,316.07
2          3        114.39
4        351.96
DEPT  2 TOTAL     466.35
DIVISION  1 TOTAL   1,782.42
2        3          5        589.53
6         72.90-
DEPT  3 TOTAL     516.63
4          7        164.67
8        402.24
DEPT  4 TOTAL     566.91
DIVISION  2 TOTAL   1,083.54
3        5          9        639.81
10         22.62-
DEPT  5 TOTAL     617.19
6         11        214.95
12        452.52
DEPT  6 TOTAL     667.47
DIVISION  3 TOTAL   1,284.66
STORE  3 TOTAL   4,150.62
SALES REPORT               PAGE:    4
STORE:  4
DIVISION DEPARTMENT CATEGORY     AMOUNT
1        1          1        690.09
2         27.66
DEPT  1 TOTAL     717.75
2          3        265.23
4        502.80
DEPT  2 TOTAL     768.03
DIVISION  1 TOTAL   1,485.78
2        3          5        740.37
6         77.94
DEPT  3 TOTAL     818.31
4          7        315.51
8        553.08
DEPT  4 TOTAL     868.59
DIVISION  2 TOTAL   1,686.90
3        5          9        790.65
10        128.22
DEPT  5 TOTAL     918.87
6         11        365.79
12        603.36
DEPT  6 TOTAL     969.15
DIVISION  3 TOTAL   1,888.02
STORE  4 TOTAL   5,060.70
SALES REPORT               PAGE:    5
STORE:  5
DIVISION DEPARTMENT CATEGORY     AMOUNT
1        1          1         59.07-
2        178.50
DEPT  1 TOTAL     119.43
2          3        416.07
4        653.64
DEPT  2 TOTAL   1,069.71
DIVISION  1 TOTAL   1,189.14
2        3          5          8.79-
6        228.78
DEPT  3 TOTAL     219.99
4          7        466.35
8        703.92
DEPT  4 TOTAL   1,170.27
DIVISION  2 TOTAL   1,390.26
3        5          9         41.49
10        279.06
DEPT  5 TOTAL     320.55
6         11        516.63
12        754.20
DEPT  6 TOTAL   1,270.83
DIVISION  3 TOTAL   1,591.38
STORE  5 TOTAL   4,170.78
SALES REPORT               PAGE:    6
STORE:  6
DIVISION DEPARTMENT CATEGORY     AMOUNT
1        1          1         91.77
2        329.34
DEPT  1 TOTAL     421.11
2          3        566.91
4         95.52-
DEPT  2 TOTAL     471.39
DIVISION  1 TOTAL     892.50
2        3          5        142.05
6        379.62
DEPT  3 TOTAL     521.67
4          7        617.19
8         45.24-
DEPT  4 TOTAL     571.95
DIVISION  2 TOTAL   1,093.62
3        5          9        192.33
10        429.90
DEPT  5 TOTAL     622.23
6         11        667.47
12          5.04
DEPT  6 TOTAL     672.51
DIVISION  3 TOTAL   1,294.74
STORE  6 TOTAL   3,280.86
GRAND    TOTAL  24,933.96

ANALYSIS: The report contains four level breaks: all records, store, division, and department. The first thing you would expect of a report like this is that the input data file must be sorted. Lines 003500, 004400, and 005300 contain the definitions for the sales file, a work file, and a sort file, respectively.

The sort itself is at lines 020400 through 021000. Note the wording of the multiple sort. When a multiple key sort is done, the first key named is the first sort. Records then are sorted in order of the second key, within the first sort, and so on. The sort keys are given in the order SORT-STORE, SORT-DIVISION, SORT-DEPARTMENT, and then SORT-CATEGORY. When the sort is complete, the primary order of the file will be by store. Then within each store, the records are sorted by division. Within each division, the records are in department order, and within each department, the records are in category order. The file is sorted on four keys, but only three of them are used. Category is not a control break, but adding category to the sort will cause the records within a department break to print in category order.

The level-1 control break extends from lines 021200 through 024700. It is similar to level-1 logic in earlier programs, with one exception. The logic to START-NEXT-PAGE is not performed as part of START-ONE-REPORT. A new page will be started on each new store, so this logic has been moved down to level 2 where it is performed in START-ONE-STORE.

The level-2 control break, PROCESS-ALL-STORES, extends from lines 024900 to 027800. This has two special features. The logic to START-NEXT-PAGE is performed inside START-ONE-STORE, at line 026300. Usually, this routine is performed as part of START-ONE-REPORT. The store information is printed on a special line, which is defined in WORKING-STORAGE at line 007200. This is named LEGEND-LINE, a name frequently used for an extra line such as this one that appears between the title of a report and the column lines of a report.

The printing of the LEGEND-LINE has been added to the START-NEW-PAGE routine at lines 038300 through 038500.

The END-ONE-STORE logic at line 026500 handles the printing of the store total. This begins at line 026900. A special totaling line is defined in WORKING-STORAGE at lines 010800 through 011600. This line can be filled in with the total type, and the store, division, or department number. The PRINT-STORE-TOTAL logic at line 026900 fills this in with the STORE-TOTAL and appropriate other values, and then it is printed.

The PRINT-STORE-TOTAL logic for the store control break is imitated at line 030000, PRINT-DIVISION-TOTAL, for printing the division total, and at line 033200, PRINT-DEPARTMENT-TOTAL, for printing the department total.

Code, compile, and run slsrpt01.cbl, and look at the sample output. You will see that control breaks are just a repetitive series of steps for each level.

Summary

Control breaks are an important part of reports, and you should know how to use them more effectively. Today, you learned these basics:

process-level-2-control-break
    perform start-level-2-control-break
    perform process-level-3-control-break
        until file at end
           or level-2-control-field not = level-2-current-value
    perform end-level-2
start-level-2
    move level-2-control-field to level-2-current-value.
    move zeroes to level-2 accumulators.
    any other starting actions
end-level-2
    perform process-level-2-accumulators
    perform add-level-2 accumulators to level-1 accumulators
    any other ending actions
process-level-1-control-break
    perform start-level-1
    perform process-level-2-control-break
        until file-at-end
    perform end-level-1
start-level-1
    read first valid record
    move zeroes to level-1-accumulators.
    any other starting actions
end-level-1
    perform process-level-1-accumulators
    any other ending actions

Q&A

Q Is a control break the same as a level break?

A Because control breaks usually are organized in levels, control break and level break sometimes are used interchangeably as terms for a control break.

Workshop

Quiz

1. What is a control break?

2. What is the function of a control break field?

3. What is the function of a control break current value field?

4. What is the function of a control break accumulator?

5. Why is a level-1 control break different from other levels?

Exercises

1. Copy slsrpt01.cbl to slsrpt02.cbl. Modify it so that the division number and department number are printed on each detail line.

Hint: Code in START-ONE-DIVISION and START-ONE-DEPARTMENT needs to be moved to PRINT-THE-RECORD.

2. Copy slsrpt01.cbl to slssum01.cbl. Modify the new program so that no detail lines are printed at all. This will become a sales summary report that prints only the totals for the control breaks.

Hint: The key to this problem is to prevent the printing of the detail line somewhere between lines 035000 and 036300.


Previous chapterNext chapterContents


© Copyright, Macmillan Computer Publishing. All rights reserved.