TERMINATE
General Format
TERMINATE report-name-1
Syntax Rules
1. Report-name-1 shall be defined by a report description entry in the report section.
2. If report-name-1 is defined in a containing program, the file description entry associated with report-name-1 shall contain a GLOBAL clause.
General Rules
1. The TERMINATE statement may be executed only for a report that is in the active state. If the report is not in the active state, the EC-REPORT-INACTIVE exception condition is set to exist and the execution of the statement has no other effect.
2. If no GENERATE statement has been executed for a report during the interval between the execution of an INITIATE statement and a TERMINATE statement for that report, the TERMINATE statement causes no processing of any kind to take place for any report groups and has the sole effect of changing the state of the report to inactive.
3. If at least one GENERATE statement has been executed for a report during the interval between the execution of an INITIATE statement and a TERMINATE statement for that report, the TERMINATE statement causes the following actions to take place:
A. The contents of any control data items are changed to their prior values.
B. Each control footing is printed, if defined, beginning with the minor control footing, as defined for the GENERATE statement, as though a control break has been sensed in the most major control data item.
C. The report footing is printed, if defined.
D. The contents of any control data items are restored to the values they had at the start of execution of the TERMINATE statement.
4. The result of executing a TERMINATE statement in which more than one report-name-1 is specified is as though a separate TERMINATE statement had been executed for each report-name-1 in the same order as specified in the statement. If an implicit TERMINATE statement results in the execution of a declarative procedure that executes a RESUME statement with the NEXT STATEMENT phrase, processing resumes at the next implicit TERMINATE statement, if any.
5. If a non-fatal exception condition is raised during the execution of a TERMINATE statement, execution resumes at the next report item, line, or report group, whichever follows in logical order.
6. The TERMINATE statement does not close the file associated with report-name-1.
Examples
Using Terminate to finish a report generation from Report Section
        input-output section.
        file-control.
            select SalesFile assign to "gbsales.dat"
                   organization is line sequential.
            select PrintFile assign to "salesreportb.lpt".
 
        file section.
        fd  SalesFile.
        01  SalesRecord.
            02 CityCode         pic 9.
            02 SalesPersonNum   pic 9.
            02 ValueOfSale      pic 9(4)V99.
 
        fd  PrintFile
            report is SalesReport.
 
        working-storage section.
        01  eof pic x value low-value.
            88 EndOfFile  value high-values.
 
        01  NameTable.
            02 TableValues.
               03 filler        pic x(18value "Dublin   Belfast  ".
               03 filler        pic x(18value "Cork     Galway   ".
               03 filler        pic x(18value "Sligo    Waterford".
               03 filler        pic x(9)  value "Limerick".
            02 filler redefines TableValues.
               03  CityName     pic x(9occurs 7 times.
        report section.
        rd  SalesReport
            controls are final
                         CityCode
                         SalesPersonNum
            page limit is 66
            heading 1
            first detail 6
            last detail 42
            footing 52.      
       01 type is report heading line number is 1.
            02 .
               03 column 12     pic x(32)
                                value "Report heading of COBOL Program".
 
       01 type is page heading line number is 2.
            02 .
               03 column 12     pic x(32)
                                value "An example COBOL Report Program".
            02 line plus 1.
               03 column 6      pic x(17)
                  value "Bible Salesperson".
               03 column 23     pic x(26)
                  value " - Sales and Salary Report".
               02 line plus 1.
                  03 column 2      pic x(4)  value "City".
                  03 column 12     pic x(11value "Salesperson".
                  03 column 28     pic x(4)  value "Sale".
               02 line plus 1.
                  03 column 2      pic x(4value "Name".
                  03 column 13     pic x(6value "Number".
                  03 column 28     pic x(5value "Value".
 
       01 DetailLine type is detail.
          02 line is plus 1.
             03 column 1      pic x(9)
                              source CityName(CityCode) group indicate.
             03 column 15     pic 9
                              source SalesPersonNum  group indicate.
             03 column 25     pic $$,$$$.99 source ValueOfSale.
 
       01 SalesPersonGrp
             type is control footing SalesPersonNum  next group plus 2.
          02 line is plus 1.
             03 column 15     pic x(21value "Sales for salesperson".
             03 column 37     pic 9 source SalesPersonNum.
             03 column 43     pic x value "=".
             03 sms column 45 pic $$$$$,$$$.99 sum ValueOfSale
                .
 
       01 CityGrp type is control footing CityCode next group plus 2.
          02 line is plus 2.
             03 column 15     PIC X(9value "Sales for".
             03 column 25     PIC X(9) source CityName(CityCode).
             03 column 43     PIC X value "=".
             03 cs column 45  PIC $$$$$,$$$.99 sum sms
                .       
      01 TotalSalesGrp type is control footing final.
          02 line is plus 4.
             03 column 15     pic x(11)
                              value "Total sales".
             03 column 43     pic x value "=".
             03 column 45     pic $$$$$,$$$.99 sum cs.        
      01 type is page footing.
 
          02 line is 53.
             03 column 1 pic x(29)
                         value "Sales, Inc.".
             03 column 45     pic x(6value "Page :".
             03 column 52     pic z9 source page-counter.
 
       01 type is report footing line number is 66.
            02 .
               03 column 12     pic x(32)
                                value "End of the COBOL Report Program".
 
        procedure division.
        Begin.
            open input SalesFile.
            open output PrintFile.
            read SalesFile
                 at end set EndOfFile to true
            end-read.
            initiate SalesReport.
            perform PrintSalaryReport
                    until EndOfFile.
            terminate SalesReport.
            close SalesFile.
            close PrintFile.
            goback.
 
        PrintSalaryReport.
            generate DetailLine.
            read SalesFile
                  at end set EndOfFile to true
            end-read.