MainframeSupports
tip week 23/2015:

It suddenly occurred to me that I have never written a tip about recursion in COBOL. You may think it sounds like a bad joke, but it is actually possible to make recursive calls in COBOL that works. You can also get into serious trouble and I will try to illustrate both in this tip.

The following program reads the PARM field in JCL and prints the contents in the parts separated by commas. If you for instance executes the program using a TSO CALL MY.LOAD(PARSING) 'A,B B,CDE , FGH' the output on SYSOUT will look like this:

PARMNO=0001, LOCALNO=0001, VALUE=<A>
PARMNO=0002, LOCALNO=0001, VALUE=<B B>
PARMNO=0003, LOCALNO=0001, VALUE=<CDE >
PARMNO=0004, LOCALNO=0001, VALUE=< FGH>
PARMNO=0004, LOCALNO=0003 AFTER RECURSION
PARMNO=0004, LOCALNO=0002 AFTER RECURSION
PARMNO=0004, LOCALNO=0001 AFTER RECURSION

The program looks like this:

IDENTIFICATION DIVISION.
PROGRAM-ID. PARSING RECURSIVE.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  COMMAPOS PIC S9(9) BINARY.
01  PARMNO PIC S9(4) BINARY VALUE 0.
01  PGMPARM.
  02  PGMPARM-LENGTH PIC S9(4) BINARY.
  02  PGMPARM-CONTENS PIC X(100).
LOCAL-STORAGE SECTION.
01  LOCALNO PIC S9(4) BINARY VALUE 0.
LINKAGE SECTION.
01  JCLPARM.
  02  JCLPARM-LENGTH PIC S9(4) BINARY.
  02  JCLPARM-CONTENS PIC X(100).
PROCEDURE DIVISION USING JCLPARM.
    MOVE JCLPARM TO PGMPARM
    PERFORM PGMSTART
    GOBACK
    .
PGMSTART.
    MOVE 1 TO COMMAPOS
    ADD 1 TO PARMNO
    ADD 1 TO LOCALNO
    IF PGMPARM-LENGTH > 0
      INSPECT PGMPARM-CONTENS(1:PGMPARM-LENGTH)
        TALLYING COMMAPOS FOR CHARACTERS BEFORE ','
      DISPLAY 'PARMNO=' PARMNO
              ', LOCALNO=' LOCALNO ', VALUE=<'
              PGMPARM-CONTENS(1:COMMAPOS - 1) '>'
      IF COMMAPOS <= JCLPARM-LENGTH
        SUBTRACT COMMAPOS FROM PGMPARM-LENGTH
        MOVE PGMPARM-CONTENS(COMMAPOS + 1:)
          TO PGMPARM-CONTENS
        MOVE PARMNO TO LOCALNO
        CALL 'PARSING' USING PGMPARM
        DISPLAY 'PARMNO=' PARMNO
                ', LOCALNO=' LOCALNO ' AFTER RECURSION'
      END-IF
    END-IF
    .
END PROGRAM PARSING.

The first and most important detail is that when you want to use recursion in COBOL you need to write RECURSIVE after the program name specified in PROGRAM-ID. If RECURSIVE is not present you will receive a runtime error when the program calls itself either direct or indirectly through another program. You cannot use RECURSIVE on a nested/embedded program. Consequently recursion is only available with load modules. Second detail is that all variables in WORKING-STORAGE SECTION holds their values from call to call which is old news. If you have some variables that do NOT retain their values from call to call you need to declare a so-called LOCAL-STORAGE SECTION as in the above example.

You can study the functionality of WORKING-STORAGE versus LOCAL-STORAGE by relating the output to the program code. It is especially important to note that the variables that needs to contain the same value before and after the recursive call must be declared in LOCAL-STORAGE.

The experienced COBOL programmer will notice that I have not used my variables especially well. This is primarily because the program can be used to illustrate how bad it will execute if you try to make recursion using PERFORM instead of CALL. If you change CALL 'PARSING' USING PGMPARM to a PERFORM PGMSTART you ought to get the same functionality except that LOCAL-STORAGE and WORKING-STORAGE will work in the same way.

But, but, but after the first recursive call the program goes into a loop. The reason is that COBOL maintains only one return address for each paragraph/section. The result is that when PGMSTART terminates COBOL returns control to the statement right after PERFORM PGMSTART within paragraph PGMSTART. DISPLAY 'PARMNO=' PARMNO will reveal this for you when SYSOUT is filled with DISPLAY's. Remember to be ready to cancel the program if you want to check for yourself if this is really true.

Previous tip in english        Forrige danske tip        Tip list