MainframeMaster

COBOL Tutorial

COBOL RECURSIVE Clause - Quick Reference

Progress0 of 0 lessons

Overview

The RECURSIVE clause is a program attribute that allows a COBOL program to call itself directly or indirectly. This enables recursive programming techniques where a program can solve problems by breaking them down into smaller, similar subproblems.

Purpose and Usage

  • Self-calling capability - Allows programs to call themselves
  • Divide-and-conquer algorithms - Breaks complex problems into smaller parts
  • Tree and graph traversal - Natural fit for hierarchical data structures
  • Mathematical algorithms - Factorial, Fibonacci, and other recursive functions
  • Backtracking algorithms - Search and optimization problems

Recursion Concept

Program A calls Program A (Direct Recursion)
Program A → Program A → Program A → ...
Program A calls Program B calls Program A (Indirect Recursion)
Program A → Program B → Program A → ...
Each call creates a new stack frame with its own local variables

Recursive calls create multiple instances of the program on the call stack.

Syntax

The RECURSIVE clause is specified in the PROGRAM-ID paragraph to indicate that the program can call itself.

Basic Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
* Basic RECURSIVE clause syntax PROGRAM-ID. program-name IS RECURSIVE. * Examples PROGRAM-ID. FACTORIAL IS RECURSIVE. PROGRAM-ID. TREE-TRAVERSE IS RECURSIVE. PROGRAM-ID. FIBONACCI IS RECURSIVE. * Complete program structure IDENTIFICATION DIVISION. PROGRAM-ID. RECURSIVE-EXAMPLE IS RECURSIVE. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 01 COUNTER PIC 9(3) VALUE 0. 01 RESULT PIC 9(5) VALUE 0. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM RECURSIVE-FUNCTION STOP RUN.

The RECURSIVE clause is specified in the PROGRAM-ID paragraph.

Direct vs Indirect Recursion

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
* Direct recursion - program calls itself PROGRAM-ID. DIRECT-RECURSIVE IS RECURSIVE. PROCEDURE DIVISION. MAIN-PROCESS. IF COUNTER < 10 ADD 1 TO COUNTER CALL "DIRECT-RECURSIVE" END-IF. * Indirect recursion - program A calls program B, which calls program A PROGRAM-ID. PROGRAM-A IS RECURSIVE. PROCEDURE DIVISION. MAIN-PROCESS. IF CONDITION-MET CALL "PROGRAM-B" END-IF. PROGRAM-ID. PROGRAM-B IS RECURSIVE. PROCEDURE DIVISION. MAIN-PROCESS. IF OTHER-CONDITION CALL "PROGRAM-A" END-IF.

Both direct and indirect recursion require the RECURSIVE clause.

Memory Management with RECURSIVE

Storage SectionBehavior with RECURSIVEUse Case
WORKING-STORAGEShared across all recursive callsGlobal data, constants
LOCAL-STORAGEUnique to each recursive callLocal variables, parameters
LINKAGE SECTIONParameters passed to each callInput/output parameters

Common Recursive Algorithms

These examples demonstrate common recursive algorithms and their implementation using the RECURSIVE clause in COBOL.

Factorial 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
IDENTIFICATION DIVISION. PROGRAM-ID. FACTORIAL IS RECURSIVE. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 01 INPUT-NUMBER PIC 9(3). 01 FACTORIAL-RESULT PIC 9(8). LINKAGE SECTION. 01 N PIC 9(3). 01 RESULT PIC 9(8). PROCEDURE DIVISION USING N RETURNING RESULT. MAIN-PROCESS. * Base case: factorial of 0 or 1 is 1 IF N = 0 OR N = 1 MOVE 1 TO RESULT ELSE * Recursive case: n! = n × (n-1)! SUBTRACT 1 FROM N GIVING INPUT-NUMBER CALL "FACTORIAL" USING INPUT-NUMBER RETURNING FACTORIAL-RESULT MULTIPLY N BY FACTORIAL-RESULT GIVING RESULT END-IF EXIT PROGRAM. * Example usage PROGRAM-ID. FACTORIAL-TEST. WORKING-STORAGE SECTION. 01 TEST-NUMBER PIC 9(3) VALUE 5. 01 FACTORIAL-OF-5 PIC 9(8). PROCEDURE DIVISION. MAIN-PROCESS. CALL "FACTORIAL" USING TEST-NUMBER RETURNING FACTORIAL-OF-5 DISPLAY "Factorial of " TEST-NUMBER " is " FACTORIAL-OF-5 STOP RUN.

This example shows recursive factorial calculation with proper base case handling.

Fibonacci Sequence

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
IDENTIFICATION DIVISION. PROGRAM-ID. FIBONACCI IS RECURSIVE. ENVIRONMENT DIVISION. DATA DIVISION. LINKAGE SECTION. 01 N PIC 9(3). 01 FIB-RESULT PIC 9(6). PROCEDURE DIVISION USING N RETURNING FIB-RESULT. MAIN-PROCESS. * Base cases: F(0) = 0, F(1) = 1 IF N = 0 MOVE 0 TO FIB-RESULT ELSE IF N = 1 MOVE 1 TO FIB-RESULT ELSE * Recursive case: F(n) = F(n-1) + F(n-2) CALL "FIBONACCI" USING (N - 1) RETURNING FIB-RESULT * Note: This is simplified; actual implementation would need * to handle the two recursive calls properly END-IF EXIT PROGRAM. * More efficient implementation using iteration PROGRAM-ID. FIBONACCI-ITERATIVE. WORKING-STORAGE SECTION. 01 N PIC 9(3). 01 FIB-RESULT PIC 9(6). 01 PREV-1 PIC 9(6) VALUE 0. 01 PREV-2 PIC 9(6) VALUE 1. 01 COUNTER PIC 9(3). PROCEDURE DIVISION USING N RETURNING FIB-RESULT. MAIN-PROCESS. IF N = 0 MOVE 0 TO FIB-RESULT ELSE IF N = 1 MOVE 1 TO FIB-RESULT ELSE PERFORM VARYING COUNTER FROM 2 BY 1 UNTIL COUNTER > N COMPUTE FIB-RESULT = PREV-1 + PREV-2 MOVE PREV-2 TO PREV-1 MOVE FIB-RESULT TO PREV-2 END-PERFORM END-IF EXIT PROGRAM.

Fibonacci demonstrates both recursive and iterative approaches.

Binary Tree Traversal

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. TREE-TRAVERSE IS RECURSIVE. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 01 TREE-NODE. 05 NODE-VALUE PIC 9(3). 05 LEFT-CHILD PIC X(8). 05 RIGHT-CHILD PIC X(8). PROCEDURE DIVISION USING TREE-NODE. MAIN-PROCESS. * In-order traversal: left subtree, root, right subtree IF LEFT-CHILD NOT = SPACES CALL "TREE-TRAVERSE" USING LEFT-CHILD END-IF * Process current node DISPLAY "Node value: " NODE-VALUE IF RIGHT-CHILD NOT = SPACES CALL "TREE-TRAVERSE" USING RIGHT-CHILD END-IF EXIT PROGRAM. * Example tree structure 01 SAMPLE-TREE. 05 ROOT-NODE. 10 ROOT-VALUE PIC 9(3) VALUE 50. 10 ROOT-LEFT PIC X(8) VALUE "LEFT-NODE". 10 ROOT-RIGHT PIC X(8) VALUE "RIGHT-NODE". 05 LEFT-NODE. 10 LEFT-VALUE PIC 9(3) VALUE 30. 10 LEFT-LEFT PIC X(8) VALUE SPACES. 10 LEFT-RIGHT PIC X(8) VALUE SPACES. 05 RIGHT-NODE. 10 RIGHT-VALUE PIC 9(3) VALUE 70. 10 RIGHT-LEFT PIC X(8) VALUE SPACES. 10 RIGHT-RIGHT PIC X(8) VALUE SPACES.

Tree traversal naturally lends itself to recursive implementation.

Best Practices and Tips

Following these best practices ensures effective and safe use of recursive programming in COBOL applications.

Recursion Design Principles

  • Always include a base case - Prevent infinite recursion
  • Ensure progress toward base case - Each call should move closer to termination
  • Use LOCAL-STORAGE for local variables - Ensure proper isolation between calls
  • Limit recursion depth - Prevent stack overflow
  • Consider iterative alternatives - Often more efficient for simple cases
  • Test with boundary conditions - Verify base cases work correctly

Common Pitfalls to Avoid

PitfallProblemSolution
Missing base caseInfinite recursion, stack overflowAlways define termination condition
No progress toward base caseInfinite recursionEnsure each call moves toward termination
Using WORKING-STORAGE for local dataData corruption between callsUse LOCAL-STORAGE for local variables
Deep recursionStack overflowLimit depth or use iterative approach
Poor performanceExcessive function call overheadConsider iterative alternatives

Performance Considerations

  • Function call overhead - Each recursive call has overhead
  • Stack memory usage - Each call consumes stack space
  • Cache efficiency - Recursive calls may be less cache-friendly
  • Compiler optimization - Some compilers optimize tail recursion
  • Memory allocation - Local variables are allocated for each call
  • Debugging complexity - Recursive programs can be harder to debug

When to Use Recursion

Use CaseRecursion SuitabilityReasoning
Tree/Graph traversalExcellentNatural recursive structure
Divide-and-conquerGoodProblem naturally breaks down
BacktrackingGoodState management is natural
Simple calculationsPoorIterative is usually better
High-frequency operationsPoorPerformance overhead too high

RECURSIVE Clause Quick Reference

UsageSyntaxExample
Program definitionPROGRAM-ID. name IS RECURSIVEPROGRAM-ID. FACTORIAL IS RECURSIVE
Direct recursionCALL "program-name"CALL "FACTORIAL"
With parametersCALL "program-name" USING paramCALL "FACTORIAL" USING N
With return valueCALL "program-name" RETURNING resultCALL "FACTORIAL" RETURNING RESULT
Local storageLOCAL-STORAGE SECTIONFor variables unique to each call

Test Your Knowledge

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

  • To define data types
  • To allow a program to call itself
  • To control file operations
  • To perform calculations

2. Where is the RECURSIVE clause typically specified in a COBOL program?

  • In the PROCEDURE DIVISION
  • In the PROGRAM-ID paragraph
  • In the WORKING-STORAGE SECTION
  • In the ENVIRONMENT DIVISION

3. What is required for a recursive program to work properly?

  • A base case to stop recursion
  • Only complex calculations
  • File operations
  • Screen handling

4. What is a potential risk of recursive programming in COBOL?

  • Improved performance
  • Stack overflow
  • Better memory usage
  • Faster execution

5. Which of the following is a common use case for recursive programming?

  • Simple arithmetic
  • Tree traversal and factorial calculation
  • File I/O operations
  • Screen display

Frequently Asked Questions