MainframeMaster

COBOL Tutorial

COBOL Arithmetic Operations

Progress0 of 0 lessons

Introduction to COBOL Arithmetic

Arithmetic operations in COBOL are fundamental to business applications, providing precise mathematical calculations essential for financial, statistical, and computational tasks. COBOL's arithmetic capabilities are designed for accuracy and reliability in business environments.

COBOL provides several methods for performing arithmetic:

  • ADD Statement: Addition operations with multiple operands
  • SUBTRACT Statement: Subtraction operations
  • MULTIPLY Statement: Multiplication operations
  • DIVIDE Statement: Division operations with remainder handling
  • COMPUTE Statement: Complex expressions with standard operators
  • Intrinsic Functions: Advanced mathematical functions

Basic Arithmetic Statements

COBOL provides four basic arithmetic statements that handle the fundamental mathematical operations with built-in precision and error handling.

ADD Statement

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. ADD-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 NUMBERS. 05 FIRST-NUMBER PIC 9(5)V99 VALUE 1234.56. 05 SECOND-NUMBER PIC 9(5)V99 VALUE 567.89. 05 THIRD-NUMBER PIC 9(5)V99 VALUE 100.00. 05 TOTAL-SUM PIC 9(6)V99 VALUE ZERO. 05 RUNNING-TOTAL PIC 9(6)V99 VALUE ZERO. PROCEDURE DIVISION. DISPLAY "=== ADD Statement Demonstration ===" DISPLAY "First Number: " FIRST-NUMBER DISPLAY "Second Number: " SECOND-NUMBER DISPLAY "Third Number: " THIRD-NUMBER * Simple addition ADD FIRST-NUMBER TO RUNNING-TOTAL DISPLAY "After adding first number: " RUNNING-TOTAL * Addition with multiple operands ADD FIRST-NUMBER SECOND-NUMBER THIRD-NUMBER GIVING TOTAL-SUM DISPLAY "Sum of all three numbers: " TOTAL-SUM * Addition with ROUNDED option ADD FIRST-NUMBER TO RUNNING-TOTAL ROUNDED DISPLAY "Running total with rounding: " RUNNING-TOTAL STOP RUN.

SUBTRACT Statement

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
IDENTIFICATION DIVISION. PROGRAM-ID. SUBTRACT-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 CALCULATIONS. 05 GROSS-AMOUNT PIC 9(6)V99 VALUE 5000.00. 05 DISCOUNT PIC 9(4)V99 VALUE 250.00. 05 TAX-AMOUNT PIC 9(4)V99 VALUE 300.00. 05 NET-AMOUNT PIC 9(6)V99 VALUE ZERO. 05 FINAL-AMOUNT PIC 9(6)V99 VALUE ZERO. PROCEDURE DIVISION. DISPLAY "=== SUBTRACT Statement Demonstration ===" DISPLAY "Gross Amount: $" GROSS-AMOUNT DISPLAY "Discount: $" DISCOUNT DISPLAY "Tax Amount: $" TAX-AMOUNT * Simple subtraction SUBTRACT DISCOUNT FROM GROSS-AMOUNT GIVING NET-AMOUNT DISPLAY "Amount after discount: $" NET-AMOUNT * Multiple subtractions SUBTRACT DISCOUNT TAX-AMOUNT FROM GROSS-AMOUNT GIVING FINAL-AMOUNT DISPLAY "Final amount after all deductions: $" FINAL-AMOUNT STOP RUN.

MULTIPLY Statement

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
IDENTIFICATION DIVISION. PROGRAM-ID. MULTIPLY-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 CALCULATIONS. 05 BASE-PRICE PIC 9(5)V99 VALUE 100.00. 05 QUANTITY PIC 9(3) VALUE 25. 05 DISCOUNT-RATE PIC 9V99 VALUE 0.15. 05 TOTAL-COST PIC 9(6)V99 VALUE ZERO. 05 DISCOUNTED-PRICE PIC 9(5)V99 VALUE ZERO. PROCEDURE DIVISION. DISPLAY "=== MULTIPLY Statement Demonstration ===" DISPLAY "Base Price: $" BASE-PRICE DISPLAY "Quantity: " QUANTITY DISPLAY "Discount Rate: " DISCOUNT-RATE * Simple multiplication MULTIPLY BASE-PRICE BY QUANTITY GIVING TOTAL-COST DISPLAY "Total cost: $" TOTAL-COST * Multiplication with decimal MULTIPLY BASE-PRICE BY DISCOUNT-RATE GIVING DISCOUNTED-PRICE DISPLAY "Discount amount: $" DISCOUNTED-PRICE STOP RUN.

DIVIDE Statement

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. DIVIDE-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 CALCULATIONS. 05 DIVIDEND PIC 9(6)V99 VALUE 1000.00. 05 DIVISOR PIC 9(3)V99 VALUE 3.00. 05 QUOTIENT PIC 9(6)V99 VALUE ZERO. 05 REMAINDER PIC 9(3)V99 VALUE ZERO. 05 AVERAGE PIC 9(5)V99 VALUE ZERO. PROCEDURE DIVISION. DISPLAY "=== DIVIDE Statement Demonstration ===" DISPLAY "Dividend: " DIVIDEND DISPLAY "Divisor: " DIVISOR * Simple division DIVIDE DIVIDEND BY DIVISOR GIVING QUOTIENT DISPLAY "Quotient: " QUOTIENT * Division with remainder DIVIDE DIVIDEND BY DIVISOR GIVING QUOTIENT REMAINDER REMAINDER DISPLAY "Quotient: " QUOTIENT DISPLAY "Remainder: " REMAINDER * Division with ROUNDED DIVIDE DIVIDEND BY DIVISOR GIVING AVERAGE ROUNDED DISPLAY "Rounded average: " AVERAGE STOP RUN.

COMPUTE Statement

The COMPUTE statement provides the most flexible way to perform arithmetic operations, allowing complex expressions with standard mathematical operators.

Basic COMPUTE Operations

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
IDENTIFICATION DIVISION. PROGRAM-ID. COMPUTE-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 CALCULATIONS. 05 PRINCIPAL PIC 9(6)V99 VALUE 10000.00. 05 INTEREST-RATE PIC 9V9999 VALUE 0.0750. 05 TIME-YEARS PIC 9(2) VALUE 5. 05 SIMPLE-INTEREST PIC 9(6)V99 VALUE ZERO. 05 COMPOUND-INTEREST PIC 9(8)V99 VALUE ZERO. PROCEDURE DIVISION. DISPLAY "=== COMPUTE Statement Demonstration ===" DISPLAY "Principal: $" PRINCIPAL DISPLAY "Interest Rate: " INTEREST-RATE DISPLAY "Time (years): " TIME-YEARS * Simple interest calculation COMPUTE SIMPLE-INTEREST = PRINCIPAL * INTEREST-RATE * TIME-YEARS DISPLAY "Simple Interest: $" SIMPLE-INTEREST * Compound interest calculation COMPUTE COMPOUND-INTEREST = PRINCIPAL * (1 + INTEREST-RATE) ** TIME-YEARS - PRINCIPAL DISPLAY "Compound Interest: $" COMPOUND-INTEREST STOP RUN.

Complex COMPUTE Expressions

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. COMPLEX-COMPUTE-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 BUSINESS-CALCULATIONS. 05 REVENUE PIC 9(7)V99 VALUE 50000.00. 05 COST-OF-GOODS PIC 9(6)V99 VALUE 20000.00. 05 OPERATING-COSTS PIC 9(6)V99 VALUE 15000.00. 05 GROSS-PROFIT PIC 9(7)V99 VALUE ZERO. 05 OPERATING-PROFIT PIC 9(7)V99 VALUE ZERO. 05 PROFIT-MARGIN PIC 9V9999 VALUE ZERO. PROCEDURE DIVISION. DISPLAY "=== Complex COMPUTE Expressions ===" DISPLAY "Revenue: $" REVENUE DISPLAY "Cost of Goods: $" COST-OF-GOODS DISPLAY "Operating Costs: $" OPERATING-COSTS * Multiple calculations with parentheses COMPUTE GROSS-PROFIT = REVENUE - COST-OF-GOODS DISPLAY "Gross Profit: $" GROSS-PROFIT COMPUTE OPERATING-PROFIT = REVENUE - COST-OF-GOODS - OPERATING-COSTS DISPLAY "Operating Profit: $" OPERATING-PROFIT * Complex expression with division COMPUTE PROFIT-MARGIN = (REVENUE - COST-OF-GOODS - OPERATING-COSTS) / REVENUE DISPLAY "Profit Margin: " PROFIT-MARGIN STOP RUN.

Mathematical Intrinsic Functions

COBOL provides intrinsic functions for advanced mathematical operations, extending the language's computational capabilities.

Common Mathematical Functions

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
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
IDENTIFICATION DIVISION. PROGRAM-ID. MATH-FUNCTIONS-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 MATH-CALCULATIONS. 05 INPUT-VALUE PIC S9(5)V99 VALUE -123.45. 05 ABSOLUTE-VALUE PIC 9(5)V99 VALUE ZERO. 05 SQUARE-ROOT PIC 9(5)V99 VALUE ZERO. 05 ROUNDED-VALUE PIC 9(5)V99 VALUE ZERO. 05 LOGARITHM PIC 9(5)V99 VALUE ZERO. 01 TRIGONOMETRIC-CALC. 05 ANGLE-DEGREES PIC 9(3)V99 VALUE 45.00. 05 ANGLE-RADIANS PIC 9(5)V99 VALUE ZERO. 05 SINE-VALUE PIC S9V9999 VALUE ZERO. 05 COSINE-VALUE PIC S9V9999 VALUE ZERO. PROCEDURE DIVISION. DISPLAY "=== Mathematical Intrinsic Functions ===" DISPLAY "Input Value: " INPUT-VALUE * Absolute value COMPUTE ABSOLUTE-VALUE = FUNCTION ABS(INPUT-VALUE) DISPLAY "Absolute Value: " ABSOLUTE-VALUE * Square root COMPUTE SQUARE-ROOT = FUNCTION SQRT(ABSOLUTE-VALUE) DISPLAY "Square Root: " SQUARE-ROOT * Rounding COMPUTE ROUNDED-VALUE = FUNCTION ROUND(INPUT-VALUE, 1) DISPLAY "Rounded Value: " ROUNDED-VALUE * Logarithm COMPUTE LOGARITHM = FUNCTION LOG(ABSOLUTE-VALUE) DISPLAY "Natural Logarithm: " LOGARITHM DISPLAY " " DISPLAY "=== Trigonometric Functions ===" DISPLAY "Angle (degrees): " ANGLE-DEGREES * Convert degrees to radians COMPUTE ANGLE-RADIANS = ANGLE-DEGREES * 3.14159 / 180 * Trigonometric functions COMPUTE SINE-VALUE = FUNCTION SIN(ANGLE-RADIANS) COMPUTE COSINE-VALUE = FUNCTION COS(ANGLE-RADIANS) DISPLAY "Sine: " SINE-VALUE DISPLAY "Cosine: " COSINE-VALUE STOP RUN.

Decimal Arithmetic and Precision

COBOL's strength in decimal arithmetic makes it ideal for financial calculations where precision is critical.

Precision Control

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
33
34
35
36
37
38
39
40
41
IDENTIFICATION DIVISION. PROGRAM-ID. DECIMAL-PRECISION-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 FINANCIAL-CALCULATIONS. 05 PRINCIPAL PIC 9(8)V99 VALUE 100000.00. 05 INTEREST-RATE PIC 9V999999 VALUE 0.075000. 05 MONTHLY-PAYMENT PIC 9(6)V99 VALUE ZERO. 05 TOTAL-PAYMENTS PIC 9(8)V99 VALUE ZERO. 05 INTEREST-PAID PIC 9(8)V99 VALUE ZERO. 01 PRECISION-CONTROL. 05 MONTHLY-RATE PIC 9V999999 VALUE ZERO. 05 PAYMENT-FACTOR PIC 9(6)V999999 VALUE ZERO. PROCEDURE DIVISION. DISPLAY "=== Decimal Precision Control ===" DISPLAY "Principal: $" PRINCIPAL DISPLAY "Annual Interest Rate: " INTEREST-RATE * Calculate monthly interest rate with high precision COMPUTE MONTHLY-RATE = INTEREST-RATE / 12 DISPLAY "Monthly Interest Rate: " MONTHLY-RATE * Calculate payment factor with precision COMPUTE PAYMENT-FACTOR = MONTHLY-RATE * (1 + MONTHLY-RATE) ** 360 / ((1 + MONTHLY-RATE) ** 360 - 1) * Calculate monthly payment COMPUTE MONTHLY-PAYMENT = PRINCIPAL * PAYMENT-FACTOR ROUNDED DISPLAY "Monthly Payment: $" MONTHLY-PAYMENT * Calculate total payments COMPUTE TOTAL-PAYMENTS = MONTHLY-PAYMENT * 360 DISPLAY "Total Payments: $" TOTAL-PAYMENTS * Calculate total interest COMPUTE INTEREST-PAID = TOTAL-PAYMENTS - PRINCIPAL DISPLAY "Total Interest Paid: $" INTEREST-PAID STOP RUN.

Performance Optimization

Optimizing arithmetic operations is crucial for high-performance applications, especially those processing large volumes of data.

Efficient Arithmetic Techniques

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
33
34
35
36
IDENTIFICATION DIVISION. PROGRAM-ID. PERFORMANCE-OPTIMIZATION-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 OPTIMIZED-CALCULATIONS. 05 BASE-AMOUNT PIC S9(8)V99 USAGE COMP-3 VALUE 1000.00. 05 MULTIPLIER PIC S9(3)V99 USAGE COMP-3 VALUE 1.15. 05 RESULT-AMOUNT PIC S9(8)V99 USAGE COMP-3 VALUE ZERO. 05 WORK-AMOUNT PIC S9(8)V99 USAGE COMP-3 VALUE ZERO. 01 PERFORMANCE-COUNTERS. 05 CALCULATION-COUNT PIC 9(6) VALUE 100000. 05 LOOP-INDEX PIC 9(6) VALUE ZERO. PROCEDURE DIVISION. DISPLAY "=== Performance Optimization Demo ===" DISPLAY "Performing " CALCULATION-COUNT " calculations" * Optimized arithmetic using COMP-3 for better performance PERFORM VARYING LOOP-INDEX FROM 1 BY 1 UNTIL LOOP-INDEX > CALCULATION-COUNT * Use COMPUTE for complex calculations COMPUTE WORK-AMOUNT = BASE-AMOUNT * MULTIPLIER * Accumulate results efficiently ADD WORK-AMOUNT TO RESULT-AMOUNT * Increment base amount for next iteration ADD 1.00 TO BASE-AMOUNT END-PERFORM DISPLAY "Final result: " RESULT-AMOUNT DISPLAY "Performance optimization completed" STOP RUN.

Error Handling in Arithmetic

Proper error handling ensures arithmetic operations complete successfully and handle exceptional conditions gracefully.

Arithmetic Error Handling

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
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
IDENTIFICATION DIVISION. PROGRAM-ID. ARITHMETIC-ERROR-HANDLING. DATA DIVISION. WORKING-STORAGE SECTION. 01 ERROR-CONTROL. 05 DIVIDEND PIC 9(6)V99 VALUE 1000.00. 05 DIVISOR PIC 9(3)V99 VALUE 0.00. 05 RESULT PIC 9(6)V99 VALUE ZERO. 05 ERROR-FLAG PIC X(1) VALUE 'N'. 01 ERROR-MESSAGES. 05 DIV-ZERO-MSG PIC X(30) VALUE "Error: Division by zero". 05 OVERFLOW-MSG PIC X(30) VALUE "Error: Arithmetic overflow". 05 UNDERFLOW-MSG PIC X(30) VALUE "Error: Arithmetic underflow". PROCEDURE DIVISION. DISPLAY "=== Arithmetic Error Handling Demo ===" PERFORM TEST-DIVISION-BY-ZERO PERFORM TEST-OVERFLOW-CONDITION PERFORM TEST-UNDERFLOW-CONDITION STOP RUN. TEST-DIVISION-BY-ZERO. DISPLAY "Testing division by zero..." MOVE 0.00 TO DIVISOR DIVIDE DIVIDEND BY DIVISOR GIVING RESULT ON SIZE ERROR DISPLAY DIV-ZERO-MSG MOVE 'Y' TO ERROR-FLAG NOT ON SIZE ERROR DISPLAY "Division successful: " RESULT END-DIVIDE. TEST-OVERFLOW-CONDITION. DISPLAY "Testing overflow condition..." MOVE 999999.99 TO DIVIDEND MOVE 0.01 TO DIVISOR MULTIPLY DIVIDEND BY 1000 GIVING RESULT ON SIZE ERROR DISPLAY OVERFLOW-MSG NOT ON SIZE ERROR DISPLAY "Multiplication successful: " RESULT END-MULTIPLY. TEST-UNDERFLOW-CONDITION. DISPLAY "Testing underflow condition..." MOVE 0.001 TO DIVIDEND MOVE 1000.00 TO DIVISOR DIVIDE DIVIDEND BY DIVISOR GIVING RESULT ON SIZE ERROR DISPLAY UNDERFLOW-MSG NOT ON SIZE ERROR DISPLAY "Division successful: " RESULT END-DIVIDE.

Best Practices for Arithmetic Operations

Following best practices ensures accurate, efficient, and maintainable arithmetic operations in COBOL applications.

Design Guidelines

  • Use appropriate PICTURE clauses for precision requirements
  • Choose optimal USAGE clauses for performance
  • Implement proper error handling for all operations
  • Use COMPUTE for complex expressions
  • Validate input data before calculations

Performance Tips

  • Use COMP-3 for decimal arithmetic when possible
  • Minimize data movement between fields
  • Use ROUNDED only when necessary
  • Avoid unnecessary conversions
  • Profile arithmetic-intensive code sections

FAQ

What are the basic arithmetic operations in COBOL?

COBOL provides four basic arithmetic operations: ADD (addition), SUBTRACT (subtraction), MULTIPLY (multiplication), and DIVIDE (division). These operations can be used with multiple operands and support various data types including numeric literals and data items.

What is the COMPUTE statement in COBOL?

The COMPUTE statement allows complex mathematical expressions using standard arithmetic operators (+, -, *, /, **). It provides more flexibility than individual ADD, SUBTRACT, MULTIPLY, and DIVIDE statements and supports parentheses for grouping operations.

How do you handle decimal arithmetic in COBOL?

COBOL handles decimal arithmetic using PICTURE clauses with V (implied decimal point) and appropriate USAGE clauses. The language automatically handles decimal alignment and precision, making it ideal for financial calculations.

What are COBOL intrinsic functions for mathematics?

COBOL provides intrinsic functions like FUNCTION ABS (absolute value), FUNCTION SQRT (square root), FUNCTION SIN/COS/TAN (trigonometric functions), FUNCTION LOG (logarithm), and FUNCTION ROUND (rounding) for advanced mathematical operations.

How do you optimize arithmetic performance in COBOL?

Arithmetic performance optimization includes using appropriate USAGE clauses (COMP-3, COMP-5), minimizing data movement, using COMPUTE for complex expressions, avoiding unnecessary conversions, and choosing efficient data types for calculations.