Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.34.2 ON SIZE ERROR Phrase

The ON SIZE ERROR phrase can be used to define special processing that is to take place when a size error occurs for a data item used to store the results of a mathematical operation. Because COBOL continues execution even if a size error occurs, a size error can cause a loop or processing result error at execution. To prevent such problems, the ON SIZE ERROR phrase can be used to clearly define the operation to be executed when a size error occurs.

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* The ON SIZE ERROR phrase can define the processing operation when a
000035* size error occurs.
000040*----------------------------------------------------------------------
000050 IDENTIFICATION    DIVISION.
000060 PROGRAM-ID.       SAMPLE.
000070 DATA              DIVISION.
000080 WORKING-STORAGE   SECTION.
000090 01 INPUT-NUM      PIC S9(4) VALUE ZERO.
000100 01 THE-SUM        PIC S9(4) VALUE ZERO.
000110 01 AVERAGE-VALUE  PIC S9(4).
000120 01 COUNTER        PIC  9(4) BINARY.
000130 PROCEDURE         DIVISION.
000140     DISPLAY "Obtain the average value of the input data (up to 4
000145-            " digits)."
000150     PERFORM TEST AFTER
000160             VARYING COUNTER FROM 1 BY 1 UNTIL INPUT-NUM = 0
000170       DISPLAY "Please input a value (end in 0). >>"  WITH NO ADVANCING
000180       ACCEPT INPUT-NUM
000190*----------------------------------------------------------------------
000200* The logic is coded so that the PERFORM statement is exited when a
000210* size error occurs for a data item used to store the sum of the 
000215* numeric data.
000220*----------------------------------------------------------------------
000230       COMPUTE THE-SUM = THE-SUM + INPUT-NUM
000240         ON SIZE ERROR DISPLAY "The intermediate data is out of range."
000250                       MOVE ZERO TO COUNTER
000260                       EXIT PERFORM
000270       END-COMPUTE
000280*----------------------------------------------------------------------
000290     END-PERFORM.
000300     IF COUNTER > 1 THEN
000310       COMPUTE AVERAGE-VALUE = THE-SUM / (COUNTER - 1)
000320       DISPLAY " "
000330       DISPLAY "The average value is " AVERAGE-VALUE "."
000340     END-IF.
000350 END PROGRAM SAMPLE.