Teach Yourself COBOL in 21 days, Second Edition

Previous chapterNext chapterContents


- Day 10 -
Printing

Reporting on the data in files by using the printing features of COBOL is one of the main activities of COBOL programs. The reports are what end users see most often, and they are the area where users have the most requests for changes. You'll probably spend more time coding (and modifying) report programs than any other type of program. Acquiring good basics of printing reports on files will serve you throughout your COBOL career.

In today's lesson, you learn about the following topics:

Printing Basics

You already have learned most of the steps for printing, because in COBOL you send data to the printer by writing data to a file. In COBOL, the printer is defined as a file, and it is opened, closed, and written to as though it were a file.

Like any file, the printer file requires both a logical and a physical definition. Listings 10.1 and 10.2 compare the differences between a SELECT statement for a file and the SELECT statement for a print file.

TYPE: Listing 10.1. A SELECT statement for a file.

000400 ENVIRONMENT DIVISION.
000500 INPUT-OUTPUT SECTION.
000600 FILE-CONTROL.
000700     SELECT PHONE-FILE
000800         ASSIGN TO "phone.dat"
000900         ORGANIZATION IS SEQUENTIAL.
001000
001100 DATA DIVISION.

TYPE: Listing 10.2. A SELECT statement for a print file.

000400 ENVIRONMENT DIVISION.
000500 INPUT-OUTPUT SECTION.
000600 FILE-CONTROL.
000700     SELECT PHONE-FILE
000800         ASSIGN TO PRINTER
000900         ORGANIZATION IS LINE SEQUENTIAL.
001000
001100 DATA DIVISION.

The difference between the listings is the ASSIGN clause at line 00800. A normal disk file is assigned to a filename on the disk. A printer file is assigned to the COBOL reserved word PRINTER.

At line 000900, the ORGANIZATION for the printer file is changed to LINE SEQUENTIAL.

A line sequential file is similar to a sequential file, but it usually has carriage return and line feed characters added to the end of each record. These are added automatically every time a record is written. This format is suitable for printing or displaying. The format also is suitable for a file that is to be edited using a text editor. In fact, the source code files that you are editing whenever you write a program are line sequential files. In this case, the printer file is organized as a line sequential file because a carriage return and line feed are "added" at the end of each line and are sent to the printer to cause the print head to return to the left margin (carriage return) and drop down one line (line feed).

ORGANIZATION IS LINE SEQUENTIAL is commonly used in many versions of COBOL for the organization of the printer file, but it is not the only organization. I have also seen ORGANIZATION IS SEQUENTIAL and ORGANIZATION IS PRINTER.

The ASSIGN statement you use varies slightly for different versions of COBOL, usually based on the device name used on your system for the printer. Table 10.1 compares some different versions of COBOL.

Table 10.1. Versions of the ASSIGN clause.

COBOL Version How to ASSIGN to PRINTER
Micro Focus COBOL or Personal COBOL ASSIGN TO PRINTER
LPI COBOL ASSIGN TO PRINT
or
ASSIGN TO PRINTER
ACUCOBOL version 2.0 ASSIGN TO PRINTER
VS COBOL ASSIGN TO "PRINTER"
VAX COBOL ASSIGN TO SYS$PRINT?

New Term: Because the printer is a device that is treated like a file in COBOL programs, a file used for printing is sometimes called a printer file or a printer device file.

On MS-DOS computers, writing a record "into" a printer file actually sends the record directly to the printer attached to your computer. When you write from the printer file, you send characters directly to the printer.

New Term: On larger computers with many users and one or more printers, writing to the printer file actually writes to a temporary file on the disk. When the printer file is closed, the temporary file is passed on to another program that handles the scheduling of the printers. The scheduling program usually is called a spooler or a print queue manager. This program sends the temporary file to the printer.

The second difference between data files and print files is shown in Listings 10.3 and 10.4. A data file uses LABEL RECORDS ARE STANDARD, and a print file uses LABEL RECORDS ARE OMITTED. A printer is a device and does not require labeling (filenames).

TYPE: Listing 10.3. The file definition for a data file.

002000 DATA DIVISION.
002100 FILE SECTION.
002200 FD  PHONE-FILE
002300     LABEL RECORDS ARE STANDARD.
002400 01  PHONE-RECORD.
002500     05  PHONE-LAST-NAME      PIC X(20).
002600     05  PHONE-FIRST-NAME     PIC X(20).
002700     05  PHONE-NUMBER         PIC X(15).
002800     05  PHONE-EXTENSION      PIC X(5).
002900

TYPE: Listing 10.4. The file definition for a printer file.

003000 FD  PRINTER-FILE
003100     LABEL RECORDS ARE OMITTED.
003200 01  PRINTER-RECORD           PIC X(80).
003300

Controlling the Printer

In addition to printing a string of characters on paper, a COBOL program has to tell the printer when to advance one line down the page. It also might have to tell the printer when to advance to the next page.

When a WRITE command is used on a printer file, the command can include instructions to force the printer to advance one or more lines. The syntax for this is the following:

WRITE a-record BEFORE ADVANCING a-number.

The BEFORE ADVANCING phrase causes one or more carriage return and line feed characters to be sent to the printer after the line is printed.

New Term: A carriage return is a command sent to a printer that causes the print head to return to the left margin of the paper.

New Term: A line feed is a command sent to a printer that causes the print head to move down one line.

The carriage return and line feed combination is used to move the print head to the left edge of the paper (carriage return) and down one line (line feed).

The advancing phrase also can be used to force the printer to eject the last page and prepare to start a new one. The advancing command in the following example sends a form feed to the printer after printing a line:

WRITE a-record BEFORE ADVANCING PAGE.

New Term: A form feed is a command sent to a printer that causes the printer to eject the last sheet of paper and prepare to start printing at the top of a new sheet.

You also might advance the paper before printing a line. Table 10.2 compares the effects of various versions of BEFORE ADVANCING and AFTER ADVANCING.

Table 10.2. Controlling the printer with WRITE.

Code Effect
WRITE PRINTER-RECORD BEFORE ADVANCING 1. Sends the characters in PRINTER-RECORD to the printer, then advances the printer one line
WRITE PRINTER-RECORD AFTER ADVANCING 1. Advances the printer one line, then sends the characters in PRINTER-RECORD to the printer
WRITE PRINTER-RECORD BEFORE ADVANCING 5. Sends the characters in PRINTER-RECORD to the printer, then advances the printer five lines
WRITE PRINTER-RECORD AFTER ADVANCING 3. Advances the printer three lines, then sends the characters in PRINTER-RECORD to the printer
WRITE PRINTER-RECORD BEFORE ADVANCING PAGE. Sends the characters in PRINTER-RECORD to the printer, then advances the printer to the next page
WRITE PRINTER-RECORD AFTER ADVANCING PAGE. Advances the printer to the next page, then sends the characters in PRINTER-RECORD to the printer

New Term: The BEFORE ADVANCING and AFTER ADVANCING clauses of the WRITE verb are called carriage control clauses or carriage control information. They control the positioning of the print head before or after a line is printed.

Most earlier COBOL programs use AFTER ADVANCING for carriage control. In fact, if you omit carriage control information when writing to a print file, each WRITE is treated as if you had included AFTER ADVANCING 1.

Most of the examples in this book use BEFORE ADVANCING. BEFORE ADVANCING has advantages for modern printers, particularly laser printers that expect to receive a form feed as the last command. This form feed causes the laser printer to print all of the last data received and eject the last page of the report.

It is a good practice to use either BEFORE or AFTER consistently in all of your code. You will see in more complex printing programs that it's easier to tell which line you are on when BEFORE or AFTER is used consistently in a program.

A Simple Printing Program

The simplest way to illustrate printing is to modify phnadd02.cbl from Appendix A, "Answers," for Day 9, "File I/O," so that it echoes each record to the printer as you add it. Listing 10.5 shows phnadd03.cbl, a modified version of phnadd02.cbl. Make sure that you have a printer attached to your computer, that the printer is on, and that the printer is ready to receive characters to print. Usually the printer will have a READY light that is on. If you run the program when the printer is not ready, it might lock up your computer.

TYPE: Listing 10.5. Echoing to the printer.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. PHNADD03.
000300*--------------------------------------------------
000400* This program creates a new data file if necessary
000500* and adds records to the file from user entered
000600* data. The records are written to the data file
000700* and echoed to the printer.
000800*--------------------------------------------------
000900 ENVIRONMENT DIVISION.
001000 INPUT-OUTPUT SECTION.
001100 FILE-CONTROL.
001200     SELECT PHONE-FILE
001300         ASSIGN TO "phone.dat"
001400         ORGANIZATION IS SEQUENTIAL.
001500
001600     SELECT PRINTER-FILE
001700         ASSIGN TO PRINTER
001800         ORGANIZATION IS LINE SEQUENTIAL.
001900
002000 DATA DIVISION.
002100 FILE SECTION.
002200 FD  PHONE-FILE
002300     LABEL RECORDS ARE STANDARD.
002400 01  PHONE-RECORD.
002500     05  PHONE-LAST-NAME      PIC X(20).
002600     05  PHONE-FIRST-NAME     PIC X(20).
002700     05  PHONE-NUMBER         PIC X(15).
002800     05  PHONE-EXTENSION      PIC X(5).
002900
003000 FD  PRINTER-FILE
003100     LABEL RECORDS ARE OMITTED.
003200 01  PRINTER-RECORD           PIC X(80).
003300
003400 WORKING-STORAGE SECTION.
003500
003600* Variables for SCREEN ENTRY
003700 01  PROMPT-1               PIC X(9)  VALUE "Last Name".
003800 01  PROMPT-2               PIC X(10) VALUE "First Name".
003900 01  PROMPT-3               PIC X(6)  VALUE "Number".
004000 01  PROMPT-4               PIC X(9)  VALUE "Extension".
004100
004200 01  YES-NO                 PIC X.
004300 01  ENTRY-OK               PIC X.
004400
004500 PROCEDURE DIVISION.
004600 MAIN-LOGIC SECTION.
004700 PROGRAM-BEGIN.
004800
004900     PERFORM OPENING-PROCEDURE.
005000     MOVE "Y" TO YES-NO.
005100     PERFORM ADD-RECORDS
005200         UNTIL YES-NO = "N".
005300     PERFORM CLOSING-PROCEDURE.
005400
005500 PROGRAM-DONE.
005600     STOP RUN.
005700
005800* OPENING AND CLOSING
005900
006000 OPENING-PROCEDURE.
006100     OPEN EXTEND PHONE-FILE.
006200     OPEN OUTPUT PRINTER-FILE.
006300
006400 CLOSING-PROCEDURE.
006500     CLOSE PHONE-FILE.
006600     MOVE SPACE TO PRINTER-RECORD.
006700     WRITE PRINTER-RECORD BEFORE ADVANCING PAGE.
006800     CLOSE PRINTER-FILE.
006900
007000 ADD-RECORDS.
007100     MOVE "N" TO ENTRY-OK.
007200     PERFORM GET-FIELDS
007300        UNTIL ENTRY-OK = "Y".
007400     PERFORM ADD-THIS-RECORD.
007500     PERFORM GO-AGAIN.
007600
007700 GET-FIELDS.
007800     MOVE SPACE TO PHONE-RECORD.
007900     DISPLAY PROMPT-1 " ? ".
008000     ACCEPT PHONE-LAST-NAME.
008100     DISPLAY PROMPT-2 " ? ".
008200     ACCEPT PHONE-FIRST-NAME.
008300     DISPLAY PROMPT-3 " ? ".
008400     ACCEPT PHONE-NUMBER.
008500     DISPLAY PROMPT-4 " ? ".
008600     ACCEPT PHONE-EXTENSION.
008700     PERFORM VALIDATE-FIELDS.
008800
008900 VALIDATE-FIELDS.
009000     MOVE "Y" TO ENTRY-OK.
009100     IF PHONE-LAST-NAME = SPACE
009200         DISPLAY "LAST NAME MUST BE ENTERED"
009300         MOVE "N" TO ENTRY-OK.
009400
009500 ADD-THIS-RECORD.
009600     MOVE PHONE-RECORD TO PRINTER-RECORD.
009700     WRITE PHONE-RECORD.
009800     WRITE PRINTER-RECORD BEFORE ADVANCING 1.
009900
010000 GO-AGAIN.
010100     DISPLAY "GO AGAIN?".
010200     ACCEPT YES-NO.
010300     IF YES-NO = "y"
010400         MOVE "Y" TO YES-NO.
010500     IF YES-NO NOT = "Y"
010600         MOVE "N" TO YES-NO.
010700

The following is the on-screen output of phnadd03.cbl:

OUTPUT:

Last Name ?
MARTINSON
First Name ?
RICKY
Number ?
555-1234
Extension ?
405
GO AGAIN?
Y
Last Name ?
JONES
First Name ?
JOHN
Number ?
555-4321
Extension ?
1122
GO AGAIN?
N

C>
C>

This is the printed output of phnadd03.cbl:

OUTPUT:

MARTINSON           RICKY               555-1234       405
JONES               JOHN                555-4321       1122

ANALYSIS: The SELECT and FD for the PRINTER-FILE are at lines 001600 through 001800 and lines 002900 through 003100. No record for the PRINTER-FILE is created as a variable because there is no need for fields within the PRINTER-RECORD, as you will learn later.

The OPENING-PROCEDURE is modified to open the PRINTER-FILE. Printer files can be opened only in OUTPUT mode, as shown at line 006100.

Before you look at the closing procedure, check lines 009600 and 009800 in ADD-THIS-RECORD. PRINTER-RECORD is filled in by moving the PHONE-RECORD to it at line 009600. Then the PRINTER-RECORD is written at line 009800.

The closing procedure at line 006400 seems odd. Just before the printer file is closed, a record of spaces is written, followed by a form feed (BEFORE ADVANCING PAGE). This forces the last page out of the printer. It doesn't hurt to do this on a standard dot-matrix printer, and it's necessary for laser printers. As I mentioned before, laser printers expect a form feed as the last command.

The only information put in the PRINTER-RECORD is either a complete copy of the PHONE-RECORD at line 009600 or SPACE at line 006400, so there is no need for the PRINTER-RECORD to be created as a structure.

A Simple Report Program

The example printing program is a variation of phnadd02.cbl from Appendix A. It echoes records as they are added to the file. Most COBOL printing programs (sometimes called report programs) are designed to read the contents of an existing file and print the information.

Printing programs, which are also called report programs, are similar to display programs such as phnlst01.cbl (see Appendix A).

You can derive the first version of a printing program that prints all records in a file, phnprt01.cbl, almost directly from phnlst02.cbl. You might want to compare the report program in Listing 10.6 to phnprt01.cbl.

TYPE: Listing 10.6. A report program.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. PHNPRT01.
000300*--------------------------------------------------
000400* This program prints the contents of the
000500* phone file.
000600*--------------------------------------------------
000700 ENVIRONMENT DIVISION.
000800 INPUT-OUTPUT SECTION.
000900 FILE-CONTROL.
001000     SELECT OPTIONAL PHONE-FILE
001100*or  SELECT PHONE-FILE
001200         ASSIGN TO "phone.dat"
001300*or      ASSIGN TO "phone"
001400         ORGANIZATION IS SEQUENTIAL.
001500
001600     SELECT PRINTER-FILE
001700         ASSIGN TO PRINTER
001800         ORGANIZATION IS LINE SEQUENTIAL.
001900
002000 DATA DIVISION.
002100 FILE SECTION.
002200 FD  PHONE-FILE
002300     LABEL RECORDS ARE STANDARD.
002400 01  PHONE-RECORD.
002500     05  PHONE-LAST-NAME      PIC X(20).
002600     05  PHONE-FIRST-NAME     PIC X(20).
002700     05  PHONE-NUMBER         PIC X(15).
002800     05  PHONE-EXTENSION      PIC X(5).
002900
003000 FD  PRINTER-FILE
003100     LABEL RECORDS ARE OMITTED.
003200 01  PRINTER-RECORD           PIC X(80).
003300
003400 WORKING-STORAGE SECTION.
003500
003600* Structure for PRINTING
003700 01  FIELDS-TO-PRINT.
003800     05  PROMPT-1             PIC X(4) VALUE "Lst:".
003900     05  PRINT-LAST-NAME      PIC X(20).
004000     05  PROMPT-2             PIC X(4) VALUE "1st:".
004100     05  PRINT-FIRST-NAME     PIC X(20).
004200     05  PROMPT-3             PIC X(3) VALUE "NO:".
004300     05  PRINT-NUMBER         PIC X(15).
004400     05  PROMPT-4             PIC X(4) VALUE "Xtn:".
004500     05  PRINT-EXTENSION      PIC X(5).
004600
004700 01  END-OF-FILE            PIC X.
004800
004900 01  PRINT-LINES           PIC 99.
005000
005100 PROCEDURE DIVISION.
005200 MAIN-LOGIC SECTION.
005300 PROGRAM-BEGIN.
005400
005500     PERFORM OPENING-PROCEDURE.
005600     MOVE ZEROES TO PRINT-LINES.
005700     MOVE "N" TO END-OF-FILE.
005800     PERFORM READ-NEXT-RECORD.
005900     PERFORM PRINT-RECORDS
006000         UNTIL END-OF-FILE = "Y".
006100     PERFORM CLOSING-PROCEDURE.
006200
006300 PROGRAM-DONE.
006400     STOP RUN.
006500
006600 OPENING-PROCEDURE.
006700     OPEN INPUT PHONE-FILE.
006800     OPEN OUTPUT PRINTER-FILE.
006900
007000 CLOSING-PROCEDURE.
007100     CLOSE PHONE-FILE.
007200     MOVE SPACE TO PRINTER-RECORD.
007300     WRITE PRINTER-RECORD BEFORE ADVANCING PAGE.
007400     CLOSE PRINTER-FILE.
007500
007600 PRINT-RECORDS.
007700     PERFORM PRINT-FIELDS.
007800     PERFORM READ-NEXT-RECORD.
007900
008000 PRINT-FIELDS.
008100     IF PRINT-LINES = 55
008200         PERFORM NEW-PAGE.
008300     MOVE PHONE-LAST-NAME TO PRINT-LAST-NAME.
008400     MOVE PHONE-FIRST-NAME TO PRINT-FIRST-NAME.
008500     MOVE PHONE-NUMBER TO PRINT-NUMBER.
008600     MOVE PHONE-EXTENSION TO PRINT-EXTENSION.
008700     MOVE FIELDS-TO-PRINT TO PRINTER-RECORD.
008800     WRITE PRINTER-RECORD BEFORE ADVANCING 1.
008900
009000     ADD 1 TO PRINT-LINES.
009100
009200 READ-NEXT-RECORD.
009300     READ PHONE-FILE NEXT RECORD
009400        AT END
009500        MOVE "Y" TO END-OF-FILE.
009600
009700 NEW-PAGE.
009800     MOVE SPACE TO PRINTER-RECORD.
009900     WRITE PRINTER-RECORD BEFORE ADVANCING PAGE.
010000     MOVE ZEROES TO PRINT-LINES.
010100

The printer output of phnprt01.cbl looks something like the following:

OUTPUT:

Lst:MARTINSON        1st:RICKY            NO:555-1234       Xtn:405
Lst:JONES            1st:JOHN             NO:555-4321       Xtn:1122
Lst:Smith            1st:Michael          NO:(213) 555-7075 Xtn:476
Lst:Fitzhugh         1st:Adrianne         NO:(202) 555-7017 Xtn:23

ANALYSIS: A printer file has been added in FILE-CONTROL and in the FILE SECTION of the DATA DIVISION. The OPENING-PROCEDURE and CLOSING-PROCEDURE paragraphs include an appropriate OPEN and CLOSE for the PRINTER-FILE, including a closing form feed to eject the last page. The DISPLAY-FIELDS paragraph in phnlst02.cbl has been changed to a PRINT-FIELDS paragraph, which loads the fields and prints them.

One interesting area of change is at lines 008100 and 008200. Here is the original phnlst02.cbl (ignoring line numbering differences):

007000     IF SCREEN-LINES = 15
007100         PERFORM PRESS-ENTER.

This is the phnprt01.cbl program:

008100     IF PRINT-LINES = 55
008200         PERFORM NEW-PAGE.

The SCREEN-LINES variable has been changed to a PRINT-LINES variable, and the size of a print page has been set to 55. A print page usually has 66 (sometimes 68) lines on which you can print data. Laser printers might have fewer lines. If you print from the top to the bottom of the page, the output might appear cluttered, so it is common to allow a margin. I have chosen 55 lines as the breakpoint.

In the original phnlst02.cbl, the user is asked to press Enter to continue, as in the following:

008500 PRESS-ENTER.
008600     DISPLAY "Press ENTER to continue . . ".
008700     ACCEPT A-DUMMY.
008800     MOVE ZEROES TO SCREEN-LINES.

In a printing program, this pause between screens is changed into a page break (form feed):

009700 NEW-PAGE.
009800     MOVE SPACE TO PRINTER-RECORD.
009900     WRITE PRINTER-RECORD BEFORE ADVANCING PAGE.
010000     MOVE ZEROES TO PRINT-LINES.

Code and compile phnprt01.cbl. If you have not done so yet, code and compile phnadd02.cbl from Appendix A. Delete the old data file, phone.dat, and use phnadd02.cbl to create a new file. Then add several phone numbers to the phone.dat file, and run phnprt01.cbl to print these entries. If you have more than 55 entries, phnprt01.cbl inserts a page break after printing 55 entries and starts a new page for the remaining entries.

If you don't feel like entering this many phone numbers, you can use the information in the next section to learn how to build test data to test your printing program.

Creating Test Data

Creating test data is one way of setting up proper conditions to test COBOL programs. The main thing to keep in mind is that you want the test data to provide fields that will test all the necessary conditions in your program. For phnprt01.cbl, you need to test these conditions:

The test data doesn't have to make sense, as long as it tests those conditions.

The program phnbld01.cbl in Listing 10.7 creates a number of dummy records, based on a quantity entered by the user.

TYPE: Listing 10.7. Creating test data for phnprt01.cbl.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. PHNBLD01.
000300*--------------------------------------------------
000400* This program creates a new data file and fills
000500* it with test data.
000600* The test records are written to the data file
000700* and echoed to the printer.
000800*--------------------------------------------------
000900 ENVIRONMENT DIVISION.
001000 INPUT-OUTPUT SECTION.
001100 FILE-CONTROL.
001200     SELECT PHONE-FILE
001300         ASSIGN TO "phone.dat"
001400         ORGANIZATION IS SEQUENTIAL.
001500
001600     SELECT PRINTER-FILE
001700         ASSIGN TO PRINTER
001800         ORGANIZATION IS LINE SEQUENTIAL.
001900
002000 DATA DIVISION.
002100 FILE SECTION.
002200 FD  PHONE-FILE
002300     LABEL RECORDS ARE STANDARD.
002400 01  PHONE-RECORD.
002500     05  PHONE-LAST-NAME      PIC X(20).
002600     05  PHONE-FIRST-NAME     PIC X(20).
002700     05  PHONE-NUMBER         PIC X(15).
002800     05  PHONE-EXTENSION      PIC X(5).
002900
003000 FD  PRINTER-FILE
003100     LABEL RECORDS ARE OMITTED.
003200 01  PRINTER-RECORD           PIC X(80).
003300
003400 WORKING-STORAGE SECTION.
003500
003600 01  HOW-MANY                 PIC 999.
003700 01  ENTRY-FIELD              PIC ZZZ.
003800
003900 01  PRINT-LINES              PIC 99 VALUE ZEROES.
004000 01  FORMATTED-NUMBER.
004100     05  FILLER              PIC X(6) VALUE "(404) ".
004200     05  FILLER              PIC X(4) VALUE "555-".
004300     05  PHONE-COUNTER       PIC 9(4) VALUE ZERO.
004400
004500 PROCEDURE DIVISION.
004600 MAIN-LOGIC SECTION.
004700 PROGRAM-BEGIN.
004800
004900     PERFORM OPENING-PROCEDURE.
005000     PERFORM GET-HOW-MANY.
005100     MOVE ZEROES TO PRINT-LINES.
005200     PERFORM ADD-RECORDS
005300         VARYING PHONE-COUNTER
005400         FROM 1 BY 1 UNTIL
005500          PHONE-COUNTER > HOW-MANY.
005600     PERFORM CLOSING-PROCEDURE.
005700
005800 PROGRAM-DONE.
005900     STOP RUN.
006000
006100* OPENING AND CLOSING
006200
006300 OPENING-PROCEDURE.
006400     OPEN OUTPUT PHONE-FILE.
006500     OPEN OUTPUT PRINTER-FILE.
006600
006700 CLOSING-PROCEDURE.
006800     CLOSE PHONE-FILE.
006900     MOVE SPACE TO PRINTER-RECORD.
007000     WRITE PRINTER-RECORD BEFORE ADVANCING PAGE.
007100     CLOSE PRINTER-FILE.
007200
007300 GET-HOW-MANY.
007400     DISPLAY "How many test entries (1-999)".
007500     ACCEPT ENTRY-FIELD.
007600*or  ACCEPT ENTRY-FIELD WITH CONVERSION.
007700     MOVE ENTRY-FIELD TO HOW-MANY.
007800
007900 ADD-RECORDS.
008000     PERFORM FORMAT-THE-RECORD.
008100     PERFORM ADD-THIS-RECORD.
008200
008300 FORMAT-THE-RECORD.
008400     MOVE "Joshua------------X" TO PHONE-FIRST-NAME.
008500     MOVE "Johnson------------X" TO PHONE-LAST-NAME.
008600     MOVE "12345" TO PHONE-EXTENSION.
008700     MOVE FORMATTED-NUMBER TO PHONE-NUMBER.
008800
008900 ADD-THIS-RECORD.
009000     WRITE PHONE-RECORD.
009100     PERFORM PRINT-THIS-RECORD.
009200
009300 PRINT-THIS-RECORD.
009400     IF PRINT-LINES NOT < 55
009500         PERFORM NEW-PAGE.
009600     MOVE PHONE-RECORD TO PRINTER-RECORD.
009700     WRITE PRINTER-RECORD BEFORE ADVANCING 1.
009800     ADD 1 TO PRINT-LINES.
009900
010000 NEW-PAGE.
010100     MOVE SPACE TO PRINTER-RECORD.
010200     WRITE PRINTER-RECORD BEFORE ADVANCING PAGE.
010300     MOVE ZEROES TO PRINT-LINES.
010400

The following output of phnbld01.cbl prints when you request 77 entries:

OUTPUT:

Johnson------------XJoshua------------X(404) 555-0001 12345
Johnson------------XJoshua------------X(404) 555-0002 12345
Johnson------------XJoshua------------X(404) 555-0003 12345
Johnson------------XJoshua------------X(404) 555-0004 12345
Johnson------------XJoshua------------X(404) 555-0005 12345
Johnson------------XJoshua------------X(404) 555-0006 12345
Johnson------------XJoshua------------X(404) 555-0007 12345
Johnson------------XJoshua------------X(404) 555-0008 12345
Johnson------------XJoshua------------X(404) 555-0009 12345
Johnson------------XJoshua------------X(404) 555-0010 12345
Johnson------------XJoshua------------X(404) 555-0011 12345
Johnson------------XJoshua------------X(404) 555-0012 12345
Johnson------------XJoshua------------X(404) 555-0013 12345
Johnson------------XJoshua------------X(404) 555-0014 12345
Johnson------------XJoshua------------X(404) 555-0015 12345
Johnson------------XJoshua------------X(404) 555-0016 12345
Johnson------------XJoshua------------X(404) 555-0017 12345
Johnson------------XJoshua------------X(404) 555-0018 12345
Johnson------------XJoshua------------X(404) 555-0019 12345
Johnson------------XJoshua------------X(404) 555-0020 12345
Johnson------------XJoshua------------X(404) 555-0021 12345
Johnson------------XJoshua------------X(404) 555-0022 12345
Johnson------------XJoshua------------X(404) 555-0023 12345
Johnson------------XJoshua------------X(404) 555-0024 12345
Johnson------------XJoshua------------X(404) 555-0025 12345
Johnson------------XJoshua------------X(404) 555-0026 12345
Johnson------------XJoshua------------X(404) 555-0027 12345
Johnson------------XJoshua------------X(404) 555-0028 12345
Johnson------------XJoshua------------X(404) 555-0029 12345
Johnson------------XJoshua------------X(404) 555-0030 12345
Johnson------------XJoshua------------X(404) 555-0031 12345
Johnson------------XJoshua------------X(404) 555-0032 12345
Johnson------------XJoshua------------X(404) 555-0033 12345
Johnson------------XJoshua------------X(404) 555-0034 12345
Johnson------------XJoshua------------X(404) 555-0035 12345
Johnson------------XJoshua------------X(404) 555-0036 12345
Johnson------------XJoshua------------X(404) 555-0037 12345
Johnson------------XJoshua------------X(404) 555-0038 12345
Johnson------------XJoshua------------X(404) 555-0039 12345
Johnson------------XJoshua------------X(404) 555-0040 12345
Johnson------------XJoshua------------X(404) 555-0041 12345
Johnson------------XJoshua------------X(404) 555-0042 12345
Johnson------------XJoshua------------X(404) 555-0043 12345
Johnson------------XJoshua------------X(404) 555-0044 12345
Johnson------------XJoshua------------X(404) 555-0045 12345
Johnson------------XJoshua------------X(404) 555-0046 12345
Johnson------------XJoshua------------X(404) 555-0047 12345
Johnson------------XJoshua------------X(404) 555-0048 12345
Johnson------------XJoshua------------X(404) 555-0049 12345
Johnson------------XJoshua------------X(404) 555-0050 12345
Johnson------------XJoshua------------X(404) 555-0051 12345
Johnson------------XJoshua------------X(404) 555-0052 12345
Johnson------------XJoshua------------X(404) 555-0053 12345
Johnson------------XJoshua------------X(404) 555-0054 12345
Johnson------------XJoshua------------X(404) 555-0055 12345

(New page starts here.)

Johnson------------XJoshua------------X(404) 555-0056 12345
Johnson------------XJoshua------------X(404) 555-0057 12345
Johnson------------XJoshua------------X(404) 555-0058 12345
Johnson------------XJoshua------------X(404) 555-0059 12345
Johnson------------XJoshua------------X(404) 555-0060 12345
Johnson------------XJoshua------------X(404) 555-0061 12345
Johnson------------XJoshua------------X(404) 555-0062 12345
Johnson------------XJoshua------------X(404) 555-0063 12345
Johnson------------XJoshua------------X(404) 555-0064 12345
Johnson------------XJoshua------------X(404) 555-0065 12345
Johnson------------XJoshua------------X(404) 555-0066 12345
Johnson------------XJoshua------------X(404) 555-0067 12345
Johnson------------XJoshua------------X(404) 555-0068 12345
Johnson------------XJoshua------------X(404) 555-0069 12345
Johnson------------XJoshua------------X(404) 555-0070 12345
Johnson------------XJoshua------------X(404) 555-0071 12345
Johnson------------XJoshua------------X(404) 555-0072 12345
Johnson------------XJoshua------------X(404) 555-0073 12345
Johnson------------XJoshua------------X(404) 555-0074 12345
Johnson------------XJoshua------------X(404) 555-0075 12345
Johnson------------XJoshua------------X(404) 555-0076 12345
Johnson------------XJoshua------------X(404) 555-0077 12345

ANALYSIS: Each record is identical except for the last four digits of the phone number field. The PHONE-FIRST-NAME field is filled in with Joshua------------X to test the full 20 characters of the printed field. Similarly, the PHONE-LAST-NAME field is filled in with Johnson------------X to test the printing of that field, and the PHONE-EXTENSION is filled in with 12345.

The trick of creating a different phone number is taken care of by the structure at lines 004000 through 004400. This sets up a structure containing (404) and 555-, followed by a PHONE-COUNTER. At line 005000, a routine is performed to ask the user how many test records to create. At lines 005200 through 005500, the routine to add records to the file is performed while varying the PHONE-COUNTER from 1 through HOW-MANY entries.

At lines 08300 through 008700, the record is filled in. When the record is added in the routine at 008900, it also is printed, ensuring that you have an accurate record of what exactly was placed in the file.

Edit, compile, and run phnbld01.cbl to create a test file large enough to test the printing capabilities of phnprt01.cbl. Then run phnprt01.cbl to see an output report with a page break in it.

By examining the output, you verify that phnprt01.cbl passes all these test criteria:

The following output of phnprt01.cbl using 77 entries was created by phnbld01.cbl:

OUTPUT:

Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0001 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0002 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0003 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0004 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0005 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0006 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0007 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0008 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0009 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0010 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0011 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0012 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0013 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0014 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0015 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0016 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0017 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0018 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0019 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0020 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0021 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0022 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0023 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0024 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0025 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0026 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0027 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0028 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0029 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0030 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0031 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0032 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0033 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0034 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0035 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0036 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0037 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0038 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0039 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0040 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0041 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0042 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0043 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0044 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0045 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0046 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0047 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0048 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0049 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0050 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0051 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0052 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0053 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0054 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0055 Xtn:12345

(New page starts here.)

Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0056 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0057 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0058 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0059 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0060 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0061 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0062 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0063 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0064 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0065 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0066 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0067 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0068 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0069 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0070 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0071 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0072 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0073 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0074 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0075 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0076 Xtn:12345
Lst:Johnson------------X1st:Joshua------------XNO:(404) 555-0077 Xtn:12345

Examination of the output does reveal a problem. The fields are all jammed end-to-end, with no space between the end of one field and the beginning of the prompt for the next field.

Laying Out a Report

Usually, a COBOL report program looks more like the example lines in Figure 10.1.

Figure 10.1.
The layout of a COBOL report program.

COBOL report layouts usually are worked out on a printer spacing sheet. A blank printer spacing sheet is shown in Figure 10.2. The printer spacing sheet uses 80 columns (or 132 for wide-carriage printers) to represent printing positions. You can buy these at a stationery shop or simply adapt graph paper to do the same job.

The spacing sheet for this sample report program is shown in Figure 10.3. The layout is done by hand and helps to calculate the spacing of the output data in a report. When you have determined the spacing, you can work out what the data should look like in the program.

Figure 10.2.
A printer spacing sheet.

Figure 10.3.
A COBOL printer layout sheet.

The main part of the report is detail lines holding enough space for each field, with a space between each field, as shown in Listing 10.8.

TYPE: Listing 10.8. The structure for the report detail.

005400
005500 01 DETAIL-LINE.
005600     05  PRINT-LAST-NAME      PIC X(20).
005700     05  FILLER               PIC X(1) VALUE SPACE.
005800     05  PRINT-FIRST-NAME     PIC X(20).
005900     05  FILLER               PIC X(1) VALUE SPACE.
006000     05  PRINT-NUMBER         PIC X(15).
006100     05  FILLER               PIC X(1) VALUE SPACE.
006200     05  PRINT-EXTENSION      PIC X(5).
006300

The top line of the report is a title line; the structure shown in Listing 10.9 holds the title for the report and an incrementing page number.

TYPE: Listing 10.9. The structure for the title.

003700 01  TITLE-LINE.
003800     05  FILLER               PIC X(21) VALUE SPACE.
003900     05  FILLER               PIC X(17) VALUE
004000     "PHONE BOOK REPORT".
004100     05  FILLER              PIC X(15) VALUE SPACE.
004200     05  FILLER              PIC X(5) VALUE "Page:".
004300     05  PRINT-PAGE-NUMBER   PIC ZZZZ9.
004400

The second line at the top of each page of the report is for column headings; the structure shown in Listing 10.10 is used to print the columns. The column headings do not change, so all the values in COLUMN-HEADINGS are defined as FILLER.

TYPE: Listing 10.10. The column headings.

004600 01  COLUMN-HEADINGS.
004700     05  FILLER               PIC X(9)  VALUE "Last Name".
004800     05  FILLER               PIC X(12) VALUE SPACE.
004900     05  FILLER               PIC X(10) VALUE "First Name".
005000     05  FILLER               PIC X(11) VALUE SPACE.
005100     05  FILLER               PIC X(6)  VALUE "Number".
005200     05  FILLER               PIC X(10) VALUE SPACE.
005300     05  FILLER               PIC X(4)  VALUE "Ext.".

With the data structure defined, you now can consider the program. Printing the information differs only slightly from phnprt01.cbl. The difference is that the logic to start another page must include ending the last page by inserting a form feed, incrementing the page number, and then printing the title line and the column heading line.

Starting a new page is really two separate problems, because first you must end the old page and then start the new one. The new page logic has to be broken into two pieces because you need to be able to start a new page at the beginning of the report (print the title and column headings) without ending an old page (insert a form feed).

Listing 10.11 is the program that results from this modification to the layout and logic, and it also includes some new features.

TYPE: Listing 10.11. The final report program.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. PHNPRT02.
000300*--------------------------------------------------
000400* This program prints the contents of the
000500* phone file.
000600*--------------------------------------------------
000700 ENVIRONMENT DIVISION.
000800 INPUT-OUTPUT SECTION.
000900 FILE-CONTROL.
001000     SELECT OPTIONAL PHONE-FILE
001100*or  SELECT PHONE-FILE
001200         ASSIGN TO "phone.dat"
001300*or      ASSIGN TO "phone"
001400         ORGANIZATION IS SEQUENTIAL.
001500
001600     SELECT PRINTER-FILE
001700         ASSIGN TO PRINTER
001800         ORGANIZATION IS LINE SEQUENTIAL.
001900
002000 DATA DIVISION.
002100 FILE SECTION.
002200 FD  PHONE-FILE
002300     LABEL RECORDS ARE STANDARD.
002400 01  PHONE-RECORD.
002500     05  PHONE-LAST-NAME      PIC X(20).
002600     05  PHONE-FIRST-NAME     PIC X(20).
002700     05  PHONE-NUMBER         PIC X(15).
002800     05  PHONE-EXTENSION      PIC X(5).
002900
003000 FD  PRINTER-FILE
003100     LABEL RECORDS ARE OMITTED.
003200 01  PRINTER-RECORD           PIC X(80).
003300
003400 WORKING-STORAGE SECTION.
003500
003600* Structure for printing a title line
003700 01  TITLE-LINE.
003800     05  FILLER               PIC X(21) VALUE SPACE.
003900     05  FILLER               PIC X(17) VALUE
004000     "PHONE BOOK REPORT".
004100     05  FILLER              PIC X(15) VALUE SPACE.
004200     05  FILLER              PIC X(5) VALUE "Page:".
004300     05  PRINT-PAGE-NUMBER   PIC ZZZZ9.
004400
004500* Structure for printing a column heading
004600 01  COLUMN-HEADINGS.
004700     05  FILLER               PIC X(9)  VALUE "Last Name".
004800     05  FILLER               PIC X(12) VALUE SPACE.
004900     05  FILLER               PIC X(10) VALUE "First Name".
005000     05  FILLER               PIC X(11) VALUE SPACE.
005100     05  FILLER               PIC X(6)  VALUE "Number".
005200     05  FILLER               PIC X(10) VALUE SPACE.
005300     05  FILLER               PIC X(4)  VALUE "Ext.".
005400
005500 01 DETAIL-LINE.
005600     05  PRINT-LAST-NAME      PIC X(20).
005700     05  FILLER               PIC X(1) VALUE SPACE.
005800     05  PRINT-FIRST-NAME     PIC X(20).
005900     05  FILLER               PIC X(1) VALUE SPACE.
006000     05  PRINT-NUMBER         PIC X(15).
006100     05  FILLER               PIC X(1) VALUE SPACE.
006200     05  PRINT-EXTENSION      PIC X(5).
006300
006400 01  END-OF-FILE            PIC X.
006500
006600 01  PRINT-LINES           PIC 99.
006700 01  PAGE-NUMBER           PIC 9(5).
006800
006900 PROCEDURE DIVISION.
007000 MAIN-LOGIC SECTION.
007100 PROGRAM-BEGIN.
007200
007300     PERFORM OPENING-PROCEDURE.
007400     MOVE ZEROES TO PRINT-LINES
007500                    PAGE-NUMBER.
007600     PERFORM START-NEW-PAGE.
007700     MOVE "N" TO END-OF-FILE.
007800     PERFORM READ-NEXT-RECORD.
007900     IF END-OF-FILE = "Y"
008000         MOVE "No records found" TO PRINTER-RECORD
008100         WRITE PRINTER-RECORD BEFORE ADVANCING 1.
008200     PERFORM PRINT-RECORDS
008300         UNTIL END-OF-FILE = "Y".
008400     PERFORM CLOSING-PROCEDURE.
008500
008600 PROGRAM-DONE.
008700     STOP RUN.
008800
008900 OPENING-PROCEDURE.
009000     OPEN INPUT PHONE-FILE.
009100     OPEN OUTPUT PRINTER-FILE.
009200
009300 CLOSING-PROCEDURE.
009400     CLOSE PHONE-FILE.
009500     PERFORM END-LAST-PAGE.
009600     CLOSE PRINTER-FILE.
009700
009800 PRINT-RECORDS.
009900     PERFORM PRINT-FIELDS.
010000     PERFORM READ-NEXT-RECORD.
010100
010200 PRINT-FIELDS.
010300     IF PRINT-LINES NOT < 55
010400         PERFORM NEXT-PAGE.
010500     MOVE PHONE-LAST-NAME TO PRINT-LAST-NAME.
010600     MOVE PHONE-FIRST-NAME TO PRINT-FIRST-NAME.
010700     MOVE PHONE-NUMBER TO PRINT-NUMBER.
010800     MOVE PHONE-EXTENSION TO PRINT-EXTENSION.
010900     MOVE DETAIL-LINE TO PRINTER-RECORD.
011000     WRITE PRINTER-RECORD BEFORE ADVANCING 1.
011100
011200     ADD 1 TO PRINT-LINES.
011300
011400 READ-NEXT-RECORD.
011500     READ PHONE-FILE NEXT RECORD
011600        AT END
011700        MOVE "Y" TO END-OF-FILE.
011800
011900 NEXT-PAGE.
012000     PERFORM END-LAST-PAGE.
012100     PERFORM START-NEW-PAGE.
012200
012300 START-NEW-PAGE.
012400     ADD 1 TO PAGE-NUMBER.
012500     MOVE PAGE-NUMBER TO PRINT-PAGE-NUMBER.
012600     MOVE TITLE-LINE TO PRINTER-RECORD.
012700     WRITE PRINTER-RECORD BEFORE ADVANCING 2.
012800     MOVE COLUMN-HEADINGS TO PRINTER-RECORD.
012900     WRITE PRINTER-RECORD BEFORE ADVANCING 2.
013000     MOVE 4 TO PRINT-LINES.
013100
013200 END-LAST-PAGE.
013300     MOVE SPACE TO PRINTER-RECORD.
013400     WRITE PRINTER-RECORD BEFORE ADVANCING PAGE.
013500     MOVE ZEROES TO PRINT-LINES.
013600

The following is output from phnprt02.cbl when run against a test data file containing 77 entries created with phnbld01.cbl:

OUTPUT:

                     PHONE BOOK REPORT               Page:    1

Last Name            First Name           Number          Ext.
Johnson------------X Joshua------------X (404) 555-0001  12345
Johnson------------X Joshua------------X (404) 555-0002  12345
Johnson------------X Joshua------------X (404) 555-0003  12345
Johnson------------X Joshua------------X (404) 555-0004  12345
Johnson------------X Joshua------------X (404) 555-0005  12345
Johnson------------X Joshua------------X (404) 555-0006  12345
Johnson------------X Joshua------------X (404) 555-0007  12345
Johnson------------X Joshua------------X (404) 555-0008  12345
Johnson------------X Joshua------------X (404) 555-0009  12345
Johnson------------X Joshua------------X (404) 555-0010  12345
Johnson------------X Joshua------------X (404) 555-0011  12345
Johnson------------X Joshua------------X (404) 555-0012  12345
Johnson------------X Joshua------------X (404) 555-0013  12345
Johnson------------X Joshua------------X (404) 555-0014  12345
Johnson------------X Joshua------------X (404) 555-0015  12345
Johnson------------X Joshua------------X (404) 555-0016  12345
Johnson------------X Joshua------------X (404) 555-0017  12345
Johnson------------X Joshua------------X (404) 555-0018  12345
Johnson------------X Joshua------------X (404) 555-0019  12345
Johnson------------X Joshua------------X (404) 555-0020  12345
Johnson------------X Joshua------------X (404) 555-0021  12345
Johnson------------X Joshua------------X (404) 555-0022  12345
Johnson------------X Joshua------------X (404) 555-0023  12345
Johnson------------X Joshua------------X (404) 555-0024  12345
Johnson------------X Joshua------------X (404) 555-0025  12345
Johnson------------X Joshua------------X (404) 555-0026  12345
Johnson------------X Joshua------------X (404) 555-0027  12345
Johnson------------X Joshua------------X (404) 555-0028  12345
Johnson------------X Joshua------------X (404) 555-0029  12345
Johnson------------X Joshua------------X (404) 555-0030  12345
Johnson------------X Joshua------------X (404) 555-0031  12345
Johnson------------X Joshua------------X (404) 555-0032  12345
Johnson------------X Joshua------------X (404) 555-0033  12345
Johnson------------X Joshua------------X (404) 555-0034  12345
Johnson------------X Joshua------------X (404) 555-0035  12345
Johnson------------X Joshua------------X (404) 555-0036  12345
Johnson------------X Joshua------------X (404) 555-0037  12345
Johnson------------X Joshua------------X (404) 555-0038  12345
Johnson------------X Joshua------------X (404) 555-0039  12345
Johnson------------X Joshua------------X (404) 555-0040  12345
Johnson------------X Joshua------------X (404) 555-0041  12345
Johnson------------X Joshua------------X (404) 555-0042  12345
Johnson------------X Joshua------------X (404) 555-0043  12345
Johnson------------X Joshua------------X (404) 555-0044  12345
Johnson------------X Joshua------------X (404) 555-0045  12345
Johnson------------X Joshua------------X (404) 555-0046  12345
Johnson------------X Joshua------------X (404) 555-0047  12345
Johnson------------X Joshua------------X (404) 555-0048  12345
Johnson------------X Joshua------------X (404) 555-0049  12345
Johnson------------X Joshua------------X (404) 555-0050  12345
Johnson------------X Joshua------------X (404) 555-0051  12345

(New page starts here.)

                     PHONE BOOK REPORT               Page:    2

Last Name            First Name           Number          Ext.

Johnson------------X Joshua------------X (404) 555-0052  12345
Johnson------------X Joshua------------X (404) 555-0053  12345
Johnson------------X Joshua------------X (404) 555-0054  12345
Johnson------------X Joshua------------X (404) 555-0055  12345
Johnson------------X Joshua------------X (404) 555-0056  12345
Johnson------------X Joshua------------X (404) 555-0057  12345
Johnson------------X Joshua------------X (404) 555-0058  12345
Johnson------------X Joshua------------X (404) 555-0059  12345
Johnson------------X Joshua------------X (404) 555-0060  12345
Johnson------------X Joshua------------X (404) 555-0061  12345
Johnson------------X Joshua------------X (404) 555-0062  12345
Johnson------------X Joshua------------X (404) 555-0063  12345
Johnson------------X Joshua------------X (404) 555-0064  12345
Johnson------------X Joshua------------X (404) 555-0065  12345
Johnson------------X Joshua------------X (404) 555-0066  12345
Johnson------------X Joshua------------X (404) 555-0067  12345
Johnson------------X Joshua------------X (404) 555-0068  12345
Johnson------------X Joshua------------X (404) 555-0069  12345
Johnson------------X Joshua------------X (404) 555-0070  12345
Johnson------------X Joshua------------X (404) 555-0071  12345
Johnson------------X Joshua------------X (404) 555-0072  12345
Johnson------------X Joshua------------X (404) 555-0073  12345
Johnson------------X Joshua------------X (404) 555-0074  12345
Johnson------------X Joshua------------X (404) 555-0075  12345
Johnson------------X Joshua------------X (404) 555-0076  12345
Johnson------------X Joshua------------X (404) 555-0077  12345

ANALYSIS: The logic called NEW-PAGE in phnprt01.cbl has been changed to NEXT-PAGE. NEXT-PAGE at line 011900 has been broken into two separate actions: END-LAST-PAGE and START-NEW-PAGE.

END-LAST-PAGE at lines 013200 through 013500 performs the familiar task of forcing a form feed.

The START-NEW-PAGE logic at lines 012300 through 013000 takes care of starting the top of a new page. It adds 1 to the page number, moves the new page number to PRINT-PAGE-NUMBER in the TITLE-LINE, writes TITLE-LINE, and advances two lines. The COLUMN-HEADINGS are written, also followed by two lines, and the PRINT-LINES variable is set to 4 to indicate the number of lines used on the page so far.

The main logic of the program, at lines 007300 through 008400, opens the files, initializes the PRINT-LINES and PAGE-NUMBER variables, starts a new page ready for printing, and reads the first record in the file.

Before the main loop is entered, the logic tests for an immediate end-of-file at line 007900. It is a good practice to have some handling for an empty file, and this program prints a "No records found" message. Without this message, all you see on the report is a title and columns. The message makes it clear that the data file contained no records.

Trace out the logic for this program until you feel comfortable with it, and then code, compile, and run it against the test file created with phnbld01.cbl.

Summary

Reporting on the data in files is one of the main activities of COBOL programs. Today, you learned the following basics about coding, modifying, and printing reports:

Q&A

Q Can I use phnbld01.cbl to create some test data, and then manually add additional data to the file?

A Yes. Run phnbld01.cbl to create the initial data; then run phnadd02.cbl from the answers in Appendix A for Day 9, and you will be able to add data to the end of the file. If you then run phnprt02.cbl, a report will be printed containing the test data, followed by the entries that you created yourself.

Workshop

Quiz

In Listing 10.11, what would be the effect of changing line 007600 to read as follows?

007600     PERFORM NEXT-PAGE.

Exercises

1. Copy phnprt02.cbl to phnprt03.cbl and modify it so that two spaces appear between each column of data.

2. Using graph paper or anything similar to a printer spacing chart, design a report layout for a customer file containing the following record definition:
001100 01  CUSTOMER-RECORD.
001200     05  CUSTOMER-NUMBER      PIC 9(4).
001300     05  CUSTOMER-NAME        PIC X(20).
001400     05  CUSTOMER-PHONE       PIC X(15).
001500     05  CUSTOMER-BALANCE     PIC S9(5)V99.
Hint: The printed picture for the CUSTOMER-NUMBER would be ZZZ9, and for the CUSTOMER-BALANCE it would be ZZ,ZZ9.99-.


Previous chapterNext chapterContents


© Copyright, Macmillan Computer Publishing. All rights reserved.