Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

Function 1 of the CBL-CTR special register

This function is invoked by a MOVE statement which places 1 (or 3) in the CBL-CTR special register.
The function consists of two parts; the respective actions are covered in the following rules.

  1. Restoration of the previous values of the control data items in control footings

    Part 1 of function 1 makes previous values of control data items available to control footing SOURCE clauses or control footing USE BEFORE REPORTING declaratives.
    SOURCE clauses (or USE BEFORE REPORTING declaratives) in control footings referring to control data items produce a problem. At the time the control footings are printed, some or all of the specified control data items have changed values. However, since the control footings printed because of a control break obviously belong to the precontrol break values, it is often desirable that the previous values (i.e. prior to the control break) should be printed. When function 1 of CBL-CTR is requested, these previous values of the control data items will be obtained by SOURCE clauses (or USE BEFORE REPORTING declaratives) of control footings.

    For example, assume that the item MONTH-NAME is defined as a control data item for a report and that the control footing MONTH-FOOTING is defined as follows:

    01 MONTH-FOOTING TYPE CONTROL FOOTING 
                            MONTH-NAME LINE PLUS 1. 
       02 COLUMN 10 PIC X(21) VALUE "***** END OF DATA FOR". 
       02 COLUMN 33 PIC X(9) SOURCE MONTH-NAME.

    In this case, the programmer wants the following control footing to be printed after all of the JANUARY data has been printed in the detail lines of the report:

    ***** END OF DATA FOR JANUARY.

    Since the above control footing was printed because the item MONTH-NAME changed from JANUARY to FEBRUARY, FEBRUARY (the current contents) would be printed rather than JANUARY. By requesting function 1, the programmer can cause the prior value (JANUARY) to be printed instead of FEBRUARY.

  2. Indicating the control break level in CBL-CTR

    Part 2 of function 1 causes the Report Writer to place, in CBL-CTR, a value indicating the control break level in the hierarchy. This is done before control is passed to a USE BEFORE REPORTING procedure for execution. This kind of procedure begins with:

    section-name SECTION. USE BEFORE REPORTING report-group-name.

    Indicating the level of the current control break in the hierarchy is accomplished by numbering the control data items consecutively, starting from the highest level in the hierarchy, not including FINAL. Thus, the first (leftmost) data-name of the CONTROL clause is numbered 1, the next is numbered 2, and so on.

    For instance, assume that a report description entry contains this CONTROL clause:

    CONTROLS ARE FINAL STATE COUNTY CITY

    In this case, STATE is assigned number 1, COUNTY number 2, and CITY number 3.

    The meanings of the CBL-CTR values in the USE procedures declared for the page heading and control headings are listed below in table 41.

    If, in the above example, the value of the control data item COUNTY changes, the value 2 will be placed in the CBL-CTR register by the Report Writer (provided that the value of CITY has not changed at the same time also).

     


    Value

    Meaning

    0

    Indicates that no GENERATE statement has been executed or that the very first GENERATE statement is being executed.

    1-254

    Indicates that the control data item with the corresponding number has just changed values, and that actions currently taking place were caused by this control break.

    255

    Indicates that no control break has occurred (cannot be encountered with control footing USE procedures).

    Table 41: CBL-CTR values in USE procedures for page headings and control headings

    The meanings of CBL-CTR values in USE declaratives for the page footing and control footings are listed below in table 42.

    Value

    Meaning

    0

    Indicates the final stage of processing, i.e. the TERMINATE statement is being executed.

    1-254

    Indicates that the control data item with the corresponding number has just changed values, and that actions currently taking place were caused by this control break.

    255

    Indicates that no control break has occurred (cannot be encountered with control footing USE procedures).

    Table 42: CBL-CTR values in USE procedures for page footings and control listings