Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

SUM clause

Function

The SUM clause instructs the Report Writer to create and (immediately or subsequently) print arithmetic sums of data items selected from the detailed information that constitutes the report. The SUM clause indicates to the Report Writer the addends which are to be used for summation. In addition, this clause provides a numeric item, which is generated automatically, for the accumulation of the addends. This field, i.e. the sum counter, is also the sending field (source item) for the implicit MOVE statement used to edit the printable field whose description contains the SUM clause.

Format


SUM {identifier-1}... [UPON data-name-1]
    [RESET ON {data-name-2 | FINAL}]

Syntax rules

  1. An identifier used as an addend in a SUM clause must be defined in the FILE SECTION, WORKING-STORAGE SECTION, LOCAL-STORAGE SECTION, LINKAGE SECTION or REPORT SECTION. From the REPORT SECTION, only the name of a sum counter may be referenced as an addend of a SUM clause.

  2. Each identifier used as an addend in a SUM clause must represent a numeric data item.

  3. data-name-1 is permitted only as the name of a detail report group that is defined in the current report description.

  4. FINAL or data-name-2 must be specified in the CONTROL clause of the current report description.

  5. identifier-1... specify the items to be accumulated in the sum counter.

  6. The UPON phrase has the effect that the specified addends are added up only when a GENERATE statement is executed referencing the very detail group defined in the UPON phrase (see "Use of the UPON phrase").

  7. The RESET phrase overrides the standard reset function of the sum counter to zero (see "Use of the RESET phrase").

General rules

  1. The SUM clause can only be specified in control footing descriptors.

    Assume the following excerpt from a report:

    JANUARY 02 B10                  2 A   3.00
               B12                  1 A   4.00
               B12                  3 C  17.00
    PURCHASES & COST FOR 1-02       6   $24.00
    

    Printed here are the detailed cost figures and their sum for January 2.

    The detailed cost figures shown on the first three print lines were printed as a result of a GENERATE statement referring to the following detail group:

     

    01 DETAIL-LINE TYPE DETAIL.
       02  ...
       .
       .
       .
       02  COLUMN 50 PICTURE ZZ9.99 SOURCE COST.
    

    This GENERATE statement was executed three times without control break, causing the detail report group to be printed three times in succession. The data item by the name of COST, described in the FILE SECTION of the Data Division as:

    02 COST PICTURE 999V99.

    supplied the detailed cost figures.

    When that GENERATE statement was executed once more, the value of the control data item DAY had been changed from 2 to a different value. The following control footing:

    01 ... TYPE CONTROL FOOTING WDAY.
       02  ...
       .
       .
       .
       02  SUM-DAY COLUMN 49 PICTURE $$$9.99 SUM COST.
    

    was generated as the fourth line of the above partial report, with the contents of sum counter SUM-DAY printed starting at column 49.

    Summation took place as follows:

    During compilation, the compiler created a sum counter (named SUM-DAY) in response to the SUM clause. At object time, when executing the appropriate INITIATE statement, the Report Writer resets the sum counter to zero. Then, each time the GENERATE DETAIL-LINE statement was executed, the current value of the data item COST was added to the contents of the SUM-DAY counter. Since the Report Writer performs this summation (see under 5. "Detail incrementing") immediately following the control break test and the action resulting from that test, the sum of the cost figures for January 2 is printed out with the control group footing for DAY. When the control footings are created, the sum counter is finally reset to zero, as the SUM clause contains no RESET phrase.

  2. Use of the PICTURE clause

    If the description of a data item, within a given report group entry, includes a SUM clause, the associated PICTURE clause describes not only the data item but also the sum counter which the compiler will establish due to the SUM clause. The data item, if printable, is used for printing out the contents of the associated sum counter. The PICTURE clause must define the data item as a numeric or numeric-edited data item, where editing symbols for sum counters will be ignored.

  3. Use of the sum counter

    If the data item entry that contains a SUM clause has a data-name immediately following the level-number, that data-name is the name of the internal sum counter, which can thus be accessed by the programmer (for example, for rounding its contents prior to printing). The sum counter is a compiler-generated data item whose USAGE is COMP-3 and whose numeric characteristics are described in the specified PICTURE clause.

  4. Types of summation

    The programmer can specify three types of summation:
    detail-incrementing, rolling forward, and crossfooting.

  5. Detail-incrementing

    The time at which the Report Writer adds up an addend (identifier-1... from the SUM clause) in the related sum counter depends on the addend itself.

    The addends used for detail-incrementing are those which are not themselves sum counters, in other words, are defined outside the REPORT SECTION.

    Detail-incrementing is the basis for the other two types of summation. The term "detailincrementing" derives from the fact that typically the addends involved in it are printed with the detail groups of the report.

    Detail-incrementing occurs each time that GENERATE statements are executed. Therefore, the programmer must ensure that the operands used for detail-incrementing contain the required values at the time that GENERATE statements are executed. If a SUM clause uses the UPON phrase, the addends in that SUM clause are added into their sum counter only when this detail-incrementing operation takes place in executing a GENERATE statement referring to the same detail group as the UPON phrase (there is, therefore, no point in using the UPON phrase for a summary report). However, if the SUM clause does not include the UPON phrase, then those addends which are not defined as sum counters are added to their related sum counters when any GENERATE statement for the report is executed (detail-incrementing).

    The Report Writer performs detail-incrementing only after taking certain actions as regards control break (test; creation of the control footings and headings if test is positive). This control break processing also includes resetting the sum counters to zero after creating the control footing whose description contains the corresponding SUM clauses (see "Use of the RESET phrase"). This ensures that the printed sum will contain only the values of the addends for the particular series of detail groups which is concluded by the associated control footing (for example, the sum of the cost figures for January 2).

  6. Rolling-forward (hierarchical summation)

    The prerequisite for this kind of summation is that a SUM clause of a control footing must specify as an addend at least one sum counter which was defined as the result of a SUM clause of a hierarchically lower (that is, less inclusive) control footing. Therefore, rolling-forward cannot be designated unless a report description includes at least two control footings whose descriptions each contain at least one SUM clause.

    The contents of a sum counter which is specified as an addend in the SUM clause of another control footing will be added, at the time the associated (hierarchically lower) control footing is generated, to the contents of the sum counter in whose SUM clause it appears as an addend.

    Example 10-8 illustrates rolling forward:  

    Example 10-8

    01 ... TYPE CONTROL FOOTING MONTH.
       02  ...
       .
       .
       02  SUM-MONTH COLUMN 46 PICTURE $$$9.99 SUM
           SUM-DAY.
    

    In the above control footing description, the rolling-forward function is specified in conjunction with the following control footing description (see "SOURCE clause"): 

    01 ... TYPE CONTROL FOOTING WDAY.
       02  ...
       .
       .
       02  SUM-DAY COLUMN 49 PICTURE $$$9.99 SUM COST.
    

    For each creation of the control footing with the control item DAY, the Report Writer adds the contents of the sum counter SUM-DAY to the contents of the sum counter SUM-MONTH, before resetting SUM-DAY to zero. If either a control break or execution of a TERMINATE statement causes the control footing to be generated with MONTH, the sum counter SUM-MONTH (before resetting to zero) will contain the sum of all daysums (values of SUM-DAY at summation times) of the current month.

  7. Crossfooting (adding hierarchically equal sums)

    This type of summation takes place when a SUM clause contains, as addends, the names of sum counters defined by other SUM clauses in the same control footing. Normally, such addends are sum counters whose values are created through detail-incrementing.

    Example 10-9

    01 MINOR TYPE CONTROL FOOTING...
       02  SUM-1 SUM WORKING-ITEM-1...
       02  SUM-2 SUM WORKING-ITEM-2...
       02  SUM   SUM SUM-1 SUM-2...
    

    WORKING-ITEM-1 and WORKING-ITEM-2 are data items defined in the WORKING-STORAGE SECTION of the Data Division. Sum counter SUM accumulates the values of SUM-1 and SUM-2, previously generated through detail-incrementing.
    The Report Writer performs crossfooting just before printing the control footing concerned. If more than one SUM clause requires such addition, the order of execution is determined by the sequence of these SUM clauses. This order is essential to the result of the addition.

    Obviously, this type of addition is carried out before rolling-forward, thereby ensuring that sums hierarchically equivalent in summation may also be rolled forward.

     

    Example 10-10

        ...
        CONTROLS ARE STATE, CITY.
        ...
    01  LINE PLUS 2 TYPE CONTROL FOOTING CITY.
        02  SUM-1 SUM MALES...
        02  SUM-2 SUM FEMALES...
        02  SUM-CITY SUM SUM-1, SUM-2...
    01  LINE PLUS 1 TYPE CONTROL FOOTING STATE.
        02 SUM-STATE SUM SUM-CITY...
    
        ...

    The values accumulated in sum counter SUM-CITY by crossfooting the values from the hierarchically equivalent sum counters SUM-1 and SUM-2 (detail-incrementing) are rolled forward in sum counter SUM-STATE (the control footing with STATE is higher in hierarchy than the control footing with CITY). This is possible only because the sum counter SUM-CITY contains the proper value before rolling-forward takes place in the sum counter SUM-STATE.

  8. Mixing operands
    A SUM clause that does not contain an UPON phrase may include one or more of each of the following kinds of operands (= addends):

    • Operands defined in the FILE SECTION, WORKING-STORAGE SECTION, LOCAL-STORAGE SECTION or LINKAGE SECTION.

    • Operands defined as sum counters in a hierarchically inferior control footing.

    • Operands defined as sum counters in the same control footing (whose description contains the SUM clause).

      Summing for each of the above kinds of operands occurs at the times indicated in the preceding discussions.
  9. Use of the UPON phrase

    • When an UPON phrase is used in a SUM clause, all addends of that clause must be defined outside the REPORT SECTION; that is, they may be defined only in the FILE SECTION, WORKING-STORAGE SECTION, LOCAL- STORAGE SECTION and LINKAGE SECTION.

    • The UPON phrase has the effect of preventing detail-incrementing of the addends from the present SUM clause, unless a GENERATE statement is executed specifying the detail report group indicating in the UPON phrase. A detail-incrementing caused by any other GENERATE statement will not, therefore, affect any of the addends in the SUM clause in question.

    Example 10-11

    DATA DIVISION:
    
    FILE SECTION.
    FD  INFILE...
    ...
        RECORDS ARE MUELLER, MEIER.
    01  MUELLER PICTURE 999.
    01  MEIER PICTURE 9999.
    REPORT SECTION. 
    ...
    01  MUELLER-DETAIL TYPE DETAIL.
        02  LINE PLUS 1 COLUMN 1 PIC 999 SOURCE MUELLER.
    01  MEIER-DETAIL TYPE DETAIL.
        02  LINE PLUS 1 COLUMN 1 PIC 9999 SOURCE MEIER.
    ...
    01 MINOR TYPE CONTROL FOOTING...
       02  SUMME-1 SUM MUELLER UPON MUELLER-DETAIL...
       02  SUMME-2 SUM MEIER UPON MEIER-DETAIL...
       ...
    PROCEDURE DIVISION.
    ...
        GENERATE MUELLER-DETAIL.
        ...
        GENERATE MEIER-DETAIL.

    Because MUELLER and MEIER are the names of two different records on the same file, they cannot be available in memory concurrently. When a MUELLER record is read, the statement GENERATE MUELLER-DETAIL is executed; at that time, the current value of MUELLER is added to sum counter SUM-1. The present value of MEIER, on the other hand, is not added to the contents of sum counter SUM-2 at this time. When a MEIER record is read, the statement GENERATE MEIER-DETAIL is executed; at this time, the detail-incrementing occurs in sum counter SUM-2, and not in SUM-1.

  10. Use of the RESET phrase

    • Only a data-name (FINAL included) supplied in the CONTROL clause of the same report may be used in a RESET phrase. Moreover, the control data item must be at a higher level in hierarchy than the control footing whose description contains the RESET phrase.

    • Normally, the Report Writer resets a sum counter to zero immediately after printing the control footing in whose description it is defined. A sum counter whose SUM clause contains the RESET phrase will be reset to zero only at a time when the (explicit or implicit) control footing for the control data item (or FINAL) that appears in the RESET phrase, is (or would be) created. Thus, the RESET phrase serves the purpose of creating a total for the specified hierarchical level.

    Example 10-12

    01 ... TYPE CONTROL FOOTING DAY.
       02  ...
       .
       .
       02  COLUMN 65 PIC $$$$9.99 SUM COST RESET ON FINAL.
    01 ... TYPE CONTROL FOOTING FINAL.
       02  ...
       .
       .
       02  COLUMN 45 PIC $$$$9.99 SUM SUM-DAY. 

    Because the SUM clause in the description of the control footing with the control item DAY contains the phrase RESET ON FINAL, the current value of the associated sum counter is printed every time the control footing of DAY is generated, without ever resetting the sum counter to zero. Only when the control footing for FINAL is generated will the sum counter be reset to zero. Therefore, each printed control footing for DAY shows the running cost figures from the first detail report group of the report (1st day) through to the last detail report group written before the current control heading.

    A control data item that appears in a RESET phrase does not have to be associated with a control footing. A sum counter will be reset, as mentioned earlier, even when no control footing exists for a control item specified in a RESET entry.

  11. Actions taken by the Report Writer
    When generating a control footing, the Report Writer executes the following steps (schematically speaking, because steps may be omitted):

    1. Adding hierarchically equivalent sums (crossfooting).

    2. Execution of the USE BEFORE REPORTING procedures for the control footing (see section "USE BEFORE REPORTING statement").

    3. PRINT SWITCH test.
      If the value of the PRINT SWITCH special register is 1, step d) is skipped, i.e. step e) immediately follows step c) after resetting the special register to zero. Otherwise, step d) comes next.

    4. Creation of the control footing (if printable).

    5. Hierarchical incrementing (rolling-forward).

    6. Any sum counters of the control footings whose SUM clauses do not contain RESET phrases are reset to zeros by implicit MOVE statements. The same applies to all those sum counters of the other control footings whose SUM clauses each contain one such RESET phrase which is referring to the control data item associated with the current (i.e. newly-created) control footing.