MainframeMaster

COBOL Tutorial

COBOL COMPUTE ROUNDED Clause - Quick Reference

Progress0 of 0 lessons

Overview

The ROUNDED clause in COMPUTE statements automatically rounds arithmetic results to fit the target field's decimal precision. It ensures mathematical accuracy in calculations, especially important for financial and scientific applications.

Purpose and Usage

  • Automatic rounding - Apply standard mathematical rounding
  • Precision control - Ensure accurate decimal arithmetic
  • Financial accuracy - Maintain precision in monetary calculations
  • Error prevention - Avoid truncation errors
  • Compliance - Meet accounting and regulatory standards

Rounding Concept

Result: 123.456789
Target: PIC 9(6)V99 (2 decimal places)
Without ROUNDED: 123.45 (truncated)
With ROUNDED: 123.46 (rounded)
Standard rounding: ≥0.5 rounds up, <0.5 rounds down

ROUNDED applies standard mathematical rounding rules automatically.

Syntax

The ROUNDED clause follows specific syntax patterns within COMPUTE statements and can be used with all arithmetic operations.

Basic Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
* Basic ROUNDED syntax COMPUTE result ROUNDED = expression * With arithmetic operations COMPUTE result ROUNDED = operand1 + operand2 COMPUTE result ROUNDED = operand1 - operand2 COMPUTE result ROUNDED = operand1 * operand2 COMPUTE result ROUNDED = operand1 / operand2 COMPUTE result ROUNDED = operand1 ** operand2 * Complex expressions COMPUTE result ROUNDED = (a + b) * c / d * Multiple targets COMPUTE result1 ROUNDED, result2 ROUNDED = expression1, expression2

ROUNDED can be used with any arithmetic operation in COMPUTE statements.

ROUNDED vs NOT ROUNDED

ClauseBehaviorExample
ROUNDEDStandard mathematical rounding123.456 → 123.46
NOT ROUNDEDTruncation without rounding123.456 → 123.45
OmittedSame as NOT ROUNDED123.456 → 123.45

Rounding Rules

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
* Standard rounding rules * 0.0 to 0.4 → rounds down * 0.5 to 0.9 → rounds up * Examples: * 123.450 → 123.45 (no rounding needed) * 123.451 → 123.45 (rounds down) * 123.455 → 123.46 (rounds up) * 123.459 → 123.46 (rounds up) * 123.460 → 123.46 (no rounding needed) * Negative numbers follow same rules * -123.455 → -123.46 (rounds up) * -123.451 → -123.45 (rounds down)

ROUNDED uses standard mathematical rounding rules for all numbers.

Practical Examples

These examples demonstrate how to use the ROUNDED clause effectively in different arithmetic scenarios.

Basic Arithmetic with ROUNDED

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
IDENTIFICATION DIVISION. PROGRAM-ID. BASIC-ROUNDED-ARITHMETIC. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-AMOUNT1 PIC 9(5)V99 VALUE 123.456. 01 WS-AMOUNT2 PIC 9(5)V99 VALUE 456.789. 01 WS-RESULT PIC 9(6)V99. 01 WS-RESULT-NO-ROUND PIC 9(6)V99. PROCEDURE DIVISION. MAIN-PROCESS. * Addition with ROUNDED COMPUTE WS-RESULT ROUNDED = WS-AMOUNT1 + WS-AMOUNT2 DISPLAY "With ROUNDED: " WS-AMOUNT1 " + " WS-AMOUNT2 " = " WS-RESULT * Addition without ROUNDED COMPUTE WS-RESULT-NO-ROUND = WS-AMOUNT1 + WS-AMOUNT2 DISPLAY "Without ROUNDED: " WS-AMOUNT1 " + " WS-AMOUNT2 " = " WS-RESULT-NO-ROUND * Multiplication with ROUNDED COMPUTE WS-RESULT ROUNDED = WS-AMOUNT1 * 1.5 DISPLAY "Multiplication with ROUNDED: " WS-AMOUNT1 " * 1.5 = " WS-RESULT * Division with ROUNDED COMPUTE WS-RESULT ROUNDED = WS-AMOUNT2 / 3 DISPLAY "Division with ROUNDED: " WS-AMOUNT2 " / 3 = " WS-RESULT STOP RUN.

Basic arithmetic operations showing the difference between ROUNDED and non-ROUNDED results.

Financial Calculations

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
IDENTIFICATION DIVISION. PROGRAM-ID. FINANCIAL-ROUNDED-CALCULATIONS. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-PRINCIPAL PIC 9(8)V99 VALUE 10000.00. 01 WS-RATE PIC 9(3)V99 VALUE 5.25. 01 WS-TIME PIC 9(2)V99 VALUE 2.50. 01 WS-INTEREST PIC 9(8)V99. 01 WS-TOTAL-AMOUNT PIC 9(8)V99. 01 WS-MONTHLY-PAYMENT PIC 9(6)V99. PROCEDURE DIVISION. MAIN-PROCESS. * Calculate simple interest with ROUNDED COMPUTE WS-INTEREST ROUNDED = WS-PRINCIPAL * WS-RATE * WS-TIME / 100 DISPLAY "Principal: " WS-PRINCIPAL DISPLAY "Rate: " WS-RATE "%" DISPLAY "Time: " WS-TIME " years" DISPLAY "Interest (ROUNDED): " WS-INTEREST * Calculate total amount COMPUTE WS-TOTAL-AMOUNT ROUNDED = WS-PRINCIPAL + WS-INTEREST DISPLAY "Total Amount (ROUNDED): " WS-TOTAL-AMOUNT * Calculate monthly payment (example) COMPUTE WS-MONTHLY-PAYMENT ROUNDED = WS-TOTAL-AMOUNT / (WS-TIME * 12) DISPLAY "Monthly Payment (ROUNDED): " WS-MONTHLY-PAYMENT STOP RUN.

Financial calculations demonstrating the importance of ROUNDED for accuracy.

Complex Expressions with ROUNDED

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
IDENTIFICATION DIVISION. PROGRAM-ID. COMPLEX-ROUNDED-EXPRESSIONS. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-VALUE1 PIC 9(4)V99 VALUE 123.45. 01 WS-VALUE2 PIC 9(4)V99 VALUE 67.89. 01 WS-VALUE3 PIC 9(4)V99 VALUE 45.67. 01 WS-RESULT1 PIC 9(6)V99. 01 WS-RESULT2 PIC 9(6)V99. 01 WS-RESULT3 PIC 9(6)V99. PROCEDURE DIVISION. MAIN-PROCESS. * Complex expression with parentheses COMPUTE WS-RESULT1 ROUNDED = (WS-VALUE1 + WS-VALUE2) * WS-VALUE3 DISPLAY "Complex 1: (" WS-VALUE1 " + " WS-VALUE2 ") * " WS-VALUE3 " = " WS-RESULT1 * Multiple operations with ROUNDED COMPUTE WS-RESULT2 ROUNDED = WS-VALUE1 * WS-VALUE2 / WS-VALUE3 + 100 DISPLAY "Complex 2: " WS-VALUE1 " * " WS-VALUE2 " / " WS-VALUE3 " + 100 = " WS-RESULT2 * Exponentiation with ROUNDED COMPUTE WS-RESULT3 ROUNDED = WS-VALUE1 ** 2 DISPLAY "Exponentiation: " WS-VALUE1 " ** 2 = " WS-RESULT3 * Nested calculations COMPUTE WS-RESULT1 ROUNDED = WS-VALUE1 + WS-VALUE2 COMPUTE WS-RESULT2 ROUNDED = WS-RESULT1 * WS-VALUE3 DISPLAY "Nested: (" WS-VALUE1 " + " WS-VALUE2 ") * " WS-VALUE3 " = " WS-RESULT2 STOP RUN.

Complex arithmetic expressions showing ROUNDED usage in sophisticated calculations.

Multiple Results with ROUNDED

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
IDENTIFICATION DIVISION. PROGRAM-ID. MULTIPLE-ROUNDED-RESULTS. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-INPUT-VALUE PIC 9(4)V99 VALUE 123.45. 01 WS-RESULT1 PIC 9(6)V99. 01 WS-RESULT2 PIC 9(6)V99. 01 WS-RESULT3 PIC 9(6)V99. 01 WS-RESULT4 PIC 9(6)V99. PROCEDURE DIVISION. MAIN-PROCESS. * Multiple results in one COMPUTE statement COMPUTE WS-RESULT1 ROUNDED, WS-RESULT2 ROUNDED = WS-INPUT-VALUE * 2, WS-INPUT-VALUE / 2 DISPLAY "Input Value: " WS-INPUT-VALUE DISPLAY "Double (ROUNDED): " WS-RESULT1 DISPLAY "Half (ROUNDED): " WS-RESULT2 * Separate calculations for clarity COMPUTE WS-RESULT3 ROUNDED = WS-INPUT-VALUE * 1.5 COMPUTE WS-RESULT4 ROUNDED = WS-INPUT-VALUE * 0.75 DISPLAY "1.5x (ROUNDED): " WS-RESULT3 DISPLAY "0.75x (ROUNDED): " WS-RESULT4 STOP RUN.

Multiple result calculations showing how to apply ROUNDED to multiple targets.

Best Practices and Considerations

Understanding best practices ensures accurate calculations and proper handling of decimal precision.

ROUNDED Best Practices

  • Use consistently - Apply ROUNDED to all financial calculations
  • Choose appropriate precision - Use adequate field sizes for your calculations
  • Test edge cases - Verify rounding behavior with boundary values
  • Document requirements - Clearly specify rounding requirements
  • Consider order of operations - Be aware of when rounding occurs

Common Pitfalls to Avoid

PitfallProblemSolution
Inconsistent roundingAccumulated errorsUse ROUNDED consistently
Inadequate precisionLoss of accuracyUse appropriate field sizes
Wrong order of operationsIncorrect resultsUse parentheses for clarity
Missing edge case testingUnexpected behaviorTest with boundary values
Inconsistent data typesType conversion issuesUse compatible data types

Performance and Precision Considerations

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
* High precision calculations 01 WS-HIGH-PRECISION PIC 9(10)V99. * 10 digits, 2 decimals 01 WS-INTERMEDIATE PIC 9(12)V99. * Intermediate with extra precision 01 WS-FINAL-RESULT PIC 9(8)V99. * Final result with ROUNDED * Example: Maintain precision through calculations COMPUTE WS-INTERMEDIATE ROUNDED = WS-HIGH-PRECISION * 1.123456 COMPUTE WS-FINAL-RESULT ROUNDED = WS-INTERMEDIATE / 100 * Financial calculations with proper precision 01 WS-CURRENCY-AMOUNT PIC 9(8)V99. * Currency amount 01 WS-TAX-RATE PIC 9(3)V99. * Tax rate percentage 01 WS-TAX-AMOUNT PIC 9(8)V99. * Calculated tax COMPUTE WS-TAX-AMOUNT ROUNDED = WS-CURRENCY-AMOUNT * WS-TAX-RATE / 100

Consider precision requirements and use appropriate field sizes.

COMPUTE ROUNDED Clause Quick Reference

OperationSyntaxExample
AdditionCOMPUTE result ROUNDED = a + bCOMPUTE WS-SUM ROUNDED = WS-A + WS-B
SubtractionCOMPUTE result ROUNDED = a - bCOMPUTE WS-DIFF ROUNDED = WS-A - WS-B
MultiplicationCOMPUTE result ROUNDED = a * bCOMPUTE WS-PRODUCT ROUNDED = WS-A * WS-B
DivisionCOMPUTE result ROUNDED = a / bCOMPUTE WS-QUOTIENT ROUNDED = WS-A / WS-B
ExponentiationCOMPUTE result ROUNDED = a ** bCOMPUTE WS-POWER ROUNDED = WS-A ** 2

Test Your Knowledge

1. What is the primary purpose of the ROUNDED clause in COMPUTE statements?

  • To round numbers up
  • To automatically round arithmetic results
  • To truncate decimal places
  • To format output

2. When is the ROUNDED clause most useful?

  • When working with integers only
  • When working with decimal arithmetic and precision is important
  • When doing string operations
  • When opening files

3. How does ROUNDED handle decimal precision?

  • It always rounds up
  • It always rounds down
  • It rounds according to standard rounding rules
  • It truncates without rounding

4. Which arithmetic operations can use the ROUNDED clause?

  • Only addition
  • Only multiplication
  • All arithmetic operations (+, -, *, /, **)
  • Only division

5. What happens if you don't use ROUNDED when precision is exceeded?

  • The program crashes
  • The result is truncated without rounding
  • The result is automatically rounded anyway
  • The result is set to zero

Frequently Asked Questions