In COBOL you can implement loops using either GO TO or PERFORM.

Since jump marks like GO TO  are notorious and considered bad coding practice, I will focus on PERFORM in this article.

Just be aware that you will find programmers using GO TO and yes, I do blame them for that no matter which programming language or how experienced they are.

GO TO should be abolished!

PERFORM

The PERFORM clause is used to redirect execution flow of a program to another paragraph than the one it is called by.

After execution of the performed paragraph has finished, control is returned to the calling paragraph.

Below is an example for usage of PERFORM.

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
      ******************************************************************
      * Author: Alexander Bolte
      * Date: 2018-06-04
      * Purpose: Demonstrates the use of PERFORM statement to call
      * different paragraphs from other parts of a COBOL program.
      * Tectonics: cobc
      ******************************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PERF-CALC.
       DATA DIVISION.
       FILE SECTION.
       WORKING-STORAGE SECTION.
      * Declare some simple variables to deal with two numbers and
      * their product.
       01  A PIC 9(2).
       01  B PIC 9(2).
       01  C PIC 9(4).
       PROCEDURE DIVISION.
       MAIN-PROCEDURE.
 
      *     First a user provides us with some numbers.
           PERFORM GET-NUMBERS.
      *     Then we display their product.
           PERFORM DISPLAY-HELLO.
 
      *     Paragraphs after the STOP RUN statement can still be called
      *     using the clause PERFORM.
           STOP RUN.
 
      * The order of calling a paragraph using PERFORM does not have to
      * match their order within a program.
      * First we are calling GET-NUMBERS, then we call DISPLAY-HELLO.
       DISPLAY-HELLO.
           COMPUTE C = A * B
           DISPLAY "A TIMES B EQUALS " C.
 
      * Get numbers from a user and store them in A and B.
       GET-NUMBERS.
           DISPLAY "Provide number A(2)."
           ACCEPT A
           DISPLAY "Provide number B(2)."
           ACCEPT B.
      *     Use the period as less as possible, but a paragraph has to end
      *     with a period.
 
       END PROGRAM PERF-CALC.
 

No Recursion Support?

"To understand recursion, one must first understand recursion!"

According to some old tutorial, I found online it is not possible to use recursive calls on paragraphs in COBOL.

That is a shame, but heck: improves code readability.

However, challenge accepted! I will give it a try and see how the GnuCOBOL compiler behaves.

The below will work in GnuCOBOL. However, older versions of this compiler or even newer versions of other proprietary compilers might not support recursion at all.

We have to bear in mind that even the COBOL changes from 2002 are probably not widely spread in businesses, since they or their programmers did not see any need for the new versions and their "fancy" stuff like object orientation.

*Sigh*, cannot wait for such people to retire.

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
      ******************************************************************
      * Author:
      * Date:
      * Purpose:
      * Tectonics: cobc
      ******************************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. REC-ME.
       DATA DIVISION.
       FILE SECTION.
       WORKING-STORAGE SECTION.
       01  A PIC 9(2).
       PROCEDURE DIVISION.
       MAIN-PROCEDURE.
 
           PERFORM DO-IT-AGAIN
           DISPLAY A
 
           STOP RUN.
 
       DO-IT-AGAIN.
           IF A < 10 THEN
               ADD 1 TO A
               PERFORM DO-IT-AGAIN
           END-IF.
       END PROGRAM REC-ME.
 

Loops implemented using PERFORM

Combined with other clauses you are able to implement different types of loops.

  • PERFORM PARAGRAPH-NAME [THRU PARAGRAPH-NAME-2] N TIMES
  • PERFORM PARAGRAPH-NAME UNTIL CONDITION
  • PERFORM PARAGRAPH-NAME VARYING X FROM N BY Y UNTIL CONDITION

PERFORM N TIMES

The PERFORM N TIMES clause is represented in other programming languages like Java by a for loop.

You are basically determining how many times you want a specific paragraph to be executed before control is returned to the calling execution flow.

Let's take a program for displaying a multiplication table on screen as example.

Since I am using GnuCOBOL to teach myself, I do not know if the below will actually work with other COBOL compilers.

However, the example should be simple enough but still demonstrate how PERFORM can be used for loops in the main paragraph as well as sub paragraphs.

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
60
61
62
63
64
65
66
67
68
69
70
      ******************************************************************
      * Author: Alexander Bolte
      * Date: 2018-06-03
      * Purpose: Gets a number from a user and displays a multiplication
      * table with according results on screen.
      * Tectonics: cobc
      ******************************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. MULT-TAB.
       DATA DIVISION.
       FILE SECTION.
       WORKING-STORAGE SECTION.
       01  A PIC 9(2) VALUE 0.
       01  B PIC 9(2) VALUE 0.
       01  C PIC 9(3).
       01  HOW-MANY-TIMES PIC 9(2).
       01  RESULT PIC X(200) VALUE " ".
 
       PROCEDURE DIVISION.
       MAIN-PROCEDURE.
 
           DISPLAY "Enter a limit for our multiplication table (0-20)."
           ACCEPT HOW-MANY-TIMES
      *     Increase the value of HOW-MANY-TIMES by one, 
      *     since this is more convinient for a user.
           ADD 1 TO HOW-MANY-TIMES
      *     Concatenate the first row with the column values of
      *     multiplicator B and display it.
           PERFORM CONCAT-FIRST-ROW HOW-MANY-TIMES TIMES
           DISPLAY "XX<" FUNCTION TRIM(RESULT)
           MOVE 0 TO C
           MOVE " " TO RESULT
      *     Build and display a multiplication table.
           PERFORM WRITE-LINE HOW-MANY-TIMES TIMES.
 
           STOP RUN.
 
       WRITE-LINE.
      *     Calculate each line 11 times 
      *     for each value between 0 and 10.
           PERFORM CALC-VALUE HOW-MANY-TIMES TIMES
      *     Display one line in a multiplication table.
           DISPLAY A "<" FUNCTION TRIM(RESULT)
      *     Increment A by one and reset B as well as RESULT.
           ADD 1 TO A
           MOVE 0 TO B
           MOVE " " TO RESULT.
 
       CALC-VALUE.
      *     Multiply A and B and store the result in C.
           MULTIPLY A BY B GIVING C
      *     Concatenate a String to hold all results for one line.
           STRING RESULT DELIMITED BY SPACES
               "-" DELIMITED BY SIZE
               C DELIMITED BY SIZE
               INTO RESULT
      *     Increment B by 1.
           ADD 1 TO B.
 
      *     Concatenates the first line displaying the value of B for
      *     each column in a multiplication table.
       CONCAT-FIRST-ROW.
           STRING RESULT DELIMITED BY SPACES
               "<" DELIMITED BY SIZE
               C DELIMITED BY SIZE
               INTO RESULT
           ADD 1 TO C.
 
       END PROGRAM MULT-TAB.
 

If you provide 20 as input the output should look as follows.

/home/abolte/Documents/GnuCOBOL/bin/multiplicationTable 

Enter a limit for our multiplication table (0-20).

20

XX<<000<001<002<003<004<005<006<007<008<009<010<011<012<013<014<015<016<017<018<019<020

00<-000-000-000-000-000-000-000-000-000-000-000-000-000-000-000-000-000-000-000-000-000

01<-000-001-002-003-004-005-006-007-008-009-010-011-012-013-014-015-016-017-018-019-020

02<-000-002-004-006-008-010-012-014-016-018-020-022-024-026-028-030-032-034-036-038-040

03<-000-003-006-009-012-015-018-021-024-027-030-033-036-039-042-045-048-051-054-057-060

04<-000-004-008-012-016-020-024-028-032-036-040-044-048-052-056-060-064-068-072-076-080

05<-000-005-010-015-020-025-030-035-040-045-050-055-060-065-070-075-080-085-090-095-100

06<-000-006-012-018-024-030-036-042-048-054-060-066-072-078-084-090-096-102-108-114-120

07<-000-007-014-021-028-035-042-049-056-063-070-077-084-091-098-105-112-119-126-133-140

08<-000-008-016-024-032-040-048-056-064-072-080-088-096-104-112-120-128-136-144-152-160

09<-000-009-018-027-036-045-054-063-072-081-090-099-108-117-126-135-144-153-162-171-180

10<-000-010-020-030-040-050-060-070-080-090-100-110-120-130-140-150-160-170-180-190-200

11<-000-011-022-033-044-055-066-077-088-099-110-121-132-143-154-165-176-187-198-209-220

12<-000-012-024-036-048-060-072-084-096-108-120-132-144-156-168-180-192-204-216-228-240

13<-000-013-026-039-052-065-078-091-104-117-130-143-156-169-182-195-208-221-234-247-260

14<-000-014-028-042-056-070-084-098-112-126-140-154-168-182-196-210-224-238-252-266-280

15<-000-015-030-045-060-075-090-105-120-135-150-165-180-195-210-225-240-255-270-285-300

16<-000-016-032-048-064-080-096-112-128-144-160-176-192-208-224-240-256-272-288-304-320

17<-000-017-034-051-068-085-102-119-136-153-170-187-204-221-238-255-272-289-306-323-340

18<-000-018-036-054-072-090-108-126-144-162-180-198-216-234-252-270-288-306-324-342-360

19<-000-019-038-057-076-095-114-133-152-171-190-209-228-247-266-285-304-323-342-361-380

20<-000-020-040-060-080-100-120-140-160-180-200-220-240-260-280-300-320-340-360-380-400

 

Process finished with exit code 0

Using the clause THRU or THROUGH you are able to perform more than one paragraph after each other in only one loop.

Of course the same can be achieved using nested PERFORM loops as I did in above example, but THRU looks more elegant.

However, for me this is the less readable form of code and I like code, which can be read easily.

PERFORM ... UNTIL

PERFORM [PARAGRAPH-NAME] UNTIL [CONDITION]

This command is running a paragraph until a certain condition is met.

The clause represents a while loop, as we know it from other programming languages like Java.

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
      ******************************************************************
      * Author: Alexander Bolte
      * Date: 2018-06-05
      * Purpose: Demonstrates the use of PERFORM ... UNTIL.
      * Tectonics: cobc
      ******************************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. YOUR-PROGRAM-NAME.
       DATA DIVISION.
       FILE SECTION.
       WORKING-STORAGE SECTION.
       01  A PIC 9(3) VALUE 1.
       01  B PIC 9(2) VALUE 1.
       01  C PIC 9(3).
      
       PROCEDURE DIVISION.
       MAIN-PROCEDURE.
           
           PERFORM CALC-SOME UNTIL A > 100
           DISPLAY A.
           
           STOP RUN.
           
       CALC-SOME.    
           COMPUTE C = A * B
           DISPLAY A " * " B " = " C
           MOVE C TO A
           ADD 1 TO B.
           
       END PROGRAM YOUR-PROGRAM-NAME.
 

The above program will print the following.

/home/abolte/Documents/GnuCOBOL/bin/performUntil 

001 * 01 = 001

001 * 02 = 002

002 * 03 = 006

006 * 04 = 024

024 * 05 = 120

120

 

Process finished with exit code 0

PERFORM ... VARYING ...

PERFORM [PARAGRAPH-NAME] VARYING [VARIABLE] FROM [X] BY [Y] UNTIL [CONDITION]

Below an example using the VARYING clause. It is used to define a variable change outside of a paragraph called by the loop.

In addition you are able to specify in which intervals a control variable is changed.

In this example I am increasing the control variable by two with every step in the loop until its value reaches more than 50.

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
      ******************************************************************
      * Author: Alexander Bolte
      * Date: 2018-06-05
      * Purpose: Demonstrates the use of PERFORM ... VARYING.
      * Tectonics: cobc
      ******************************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PERF-VAR.
       DATA DIVISION.
       FILE SECTION.
       WORKING-STORAGE SECTION.
       01  A PIC 9(3) VALUE 100.
       01  B PIC 9(2).
       PROCEDURE DIVISION.
       MAIN-PROCEDURE.
     
           PERFORM CALC-MOD VARYING B FROM 1 BY 2 UNTIL B > 50     
            
           STOP RUN.
            
       CALC-MOD.
           DISPLAY A " MOD " B " -> " FUNCTION MOD(A,B).
       
       END PROGRAM PERF-VAR.
 

 The output of above program looks as follows.

/home/abolte/Documents/GnuCOBOL/bin/bin/performVarying 

100 MOD 01 -> +000000000000000000

100 MOD 03 -> +000000000000000001

100 MOD 05 -> +000000000000000000

100 MOD 07 -> +000000000000000002

100 MOD 09 -> +000000000000000001

100 MOD 11 -> +000000000000000001

100 MOD 13 -> +000000000000000009

100 MOD 15 -> +000000000000000010

100 MOD 17 -> +000000000000000015

100 MOD 19 -> +000000000000000005

100 MOD 21 -> +000000000000000016

100 MOD 23 -> +000000000000000008

100 MOD 25 -> +000000000000000000

100 MOD 27 -> +000000000000000019

100 MOD 29 -> +000000000000000013

100 MOD 31 -> +000000000000000007

100 MOD 33 -> +000000000000000001

100 MOD 35 -> +000000000000000030

100 MOD 37 -> +000000000000000026

100 MOD 39 -> +000000000000000022

100 MOD 41 -> +000000000000000018

100 MOD 43 -> +000000000000000014

100 MOD 45 -> +000000000000000010

100 MOD 47 -> +000000000000000006

100 MOD 49 -> +000000000000000002

 

Process finished with exit code 0