The COMPUTE statement in COBOL provides powerful capabilities for performing complex mathematical calculations using standard arithmetic operators and intrinsic functions. Advanced compute operations enable sophisticated business logic, scientific calculations, and data processing that goes beyond simple arithmetic. Understanding advanced compute techniques is essential for implementing complex business rules and mathematical algorithms.
Advanced compute operations in COBOL involve complex mathematical expressions using multiple operators, parentheses for grouping, intrinsic functions, and proper handling of decimal precision. The COMPUTE statement evaluates expressions from left to right with proper operator precedence, allowing sophisticated calculations to be performed efficiently and accurately.
COBOL follows standard mathematical operator precedence where multiplication and division are performed before addition and subtraction. Parentheses can be used to override precedence and group operations. Understanding precedence is crucial for writing correct mathematical expressions.
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145IDENTIFICATION DIVISION. PROGRAM-ID. COMPUTE-ADVANCED-EXAMPLE. *> This program demonstrates advanced COMPUTE statement usage DATA DIVISION. WORKING-STORAGE SECTION. *> Variables for complex calculations 01 CALCULATION-DATA. 05 BASE-VALUE PIC 9(5)V99 VALUE 100.00. 05 MULTIPLIER PIC 9(3)V99 VALUE 2.50. 05 DIVISOR PIC 9(3)V99 VALUE 4.00. 05 ADDITION-FACTOR PIC 9(3)V99 VALUE 25.00. 05 SUBTRACTION-FACTOR PIC 9(3)V99 VALUE 15.00. 01 COMPLEX-RESULTS. 05 RESULT-1 PIC 9(8)V99. 05 RESULT-2 PIC 9(8)V99. 05 RESULT-3 PIC 9(8)V99. 05 RESULT-4 PIC 9(8)V99. 05 FINAL-RESULT PIC 9(10)V99. 01 PRECISION-CONTROLS. 05 ROUNDING-ENABLED PIC X(1). 88 ROUNDING-ON VALUE 'Y'. 88 ROUNDING-OFF VALUE 'N'. PROCEDURE DIVISION. COMPUTE-ADVANCED-MAIN. DISPLAY 'Advanced COMPUTE Statement Demonstration' DISPLAY '=======================================' *> Demonstrate operator precedence PERFORM DEMONSTRATE-OPERATOR-PRECEDENCE *> Demonstrate parentheses grouping PERFORM DEMONSTRATE-PARENTHESES-GROUPING *> Demonstrate complex expressions PERFORM DEMONSTRATE-COMPLEX-EXPRESSIONS *> Demonstrate rounding and precision PERFORM DEMONSTRATE-ROUNDING-PRECISION STOP RUN. DEMONSTRATE-OPERATOR-PRECEDENCE. *> Demonstrate operator precedence in COMPUTE statements DISPLAY 'Operator Precedence Demonstration:' DISPLAY 'Base Value: ' BASE-VALUE DISPLAY 'Multiplier: ' MULTIPLIER DISPLAY 'Divisor: ' DIVISOR DISPLAY 'Addition Factor: ' ADDITION-FACTOR DISPLAY 'Subtraction Factor: ' SUBTRACTION-FACTOR DISPLAY ' ' *> Expression: BASE-VALUE + MULTIPLIER * DIVISOR *> Precedence: multiplication first, then addition COMPUTE RESULT-1 = BASE-VALUE + MULTIPLIER * DIVISOR DISPLAY 'BASE-VALUE + MULTIPLIER * DIVISOR = ' RESULT-1 DISPLAY 'Calculation: 100.00 + 2.50 * 4.00 = 100.00 + 10.00 = 110.00' DISPLAY ' ' *> Expression: BASE-VALUE * MULTIPLIER + DIVISOR *> Precedence: multiplication first, then addition COMPUTE RESULT-2 = BASE-VALUE * MULTIPLIER + DIVISOR DISPLAY 'BASE-VALUE * MULTIPLIER + DIVISOR = ' RESULT-2 DISPLAY 'Calculation: 100.00 * 2.50 + 4.00 = 250.00 + 4.00 = 254.00' DISPLAY ' ' *> Expression: BASE-VALUE / DIVISOR - SUBTRACTION-FACTOR *> Precedence: division first, then subtraction COMPUTE RESULT-3 = BASE-VALUE / DIVISOR - SUBTRACTION-FACTOR DISPLAY 'BASE-VALUE / DIVISOR - SUBTRACTION-FACTOR = ' RESULT-3 DISPLAY 'Calculation: 100.00 / 4.00 - 15.00 = 25.00 - 15.00 = 10.00' DISPLAY ' '. DEMONSTRATE-PARENTHESES-GROUPING. *> Demonstrate parentheses grouping to override precedence DISPLAY 'Parentheses Grouping Demonstration:' *> Expression: (BASE-VALUE + MULTIPLIER) * DIVISOR *> Parentheses force addition first, then multiplication COMPUTE RESULT-1 = (BASE-VALUE + MULTIPLIER) * DIVISOR DISPLAY '(BASE-VALUE + MULTIPLIER) * DIVISOR = ' RESULT-1 DISPLAY 'Calculation: (100.00 + 2.50) * 4.00 = 102.50 * 4.00 = 410.00' DISPLAY ' ' *> Expression: BASE-VALUE * (MULTIPLIER + DIVISOR) *> Parentheses force addition first, then multiplication COMPUTE RESULT-2 = BASE-VALUE * (MULTIPLIER + DIVISOR) DISPLAY 'BASE-VALUE * (MULTIPLIER + DIVISOR) = ' RESULT-2 DISPLAY 'Calculation: 100.00 * (2.50 + 4.00) = 100.00 * 6.50 = 650.00' DISPLAY ' ' *> Expression: (BASE-VALUE + ADDITION-FACTOR) / (DIVISOR - SUBTRACTION-FACTOR) *> Complex grouping with multiple operations COMPUTE RESULT-3 = (BASE-VALUE + ADDITION-FACTOR) / (DIVISOR - SUBTRACTION-FACTOR) DISPLAY '(BASE-VALUE + ADDITION-FACTOR) / (DIVISOR - SUBTRACTION-FACTOR) = ' RESULT-3 DISPLAY 'Calculation: (100.00 + 25.00) / (4.00 - 15.00) = 125.00 / (-11.00) = -11.36' DISPLAY ' '. DEMONSTRATE-COMPLEX-EXPRESSIONS. *> Demonstrate complex mathematical expressions DISPLAY 'Complex Expressions Demonstration:' *> Complex expression with multiple operations COMPUTE RESULT-4 = BASE-VALUE * MULTIPLIER + ADDITION-FACTOR / DIVISOR - SUBTRACTION-FACTOR DISPLAY 'Complex expression result: ' RESULT-4 DISPLAY 'Calculation: 100.00 * 2.50 + 25.00 / 4.00 - 15.00' DISPLAY 'Step 1: 100.00 * 2.50 = 250.00' DISPLAY 'Step 2: 25.00 / 4.00 = 6.25' DISPLAY 'Step 3: 250.00 + 6.25 = 256.25' DISPLAY 'Step 4: 256.25 - 15.00 = 241.25' DISPLAY ' ' *> Nested parentheses expression COMPUTE FINAL-RESULT = ((BASE-VALUE + ADDITION-FACTOR) * MULTIPLIER) / (DIVISOR + SUBTRACTION-FACTOR) DISPLAY 'Nested parentheses result: ' FINAL-RESULT DISPLAY 'Calculation: ((100.00 + 25.00) * 2.50) / (4.00 + 15.00)' DISPLAY 'Step 1: (100.00 + 25.00) = 125.00' DISPLAY 'Step 2: 125.00 * 2.50 = 312.50' DISPLAY 'Step 3: (4.00 + 15.00) = 19.00' DISPLAY 'Step 4: 312.50 / 19.00 = 16.45' DISPLAY ' '. DEMONSTRATE-ROUNDING-PRECISION. *> Demonstrate rounding and precision control DISPLAY 'Rounding and Precision Demonstration:' SET ROUNDING-ON TO TRUE *> Division with rounding COMPUTE RESULT-1 ROUNDED = BASE-VALUE / DIVISOR DISPLAY 'Division with rounding: ' RESULT-1 DISPLAY 'Calculation: 100.00 / 4.00 = 25.00 (rounded)' *> Complex calculation with rounding COMPUTE RESULT-2 ROUNDED = (BASE-VALUE * MULTIPLIER) / DIVISOR DISPLAY 'Complex calculation with rounding: ' RESULT-2 DISPLAY 'Calculation: (100.00 * 2.50) / 4.00 = 250.00 / 4.00 = 62.50 (rounded)' *> Multiple operations with rounding COMPUTE FINAL-RESULT ROUNDED = BASE-VALUE + (MULTIPLIER * DIVISOR) / ADDITION-FACTOR DISPLAY 'Multiple operations with rounding: ' FINAL-RESULT DISPLAY 'Calculation: 100.00 + (2.50 * 4.00) / 25.00 = 100.00 + 10.00 / 25.00 = 100.40 (rounded)'.
This example demonstrates advanced COMPUTE statement usage including operator precedence, parentheses grouping, complex expressions, and rounding control. The program shows how COBOL evaluates mathematical expressions according to standard precedence rules, how parentheses can override precedence, and how complex calculations can be performed in a single COMPUTE statement. The ROUNDED option is demonstrated for controlling decimal precision.
Intrinsic functions provide powerful mathematical and string operations that can be used within COMPUTE statements. These functions include mathematical operations like square root, trigonometric functions, logarithmic functions, and string manipulation functions. Understanding intrinsic functions enables sophisticated calculations and data processing.
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132IDENTIFICATION DIVISION. PROGRAM-ID. INTRINSIC-FUNCTIONS-DEMO. *> This program demonstrates intrinsic functions in COMPUTE statements DATA DIVISION. WORKING-STORAGE SECTION. *> Variables for intrinsic function demonstrations 01 MATH-DATA. 05 INPUT-VALUE PIC 9(5)V99 VALUE 144.00. 05 ANGLE-DEGREES PIC 9(3)V99 VALUE 45.00. 05 ANGLE-RADIANS PIC 9(3)V99. 05 LOG-BASE PIC 9(3)V99 VALUE 10.00. 05 LOG-VALUE PIC 9(3)V99 VALUE 100.00. 01 INTRINSIC-RESULTS. 05 SQUARE-ROOT PIC 9(5)V99. 05 SQUARE-VALUE PIC 9(8)V99. 05 ABSOLUTE-VALUE PIC 9(5)V99. 05 MAXIMUM-VALUE PIC 9(5)V99. 05 MINIMUM-VALUE PIC 9(5)V99. 05 SINE-VALUE PIC 9(3)V99. 05 COSINE-VALUE PIC 9(3)V99. 05 LOGARITHM-VALUE PIC 9(3)V99. 05 POWER-VALUE PIC 9(8)V99. 01 STRING-DATA. 05 INPUT-STRING PIC X(20) VALUE 'Hello World'. 05 STRING-LENGTH PIC 9(2). 05 UPPER-STRING PIC X(20). 05 LOWER-STRING PIC X(20). PROCEDURE DIVISION. INTRINSIC-FUNCTIONS-MAIN. DISPLAY 'Intrinsic Functions in COMPUTE Demonstration' DISPLAY '===========================================' *> Demonstrate mathematical intrinsic functions PERFORM DEMONSTRATE-MATHEMATICAL-FUNCTIONS *> Demonstrate string intrinsic functions PERFORM DEMONSTRATE-STRING-FUNCTIONS *> Demonstrate complex calculations with intrinsic functions PERFORM DEMONSTRATE-COMPLEX-CALCULATIONS STOP RUN. DEMONSTRATE-MATHEMATICAL-FUNCTIONS. *> Demonstrate mathematical intrinsic functions DISPLAY 'Mathematical Intrinsic Functions:' DISPLAY 'Input Value: ' INPUT-VALUE DISPLAY 'Angle (degrees): ' ANGLE-DEGREES DISPLAY ' ' *> Square root function COMPUTE SQUARE-ROOT = FUNCTION SQRT(INPUT-VALUE) DISPLAY 'SQRT(' INPUT-VALUE ') = ' SQUARE-ROOT *> Square function (power of 2) COMPUTE SQUARE-VALUE = INPUT-VALUE ** 2 DISPLAY 'Square of ' INPUT-VALUE ' = ' SQUARE-VALUE *> Absolute value function COMPUTE ABSOLUTE-VALUE = FUNCTION ABS(-INPUT-VALUE) DISPLAY 'ABS(-' INPUT-VALUE ') = ' ABSOLUTE-VALUE *> Maximum function COMPUTE MAXIMUM-VALUE = FUNCTION MAX(INPUT-VALUE, 200.00) DISPLAY 'MAX(' INPUT-VALUE ', 200.00) = ' MAXIMUM-VALUE *> Minimum function COMPUTE MINIMUM-VALUE = FUNCTION MIN(INPUT-VALUE, 200.00) DISPLAY 'MIN(' INPUT-VALUE ', 200.00) = ' MINIMUM-VALUE *> Convert degrees to radians for trigonometric functions COMPUTE ANGLE-RADIANS = ANGLE-DEGREES * 3.14159 / 180 *> Sine function COMPUTE SINE-VALUE = FUNCTION SIN(ANGLE-RADIANS) DISPLAY 'SIN(' ANGLE-DEGREES ' degrees) = ' SINE-VALUE *> Cosine function COMPUTE COSINE-VALUE = FUNCTION COS(ANGLE-RADIANS) DISPLAY 'COS(' ANGLE-DEGREES ' degrees) = ' COSINE-VALUE *> Logarithm function COMPUTE LOGARITHM-VALUE = FUNCTION LOG(LOG-VALUE) DISPLAY 'LOG(' LOG-VALUE ') = ' LOGARITHM-VALUE *> Power function COMPUTE POWER-VALUE = FUNCTION POWER(2.00, 8.00) DISPLAY 'POWER(2.00, 8.00) = ' POWER-VALUE DISPLAY ' '. DEMONSTRATE-STRING-FUNCTIONS. *> Demonstrate string intrinsic functions DISPLAY 'String Intrinsic Functions:' DISPLAY 'Input String: ' INPUT-STRING DISPLAY ' ' *> String length function COMPUTE STRING-LENGTH = FUNCTION LENGTH(INPUT-STRING) DISPLAY 'LENGTH(' INPUT-STRING ') = ' STRING-LENGTH *> Upper case function MOVE FUNCTION UPPER-CASE(INPUT-STRING) TO UPPER-STRING DISPLAY 'UPPER-CASE(' INPUT-STRING ') = ' UPPER-STRING *> Lower case function MOVE FUNCTION LOWER-CASE(INPUT-STRING) TO LOWER-STRING DISPLAY 'LOWER-CASE(' INPUT-STRING ') = ' LOWER-STRING DISPLAY ' '. DEMONSTRATE-COMPLEX-CALCULATIONS. *> Demonstrate complex calculations using intrinsic functions DISPLAY 'Complex Calculations with Intrinsic Functions:' *> Complex calculation: sqrt(a^2 + b^2) - Pythagorean theorem COMPUTE SQUARE-ROOT = FUNCTION SQRT((INPUT-VALUE ** 2) + (100.00 ** 2)) DISPLAY 'Pythagorean theorem: sqrt(' INPUT-VALUE '^2 + 100^2) = ' SQUARE-ROOT *> Complex calculation: log base 10 of (a * b) COMPUTE LOGARITHM-VALUE = FUNCTION LOG(INPUT-VALUE * 10.00) DISPLAY 'Logarithm: log(' INPUT-VALUE ' * 10) = ' LOGARITHM-VALUE *> Complex calculation: max(sin(x), cos(x)) * 100 COMPUTE MAXIMUM-VALUE = FUNCTION MAX(SINE-VALUE, COSINE-VALUE) * 100 DISPLAY 'Max trigonometric: max(sin, cos) * 100 = ' MAXIMUM-VALUE *> Complex calculation: (abs(a) + sqrt(b)) / 2 COMPUTE FINAL-RESULT = (FUNCTION ABS(-INPUT-VALUE) + FUNCTION SQRT(INPUT-VALUE)) / 2 DISPLAY 'Complex expression: (abs(-a) + sqrt(a)) / 2 = ' FINAL-RESULT.
This example demonstrates the use of intrinsic functions within COMPUTE statements. The program shows mathematical functions like SQRT, ABS, MAX, MIN, SIN, COS, LOG, and POWER, as well as string functions like LENGTH, UPPER-CASE, and LOWER-CASE. Complex calculations combining multiple intrinsic functions are also demonstrated, showing how these functions can be used together to perform sophisticated mathematical operations.
Advanced compute operations can result in size errors, overflow conditions, or division by zero. COBOL provides mechanisms to handle these conditions gracefully using ON SIZE ERROR, ON OVERFLOW, and other exception handling clauses. Proper error handling ensures robust calculations and prevents program termination due to arithmetic exceptions.
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172IDENTIFICATION DIVISION. PROGRAM-ID. COMPUTE-ERROR-HANDLING. *> This program demonstrates error handling in advanced COMPUTE statements DATA DIVISION. WORKING-STORAGE SECTION. *> Variables for error handling demonstration 01 ERROR-DEMO-DATA. 05 LARGE-NUMBER-1 PIC 9(5)V99 VALUE 99999.99. 05 LARGE-NUMBER-2 PIC 9(5)V99 VALUE 99999.99. 05 SMALL-NUMBER PIC 9(3)V99 VALUE 0.01. 05 DIVISOR-ZERO PIC 9(3)V99 VALUE 0.00. 05 RESULT-FIELD PIC 9(8)V99. 05 ERROR-FIELD PIC 9(8)V99. 01 ERROR-CONTROLS. 05 ERROR-STATUS PIC X(1). 88 NO-ERROR VALUE 'N'. 88 SIZE-ERROR VALUE 'S'. 88 OVERFLOW-ERROR VALUE 'O'. 88 DIVIDE-ZERO-ERROR VALUE 'D'. 05 ERROR-MESSAGE PIC X(50). 01 CALCULATION-RESULTS. 05 MULTIPLICATION-RESULT PIC 9(10)V99. 05 DIVISION-RESULT PIC 9(8)V99. 05 ADDITION-RESULT PIC 9(8)V99. 05 POWER-RESULT PIC 9(12)V99. PROCEDURE DIVISION. COMPUTE-ERROR-HANDLING-MAIN. DISPLAY 'Error Handling in Advanced COMPUTE Demonstration' DISPLAY '===============================================' *> Demonstrate size error handling PERFORM DEMONSTRATE-SIZE-ERROR-HANDLING *> Demonstrate overflow error handling PERFORM DEMONSTRATE-OVERFLOW-ERROR-HANDLING *> Demonstrate division by zero handling PERFORM DEMONSTRATE-DIVISION-ZERO-HANDLING *> Demonstrate complex error handling PERFORM DEMONSTRATE-COMPLEX-ERROR-HANDLING STOP RUN. DEMONSTRATE-SIZE-ERROR-HANDLING. *> Demonstrate size error handling in COMPUTE statements DISPLAY 'Size Error Handling Demonstration:' DISPLAY 'Large Number 1: ' LARGE-NUMBER-1 DISPLAY 'Large Number 2: ' LARGE-NUMBER-2 DISPLAY ' ' *> Multiplication that will cause size error COMPUTE MULTIPLICATION-RESULT = LARGE-NUMBER-1 * LARGE-NUMBER-2 ON SIZE ERROR SET SIZE-ERROR TO TRUE MOVE 'Size error in multiplication' TO ERROR-MESSAGE DISPLAY 'SIZE ERROR: Multiplication result too large' NOT ON SIZE ERROR SET NO-ERROR TO TRUE DISPLAY 'Multiplication successful: ' MULTIPLICATION-RESULT END-COMPUTE *> Addition that might cause size error COMPUTE ADDITION-RESULT = LARGE-NUMBER-1 + LARGE-NUMBER-2 ON SIZE ERROR SET SIZE-ERROR TO TRUE MOVE 'Size error in addition' TO ERROR-MESSAGE DISPLAY 'SIZE ERROR: Addition result too large' NOT ON SIZE ERROR SET NO-ERROR TO TRUE DISPLAY 'Addition successful: ' ADDITION-RESULT END-COMPUTE DISPLAY ' '. DEMONSTRATE-OVERFLOW-ERROR-HANDLING. *> Demonstrate overflow error handling DISPLAY 'Overflow Error Handling Demonstration:' *> Power calculation that might cause overflow COMPUTE POWER-RESULT = LARGE-NUMBER-1 ** 3 ON SIZE ERROR SET OVERFLOW-ERROR TO TRUE MOVE 'Overflow in power calculation' TO ERROR-MESSAGE DISPLAY 'OVERFLOW ERROR: Power calculation overflow' NOT ON SIZE ERROR SET NO-ERROR TO TRUE DISPLAY 'Power calculation successful: ' POWER-RESULT END-COMPUTE *> Complex calculation with potential overflow COMPUTE RESULT-FIELD = (LARGE-NUMBER-1 * LARGE-NUMBER-2) + 1000.00 ON SIZE ERROR SET OVERFLOW-ERROR TO TRUE MOVE 'Overflow in complex calculation' TO ERROR-MESSAGE DISPLAY 'OVERFLOW ERROR: Complex calculation overflow' NOT ON SIZE ERROR SET NO-ERROR TO TRUE DISPLAY 'Complex calculation successful: ' RESULT-FIELD END-COMPUTE DISPLAY ' '. DEMONSTRATE-DIVISION-ZERO-HANDLING. *> Demonstrate division by zero handling DISPLAY 'Division by Zero Handling Demonstration:' DISPLAY 'Divisor Zero: ' DIVISOR-ZERO DISPLAY ' ' *> Division by zero that will cause error COMPUTE DIVISION-RESULT = LARGE-NUMBER-1 / DIVISOR-ZERO ON SIZE ERROR SET DIVIDE-ZERO-ERROR TO TRUE MOVE 'Division by zero error' TO ERROR-MESSAGE DISPLAY 'DIVISION BY ZERO ERROR: Cannot divide by zero' NOT ON SIZE ERROR SET NO-ERROR TO TRUE DISPLAY 'Division successful: ' DIVISION-RESULT END-COMPUTE *> Safe division with zero check IF DIVISOR-ZERO NOT = 0 COMPUTE DIVISION-RESULT = LARGE-NUMBER-1 / DIVISOR-ZERO ON SIZE ERROR SET DIVIDE-ZERO-ERROR TO TRUE MOVE 'Size error in safe division' TO ERROR-MESSAGE DISPLAY 'SIZE ERROR: Safe division error' NOT ON SIZE ERROR SET NO-ERROR TO TRUE DISPLAY 'Safe division successful: ' DIVISION-RESULT END-COMPUTE ELSE SET DIVIDE-ZERO-ERROR TO TRUE MOVE 'Divisor is zero - cannot divide' TO ERROR-MESSAGE DISPLAY 'DIVISION BY ZERO PREVENTED: Divisor is zero' END-IF DISPLAY ' '. DEMONSTRATE-COMPLEX-ERROR-HANDLING. *> Demonstrate complex error handling scenarios DISPLAY 'Complex Error Handling Demonstration:' *> Complex calculation with multiple potential errors COMPUTE RESULT-FIELD = (LARGE-NUMBER-1 + LARGE-NUMBER-2) * 2.00 / SMALL-NUMBER ON SIZE ERROR SET SIZE-ERROR TO TRUE MOVE 'Size error in complex calculation' TO ERROR-MESSAGE DISPLAY 'SIZE ERROR: Complex calculation size error' NOT ON SIZE ERROR SET NO-ERROR TO TRUE DISPLAY 'Complex calculation successful: ' RESULT-FIELD END-COMPUTE *> Error status summary DISPLAY 'Error Status Summary:' IF NO-ERROR DISPLAY ' Status: NO ERRORS' ELSE IF SIZE-ERROR DISPLAY ' Status: SIZE ERROR DETECTED' END-IF IF OVERFLOW-ERROR DISPLAY ' Status: OVERFLOW ERROR DETECTED' END-IF IF DIVIDE-ZERO-ERROR DISPLAY ' Status: DIVISION BY ZERO ERROR DETECTED' END-IF END-IF DISPLAY ' Error Message: ' ERROR-MESSAGE.
This example demonstrates comprehensive error handling in advanced COMPUTE statements. The program shows how to handle size errors, overflow conditions, and division by zero using ON SIZE ERROR clauses. The example includes both automatic error detection and manual error prevention techniques. Complex error handling scenarios are demonstrated, showing how multiple potential error conditions can be managed in sophisticated calculations.