MainframeMaster

COBOL Tutorial

COBOL REMAINDER Clause - Quick Reference

Progress0 of 0 lessons

Overview

The REMAINDER clause is used in DIVIDE statements to capture the remainder value from division operations. It enables modular arithmetic and is essential for calculations that need to know what's left over after division.

Purpose and Usage

  • Modular arithmetic - Capture remainder from division
  • Even/odd detection - Determine if numbers are even or odd
  • Circular calculations - Implement circular buffers and arrays
  • Validation codes - Calculate check digits and validation
  • Data distribution - Implement round-robin algorithms

Mathematical Concept

Dividend ÷ Divisor = Quotient with Remainder
17 ÷ 5 = 3 remainder 2
17 = (5 × 3) + 2
REMAINDER captures the "2" in this example

REMAINDER represents what's left after division is complete.

Syntax

The REMAINDER clause follows specific syntax patterns within DIVIDE statements and can be combined with other arithmetic options.

Basic Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
* Basic REMAINDER clause syntax DIVIDE divisor INTO dividend REMAINDER remainder-field * With GIVING clause DIVIDE dividend BY divisor GIVING quotient REMAINDER remainder-field * Complete example DIVIDE 17 BY 5 GIVING QUOTIENT REMAINDER REMAINDER-VALUE * With data names DIVIDE DIVIDEND-VALUE BY DIVISOR-VALUE GIVING QUOTIENT-RESULT REMAINDER REMAINDER-RESULT * With ROUNDED option DIVIDE TOTAL-AMOUNT BY ITEM-COUNT GIVING AVERAGE-AMOUNT REMAINDER REMAINDER-AMOUNT ROUNDED

REMAINDER can be used with both INTO and BY forms of DIVIDE.

REMAINDER vs ROUNDED Comparison

ClausePurposeResult
REMAINDERCapture remainder valueWhat\'s left after division
ROUNDEDRound quotientRounded quotient value
BothRound quotient + get remainderBoth values available

Data Type Considerations

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
* Integer division with REMAINDER 01 INTEGER-DIVIDEND PIC 9(3) VALUE 17. 01 INTEGER-DIVISOR PIC 9(2) VALUE 5. 01 INTEGER-QUOTIENT PIC 9(2). 01 INTEGER-REMAINDER PIC 9(2). DIVIDE INTEGER-DIVIDEND BY INTEGER-DIVISOR GIVING INTEGER-QUOTIENT REMAINDER INTEGER-REMAINDER. * Decimal division with REMAINDER 01 DECIMAL-DIVIDEND PIC 9(3)V99 VALUE 10.50. 01 DECIMAL-DIVISOR PIC 9(2)V99 VALUE 3.00. 01 DECIMAL-QUOTIENT PIC 9(2)V99. 01 DECIMAL-REMAINDER PIC 9(2)V99. DIVIDE DECIMAL-DIVIDEND BY DECIMAL-DIVISOR GIVING DECIMAL-QUOTIENT REMAINDER DECIMAL-REMAINDER.

REMAINDER works with both integer and decimal arithmetic.

Practical Examples

These examples demonstrate how to use the REMAINDER clause effectively in different programming scenarios.

Even/Odd Number Detection

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
IDENTIFICATION DIVISION. PROGRAM-ID. EVEN-ODD-CHECK. DATA DIVISION. WORKING-STORAGE SECTION. 01 NUMBER-TO-CHECK PIC 9(4) VALUE 1234. 01 REMAINDER-VALUE PIC 9(1). 01 RESULT-MESSAGE PIC X(20). PROCEDURE DIVISION. MAIN-PROCESS. * Check if number is even or odd DIVIDE NUMBER-TO-CHECK BY 2 REMAINDER REMAINDER-VALUE * Determine result based on remainder IF REMAINDER-VALUE = 0 MOVE "Number is EVEN" TO RESULT-MESSAGE ELSE MOVE "Number is ODD" TO RESULT-MESSAGE END-IF DISPLAY "Number: " NUMBER-TO-CHECK DISPLAY "Result: " RESULT-MESSAGE STOP RUN. * Alternative using condition names 01 NUMBER-TO-CHECK PIC 9(4) VALUE 1234. 01 REMAINDER-VALUE PIC 9(1). 88 IS-EVEN VALUE 0. 88 IS-ODD VALUE 1. PROCEDURE DIVISION. MAIN-PROCESS. DIVIDE NUMBER-TO-CHECK BY 2 REMAINDER REMAINDER-VALUE EVALUATE TRUE WHEN IS-EVEN DISPLAY "Number is EVEN" WHEN IS-ODD DISPLAY "Number is ODD" END-EVALUATE.

REMAINDER is perfect for determining if a number is even or odd.

Day of Week Calculation

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
* Calculate day of week (0=Sunday, 1=Monday, etc.) 01 DAYS-SINCE-EPOCH PIC 9(8) VALUE 18765. 01 DAY-OF-WEEK PIC 9(1). 01 DAY-NAMES. 05 FILLER PIC X(9) VALUE "Sunday". 05 FILLER PIC X(9) VALUE "Monday". 05 FILLER PIC X(9) VALUE "Tuesday". 05 FILLER PIC X(9) VALUE "Wednesday". 05 FILLER PIC X(9) VALUE "Thursday". 05 FILLER PIC X(9) VALUE "Friday". 05 FILLER PIC X(9) VALUE "Saturday". 01 DAY-NAME-TABLE REDEFINES DAY-NAMES. 05 DAY-NAME PIC X(9) OCCURS 7 TIMES. PROCEDURE DIVISION. CALCULATE-DAY. * Calculate day of week using remainder DIVIDE DAYS-SINCE-EPOCH BY 7 REMAINDER DAY-OF-WEEK * Display day name DISPLAY "Day of week: " DAY-NAME(DAY-OF-WEEK + 1) STOP RUN. * Alternative with offset (if epoch starts on different day) 01 DAYS-SINCE-EPOCH PIC 9(8) VALUE 18765. 01 EPOCH-OFFSET PIC 9(1) VALUE 4. * Thursday 01 DAY-OF-WEEK PIC 9(1). PROCEDURE DIVISION. CALCULATE-DAY-WITH-OFFSET. * Add offset and calculate remainder ADD EPOCH-OFFSET TO DAYS-SINCE-EPOCH DIVIDE DAYS-SINCE-EPOCH BY 7 REMAINDER DAY-OF-WEEK DISPLAY "Day of week: " DAY-NAME(DAY-OF-WEEK + 1).

REMAINDER is essential for circular calculations like day of week.

Circular Buffer Implementation

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
* Circular buffer using REMAINDER 01 BUFFER-SIZE PIC 9(2) VALUE 10. 01 CURRENT-INDEX PIC 9(2) VALUE 0. 01 BUFFER-ARRAY. 05 BUFFER-ELEMENT PIC X(20) OCCURS 10 TIMES. 01 NEW-INDEX PIC 9(2). PROCEDURE DIVISION. ADD-TO-BUFFER. * Add item to circular buffer MOVE "New Item" TO BUFFER-ELEMENT(CURRENT-INDEX + 1) * Calculate next index using remainder ADD 1 TO CURRENT-INDEX DIVIDE CURRENT-INDEX BY BUFFER-SIZE REMAINDER NEW-INDEX MOVE NEW-INDEX TO CURRENT-INDEX DISPLAY "Added item at position: " CURRENT-INDEX. READ-FROM-BUFFER. * Read item from circular buffer DISPLAY "Reading from position: " CURRENT-INDEX DISPLAY "Item: " BUFFER-ELEMENT(CURRENT-INDEX + 1) * Move to next position ADD 1 TO CURRENT-INDEX DIVIDE CURRENT-INDEX BY BUFFER-SIZE REMAINDER NEW-INDEX MOVE NEW-INDEX TO CURRENT-INDEX.

REMAINDER enables efficient circular buffer implementations.

Check Digit Calculation

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
* Calculate check digit using REMAINDER 01 ACCOUNT-NUMBER PIC 9(8) VALUE 12345678. 01 WEIGHTED-SUM PIC 9(4) VALUE 0. 01 CHECK-DIGIT PIC 9(1). 01 WEIGHTS. 05 FILLER PIC 9(1) OCCURS 8 TIMES VALUE 1. 01 WEIGHT-TABLE REDEFINES WEIGHTS. 05 WEIGHT PIC 9(1) OCCURS 8 TIMES. 01 I PIC 9(1). PROCEDURE DIVISION. CALCULATE-CHECK-DIGIT. * Set up weights (alternating 1 and 3) MOVE 1 TO WEIGHT(1) MOVE 3 TO WEIGHT(2) MOVE 1 TO WEIGHT(3) MOVE 3 TO WEIGHT(4) MOVE 1 TO WEIGHT(5) MOVE 3 TO WEIGHT(6) MOVE 1 TO WEIGHT(7) MOVE 3 TO WEIGHT(8) * Calculate weighted sum PERFORM VARYING I FROM 1 BY 1 UNTIL I > 8 COMPUTE WEIGHTED-SUM = WEIGHTED-SUM + (ACCOUNT-NUMBER(I:1) * WEIGHT(I)) END-PERFORM * Calculate check digit using remainder DIVIDE WEIGHTED-SUM BY 10 REMAINDER CHECK-DIGIT * If remainder is 0, check digit is 0, otherwise it's 10 - remainder IF CHECK-DIGIT = 0 MOVE 0 TO CHECK-DIGIT ELSE COMPUTE CHECK-DIGIT = 10 - CHECK-DIGIT END-IF DISPLAY "Account Number: " ACCOUNT-NUMBER DISPLAY "Check Digit: " CHECK-DIGIT STOP RUN.

REMAINDER is essential for validation code calculations.

Error Handling and Best Practices

Understanding error handling and best practices ensures reliable use of the REMAINDER clause.

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
* REMAINDER with error handling 01 DIVIDEND-VALUE PIC 9(3) VALUE 100. 01 DIVISOR-VALUE PIC 9(2) VALUE 0. 01 QUOTIENT-RESULT PIC 9(3). 01 REMAINDER-RESULT PIC 9(2). PROCEDURE DIVISION. SAFE-DIVIDE. * Check for division by zero IF DIVISOR-VALUE = 0 DISPLAY "Error: Division by zero" STOP RUN END-IF * Perform division with REMAINDER DIVIDE DIVIDEND-VALUE BY DIVISOR-VALUE GIVING QUOTIENT-RESULT REMAINDER REMAINDER-RESULT ON SIZE ERROR DISPLAY "Error: Result too large for field" NOT ON SIZE ERROR DISPLAY "Quotient: " QUOTIENT-RESULT DISPLAY "Remainder: " REMAINDER-RESULT END-DIVIDE. * Alternative with validation PROCEDURE DIVISION. VALIDATED-DIVIDE. * Validate inputs IF DIVIDEND-VALUE < 0 OR DIVISOR-VALUE <= 0 DISPLAY "Error: Invalid input values" STOP RUN END-IF * Ensure remainder field is large enough IF DIVISOR-VALUE > 99 DISPLAY "Error: Divisor too large for remainder field" STOP RUN END-IF DIVIDE DIVIDEND-VALUE BY DIVISOR-VALUE GIVING QUOTIENT-RESULT REMAINDER REMAINDER-RESULT.

Always check for division by zero and validate inputs.

Best Practices

  • Check for division by zero - Always validate divisor before division
  • Size remainder field appropriately - Ensure it can hold maximum remainder
  • Use meaningful variable names - Make code self-documenting
  • Handle edge cases - Consider boundary conditions
  • Test with various inputs - Verify behavior with different values
  • Document the algorithm - Explain the mathematical logic

Common Pitfalls to Avoid

PitfallProblemSolution
Division by zeroRuntime errorCheck divisor before division
Insufficient field sizeData overflowSize remainder field appropriately
Negative remaindersUnexpected resultsUse absolute values or handle signs
Decimal precisionRounding errorsUnderstand decimal arithmetic behavior
Confusing with ROUNDEDWrong resultsUnderstand difference between clauses

Performance Considerations

  • Integer vs decimal - Integer division is faster than decimal
  • Field sizes - Smaller fields use less memory and may be faster
  • Frequent calculations - Consider caching results for repeated operations
  • Compiler optimization - Some compilers optimize remainder calculations
  • Hardware support - Modern processors have efficient remainder operations

REMAINDER Clause Quick Reference

UsageSyntaxExample
Basic REMAINDERDIVIDE dividend BY divisor REMAINDER fieldDIVIDE 17 BY 5 REMAINDER REMAINDER-VALUE
With GIVINGDIVIDE dividend BY divisor GIVING quotient REMAINDER fieldDIVIDE 17 BY 5 GIVING QUOTIENT REMAINDER REMAINDER-VALUE
With INTODIVIDE divisor INTO dividend REMAINDER fieldDIVIDE 5 INTO 17 REMAINDER REMAINDER-VALUE
With ROUNDEDDIVIDE dividend BY divisor GIVING quotient REMAINDER field ROUNDEDDIVIDE 17 BY 5 GIVING QUOTIENT REMAINDER REMAINDER-VALUE ROUNDED
Error handlingDIVIDE dividend BY divisor GIVING quotient REMAINDER field ON SIZE ERRORDIVIDE 17 BY 5 GIVING QUOTIENT REMAINDER REMAINDER-VALUE ON SIZE ERROR

Test Your Knowledge

1. What is the primary purpose of the REMAINDER clause in COBOL?

  • To perform division
  • To capture the remainder from division
  • To round numbers
  • To perform multiplication

2. In which statement is the REMAINDER clause most commonly used?

  • MULTIPLY
  • DIVIDE
  • ADD
  • SUBTRACT

3. What happens when you use REMAINDER in a DIVIDE statement?

  • The quotient is stored
  • The remainder is stored in the specified field
  • The dividend is modified
  • The divisor is changed

4. What is the mathematical relationship between DIVIDE and REMAINDER?

  • They are unrelated
  • REMAINDER is the fractional part
  • REMAINDER is what's left after division
  • REMAINDER is the quotient

5. Which of the following is a valid REMAINDER clause usage?

  • REMAINDER IS data-name
  • REMAINDER data-name
  • REMAINDER INTO data-name
  • All of the above

Frequently Asked Questions