Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.34.1 ROUNDED Phrase

Normally for COBOL arithmetic expressions, truncation is performed based on the number of digits of the data item where the operation results are stored. However, the ROUNDED phrase can be used to round the operation results instead of truncating them.

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* The ROUNDED phrase can be used to round the operation results.
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(8) VALUE ZERO.
000110 01 AVERAGE-VALUE  PIC S9(4).
000120 01 COUNTER        PIC  9(4) BINARY.
000130 PROCEDURE         DIVISION.
000140     DISPLAY "Round off 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       COMPUTE THE-SUM = THE-SUM + INPUT-NUM
000200     END-PERFORM.
000210     IF COUNTER > 1 THEN
000220*----------------------------------------------------------------------
000230* The ROUNDED phrase rounds the operation results.
000240* Truncation is performed if the ROUNDED phrase is omitted.
000250*----------------------------------------------------------------------
000260       COMPUTE AVERAGE-VALUE ROUNDED = THE-SUM / (COUNTER - 1)
000270*----------------------------------------------------------------------
000280       DISPLAY " "
000290       DISPLAY "The average value is " AVERAGE-VALUE "."
000300     END-IF.
000310 END PROGRAM SAMPLE.