REPORT WRITER

Report writer is a feature of COBOL that allows for the generation of COBOL reports by describing the characteristics of the reports in the DATA DIVISION and then GENERATING the report from the PROCEDURE DIVISION. Report writer is more than just a way of producing reports. It is a feature of the COBOL language and using it does not mean that you loose any of the power of COBOL. You can still have very complex COBOL logic and processing in your report and include the features of the REPORT WRITER to set-up and generate the report. The DECLARATIVE SECTION can give REPORT WRITER more power by allowing the programmer to code special features that REPORT WRITER does not have.

First, a simple example which will be used to introduce REPORT WRITER.
FILE-CONTROL
    	SELECT INPUT-FILE ASSIGN TO...
    	SELECT PRINT-FILE ASSIGN TO...
DATA DIVISION.
FILE SECTION.
FD   INPUT-FILE...
01  	INPUT-REC.
     	05  STUDENT-ID               PIC  9(5).
    	05  STUDENT-NAME             PIC  X(20).
    	05  MAJOR                    PIC  XXX.
    	05  NUM-COURSES              PIC  99.
FD  	PRINT-FILE
	REPORT IS STUDENT-REPORT.
WORKING-STORAGE SECTION.
01   ARE-THERE-MORE-RECORDS       PIC  XXX   VALUE  "YES".          
REPORT SECTION.
RD  	STUDENT-RERPORT.
01   REPORT-LINE
     TYPE DETAIL.
      LINE PLUS  1
     05  COLUMN 4	  PIC 9(6)     SOURCE	STUDENT-ID.
     05  COLUMN 15        PIC X(20)    SOURCE	STUDENT-NAME.
     05  COLUMN 40	  PIC XXX      SOURCE	MAJOR.
     05  COLUMN 46	  PIC 99       SOURCE	NUM-COURSES.
PROCEDURE DIVISION.
A000-MAINLINE.
     OPEN  INPUT  INPUT-FILE
		OUTPUT PRINT-FILE
	INITIATE STUDENT-REPORT
	READ INPUT-FILE
		AT END
			MOVE "NO" TO ARE-THERE-MORE-RECORDS.
	PERFORM A001-LOOP
		UNTIL ARE-THERE-MORE-RECORD = "NO ".
	TERMINATE STUDENT-REPORT.
	CLOSE INPUT-FILE
	 	 PRINT-FILE.
	STOP RUN.
A001-LOOP.
	GENERATE REPORT-LINE.
	READ INPUT-FILE
		AT END
			MOVE "NO " TO ARE-THERE-MORE-RECORDS.
In the DATA DIVISION, there is a new section called REPORT SECTION. This section is required when you are using the REPORT WRITER. It must be the last section in the DATA DIVISION. In using the REPORT WRITER, the FD for the report file has no 01 level as we are accustomed to seeing. Instead the REPORT IS clause is used to give a name to the report and to tell COBOL that REPORT WRITER will be using this file to write out a report. The name used in the REPORT IS clause must appear in the REPORT SECTION as part of an RD (record description entry). The description given in the RD is what gives the characteristics for the report. The 01 levels of the RD describe a line or group of related lines that will be used for the report. The line/lines under the 01 level are called a REPORT GROUP (in our example the REPORT GROUP consists of only one line called REPORT-LINE). Looking at REPORT-LINE, the first entry is TYPE. The TYPE clause asks for the type of line and in our example since we are only generating detail lines, the TYPE is DETAIL. Examples of TYPEs are: The LINE PLUS 1 clause. tells COBOL to single space the detail lines on the report. If you wanted to double space you would use LINE PLUS 2. This is called a RELATIVE LINE NUMBER CLAUSE and is one of the ways you can control spacing on your report. Another way to control spacing is to use the LINE clause to specify which line you are printing on. This is called ABSOLUTE LINE NUMBER CLAUSE. For example, if you were writing a page header the following line could be set up in an 01 level of the RD:
01	TYPE IS PAGE HEADING.
	05  LINE 1.
	    10  COLUMN 50 PIC ...  VALUE ...
	05  LINE PLUS 2.
	    10  COLUMN 20 PIC ...  VALUE ...
	    10  COLUMN 80 PIC ...  VALUE ...
These entries specify that the first page heading line is to appear on line 1 of the report and that the second page heading line will appear two lines below it.

The COLUMN clause tells what column you want the field to start at. If I specify COLUMN 5, that means that the first character of the SOURCE field or the first character of my VALUE clause will appear in that position.

The SOURCE clause tells REPORT WRITER where to get the data from to fill this field - the SOURCE must be a field defined in the DATA DIVISION.

This example uses three new COBOL verbs in the PROCEDURE DIVISION. The simple explanation of the verbs that follows will be expanded upon as more complex examples are looked at.
The following example uses headers and a final total to illustrate more elements of the REPORT WRITER.
DATA DIVISION.
FILE SECTION.
FD	CUST-ORDER-FILE...
01	CUST-ORDER-REC.
	05  CUST-NUM      PIC 9(5).
	05  ITEM-NUM	   PIC 9(6).
	05  NUM-ORD       PIC 999.
	05  PRICE         PIC 999V99.
	05  SHIPPING      PIC 99V99.
	05  FILLER        PIC X(7).
FD 	CUST-PRINT-FILE
	REPORT IS ORDER-REPORT.
WORKING-STORAGE SECTION.
01	INDICATORS.
	05  ARE-THERE-MORE-RECORDS     PIC XXX   VALUE 'YES'.
	    88  THERE-ARE-NO-MORE-RECORDS        VALUE 'NO '.
01	CONSTANTS.
	05  SALES-TAX     PIC V99        VALUE .05.
01  	WORK-AREAS.
	05  AMT-TAX       PIC 9999V99      VALUE 0.
	05  AMT-ORDER     PIC 9(5)V99      VALUE 0.
	05  TOT-ORDER     PIC 9(6)V99      VALUE 0.

REPORT SECTION.
RD	ORDER-REPORT
	CONTROL FINAL
	PAGE 55 LINES
	FIRST DETAIL 6.
01	TYPE REPORT HEADING.
	LINE 1.
       		10	COLUMN 44	PIC X(21)	
                           VALUE 'CUSTOMER ORDER REPORT'.
	01 	TYPE PAGE HEADING.
	05 LINE 2.
	   10  COLUMN 100   PIC XXX
		     VALUE 'PAGE'.
		10  COLUMN 106	PIC ZZ9
               SOURCE PAGE-COUNTER.
	05 LINE 4.
        10  COLUMN 11	PIC X(8)
		       VALUE 'CUST NUM'.
		10  COLUMN 26	PIC XXXX.
               VALUE 'PART'
		10  COLUMN 39	PIC X(7)
               VALUE '# ITEMS'.
		10  COLUMN 50	PIC X(5)
               VALUE 'PRICE'.
		10  COLUMN 66 	PIC X(7)
               VALUE 'QUANTITY'.
		10  COLUMN 82	PIC XXX
		       VALUE 'TAX'.
		10  COLUMN 91 	PIC X(8)
               VALUE 'SHIPPING'.
		10  COLUMN 108	PIC X(5)
               VALUE 'TOTAL'.
01	DETAIL-LINE TYPE IS DETAIL
	LINE PLUS 1.
	O5  COLUMN 12		PIC 9(5)
               SOURCE CUST-NUM.
	05  COLUMN 25		PIC 9(6)
               SOURCE ITEM-NUM.
	05  COLUMN 41		PIC 999
               SOURCE NUM-ORD.
	05  COLUMN 49		PIC ZZZ.99
               SOURCE PRICE.
	05  COLUMN 64		PIC ZZ.ZZZ.99
               SOURCE AMT-ORDER.
	05  COLUMN 80		PIC Z.ZZZ.99
               SOURCE AMT-TAX.
	05  COLUMN 93		PIC ZZ.99
               SOURCE SHIPPING.
	05  COLUMN 104		PIC ZZZ.ZZZ.99
               SOURCE TOT-ORDER.
	

01 	TYPE CONTROL FOOTING FINAL
	LINE PLUS 2.
	05  COLUMN 42		PIC X(12)
               VALUE 'FINAL TOTALS'.
	05  COLUMN 63		PIC ZZZ.ZZZ.99
               SOURCE AMT-ORDER.
	05  COLUMN 79		PIC ZZ.ZZZ.99
               SUM AMT-TAX.
	05  COLUMN 92		PIC ZZZ.99
               SUM SHIPPING.
	05  COLUMN 102		PIC Z.ZZZ.ZZZ.99
               SUM TOT-ORDER.
PROCEDURE DIVISION.
A000-MAINLINE.
	OPEN INPUT CUST-ORDER-FILE
	     OUTPUT CUST-PRINT-FILE.
	INITIATE ORDER-REPORT.
	READ CUST-ORDER-FILE
         AT END
             MOVE 'NO' TO ARE-THERE-MORE-RECORDS.
	PERFORM A001-LOOP
         UNTIL THERE-ARE-NO-MORE-RECORDS.
	TERMINATE ORDER-REPORT.
	CLOSE CUST-ORDER-FILE
           CUST-PRINT-FILE.
	STOP RUN.
A001-LOOP.
	MULTIPLY NUM-ORD BY PRICE GIVING AMT-ORD.
	MULTIPLY AMT-ORD BY SALE-TAX GIVING AMT-TAX.
	ADD AMT-ORD. SHIPPING. AMT-TAX GIVING TOT-ORDER.
	GENERATE DETAIL-LINE.
	READ CUST-ORDER-FILE
         AT END
             MOVE 'NO' TO ARE-THERE-MORE-RECORDS.
This program generates multiple line types - there is a report heading line. two page heading lines. a detail line and a final total line - there are therefore four 01 levels. one for each type.

Notice that the final total line has TYPE IS CONTROL FOOTING FINAL. The line has the word FINAL after it to indicate that the break is to be the final break - REPORT WRITER considers a final total a control break so you must have this clause.

Sum is used to accumulate a field. The clause SUM TOT-ORDER causes the REPORT WRITER to sum the field called TOT-ORDER each time it is calculated - it actually sets up a field called a SUM COUNTER to accumulate the total amounts. Whenever a GENERATE DETAIL-LINE is executed. REPORT WRITER adds the value of TOT-ORDER into the sum counter. The picture of the sum counter is generated based on the picture in the clause that has the SUM. SUM can only be used with a CONTROL FOOTING REPORT LINE.

If you look at the PAGE heading you will see the clause SOURCE PAGE-COUNTER. This is a reserved word that when used means that the REPORT WRITER will keep track of the page numbers for you its own field called PAGE-COUNTER.

The next two examples of the REPORT WRITER involve control breaks and the use of the SUM clause.

Example #1

ENVIRONMENT DIVISION.
...
FILE-CONTROL.
	SELECT STUDENT-FILE ASSIGN TO ...
	SELECT PRINT-FILE ASSIGN TO ...
DATA DIVISION.
FILE SECTION.
FD	STUDENT-FILE
	...
01	STUDENT-REC		PIC X(60).
FD	PRINT-FILE
	REPORT IS CONTROL-BREAK.
	
WORKING-STORAGE SECTION.
01	INDICATORS.
	05  ARE-THERE-MORE-RECORDS PIC XXX
                  VALUE 'YES'.
		 88 THERE-ARE-NO-MORE-RECORDS
                  VALUE 'NO'.
01 	CONSTANTS.
	05  NUM		PIC 99
                   VALUE 1.
01	STUDENT-AREA.
	05  STUDENT-NAME	PIC X(20).
	05  COURSE-PTS		PIC 99.
	05  MAJOR		PIC XXX.
	05  ADVISOR		PIC X(20).
	05  CAMPUS		PIC X(15).
REPORT SECTION.
RD	CONTROL-BREAK
	CONTROLS ARE MAJOR ADVISOR
	PAGE LIMIT 50 LINES
	HEADING 1
	FIRST DETAIL 5
	FOOTING 48.
01	TYPE IS PAGE HEADING.
	05 	 LINE 1.
		 10  COLUMN 61	PIC X(4)
                VALUE 'PAGE'.
		 10  COLUMN 66	PIC ZZZ9
                SOURCE PAGE-COUNTER.
	05 	 LINE PLUS 2.
		 10  COLUMN 26 	PIC X(23)
                VALUE 'STUDENT ADVISEMENT LIST'.
01	TYPE IS CONTROL HEADING MAJOR.
	05	 LINE 5.
		 10  COLUMN 37	PIC X(5)
                VALUE 'MAJOR'.
		 10  COLUMN 44	PIC X(20)
                SOURCE MAJOR.
	05	 LINE 7.
		 10  COLUMN 4	PIC X(12)
                VALUE 'STUDENT NAME'.
		 10  COLUMN 25	PIC XXX
                VALUE 'PTS'.
		 10  COLUMN 34	PIC X(6)
                VALUE 'CAMPUS'.
01	TRANS-LINE TYPE IS DETAIL.
	05	 LINE NUMBER PLUS 1.
		 10  COLUMN 1	PIC X(20)
                SOURCE STUDENT-NAME.
		 10  COLUMN 26	PIC 99
                SOURCE COURSE-PTS.
		 10  COLUMN 30	PIC X(15)
                SOURCE CAMPUS.
01	TYPE IS CONTROL FOOTING ADVISOR.
	05	 LINE PLUS 2.
		 10  COLUMN 5 	PIC X(13)
                VALUE 'ADVISOR TOTAL'.
		 10  ADV-TOTAL
		     COLUMN 22	PIC ZZ9
                SUM NUM.

01	TYPE IS CONTROL FOOTING MAJOR.
	05	 LINE PLUS 2.
		 10  COLUMN 5	PIC X(11)
                VALUE 'MAJOR TOTAL'.
		 10  MAJ-TOTAL
		     COLUMN 22	PIC ZZ9
                SUM ADV-TOTAL.
01	TYPE IS CONTROL FOOTING FINAL.
	05  LINE PLUS 3.
		 10  COLUMN 5	PIC X(11)
                VALUE 'FINAL TOTAL'.
		 10  STU-TOTAL
		     COLUMN 21	PIC ZZZ9
                SUM MAJ-TOTAL.
PROCEDURE DIVISION.
A000-CREATE-REPORTS.
	OPEN INPUT STUDENT-FILE
		 OUTPUT PRINT-FILE.
	INITIATE CONTROL-BREAK.
	READ STUDENT-FILE INTO STUDENT-AREA
		 AT END
		     MOVE 'NO ' TO ARE-THERE-MORE-RECORDS.
	PERFORM A001-LOOP
		 UNTIL THERE-ARE-NO-MORE-RECORDS.
	TERMINATE CONTROL-BREAK.
	CLOSE STUDENT-FILE.
		    PRINT-FILE.
	STOP RUN.
A001-LOOP.
	GENERATE TRANS-LINE.
	READ STUDENT-FILE INTO STUDENT-AREA
		 AT END
		     MOVE 'NO ' TO ARE-THERE-MORE-RECORDS.

Example #2

FD	INV-FILE...
01	INV-REC.
	05	 DEPT-IN		PIC 99.
	05	 DEPT-NAM-IN		PIC X(18).
	05	 MONTH-IN		PIC 99.
	05	 ITEM-NO-IN		PIC 9(5).
	05	 INV-TOT-IN		PIC 9(6)V99.
FD	REPORT-FILE
	REPORT IS INV-REPORT.
WORKING-STORAGE SECTION.
01	INDICATORS.
	O5  ARE-THERE-MORE-RECORDS	PIC XXX
                 VALUE 'YES'.
REPORT SECTION.
RD	INV-REPORT.
	CONTROLS ARE FINAL DEPT-IN MONTH-IN
	PAGE LIMIT 25 LINES
	HEADING 2
	FIRST DETAIL 5
	LAST DETAIL 18
	FOOTING 20.
01	TYPE IS REPORT HEADING.
	05  LINE 2 COLUMN 50	PIC X(16)
                   VALUE 'INVENTORY REPORT'.
01	TYPE IS CONTROL HEADING DEPT-IN
	LINE NUMBER IS PLUS 2
	NEXT GROUP IS PLUS 2.
	05  COLUMN 2		PIC X(13)
                  VALUE 'DEPARTMENT #:'.
	05	 COLUMN 27		PIC 99
                  SOURCE DEPT-IN.
	05  COLUMN 31		PIC X(16)
                  VALUE 'DEPARTMENT NAME:'.
	05	 COLUMN 50		PIC X(18)
                  SOURCE DEPT-NAM-IN.
01	INV-DETAIL TYPE IS DETAIL
	LINE PLUS 2.
	05  COLUMN 10		PIC 99
                  SOURCE MONTH-IN  GROUP INDICATE.
	05  COLUMN 25		PIC 9(5)
                  SOURCE ITEM-NO-IN.
	05  COLUMN 40		PIC ZZZ.ZZZ.99
                  SOURCE IS INV-TOT-IN.
01	TYPE IS CONTROL FOOTING MONTH-IN
	LINE PLUS 2.
	05  MONTH-TOTAL COLUMN 55 PIC Z.ZZZ.ZZZ.99
                  SUM INV-TOT-IN.
01	TYPE IS CONTROL FOOTING DEPT-IN
	LINE PLUS 2.
	05  DEPT-TOTAL  COLUMN 75 PIC ZZ.ZZZ.ZZZ.99
                  SUM MONTH-TOTAL.
01 	TYPE IS CONTROL FOOTING FINAL
	LINE PLUS 2
	05  FINAL-TOTAL COLUMN 95 PIC ZZZ.ZZZ.ZZZ.99
                  SUM DEPT-TOTAL.
PROCEDURE DIVISION.
A000-MAINLINE.
	OPEN INPUT INV-FILE
		 OUTPUT PRINT-FILE.
	INITIATE INV-REPORT.
	READ INV-FILE
		 AT END
		     MOVE 'NO ' TO ARE-THERE-MORE-RECORDS.
	PERFORM A001-LOOP
		 UNTIL ARE-THERE-MORE-RECORDS = 'NO '.
	CLOSE INV-FILE
		 PRINT-FILE.
	STOP RUN.
A001-LOOP.
	GENERATE INV-DETAIL.
	READ INV-FILE
		 AT END
             MOVE 'NO ' TO ARE-THERE-MORE-RECORDS.

COBOL REPORT WRITER
LANGUAGE SPECIFICATIONS

CONTROL IS      data-name-1 [.data-name-2]
CONTROLS ARE    FINAL [.data-name-] [.data-name-2]
Data-name-1 and data-name-2 must be defined in the FILE SECTION or the WORKING-STORAGE SECTION - they must not be defined in the REPORT SECTION. If FINAL is specified it is the highest control followed by data-name-1 as the intermediate break and data-name-2 as the minor break. If there is a data-name-3 than data-name-1 becomes the major, data-name-2 the intermediate break and data-name-3 the minor break etc. Note this means that FINAL must be specified first in the list (if used) and that the last data-name specified is the minor break.
GROUP INDICATE

The GROUP INDICATE clause means that the item is printed only on its first occurrence - that means it is printed after a control break or a skip to top of page. Examples:
	05  COLUMN 2		PIC 99
                   SOURCE IS MONTH-IN GROUP INDICATE.

LINE NUMBER IS integer-1 [ON NEXT PAGE]
                   PLUS integer-2
The LINE clause is used to specify vertical positioning for the report group. The rules are:
                  integer-1
NEXT GROUP IS     PLUS integer-2
                  NEXT PAGE
Information for vertical positioning following the last line of a report group is given with the NEXT GROUP clause. NEXT GROUP is ignored if it is on a CONTROL FOOTING and not at the highest level at which the control break is triggered. Rules are:
NEXT PAGE phrase can't be specified in a PAGE FOOTING report group.
PAGE  LIMIT IS	   integer-1  LINE
      LIMITS ARE	         LINES
[HEADING integer-2] [FIRST DETAIL integer-3] [LAST DETAIL integer-4] [FOOTING integer-5] The PAGE clause defines the length of the page - its established the vertical subdivisions within which the report groups must print. The phrases that can be included here allow you to establish lines for different things to print at.

SOURCE IS identifier-1

The SOURCE clause defines the data-item that is moved to the slot on in the report group description entry - defines the sending data-item. Identifier-1 must be defined in the DATA DIVISION - it can be anywhere in the FILE SECTION or the WORKING-STORAGE SECTION - if it is in the REPORT SECTION it can only be a PAGE-COUNTER. LINE-COUNTER or a sum counter used with the SUM clause.