Hi everybody,

I tried a simple Factorial function and the two pgms can be found below.

I think a recursive function should not be access outside memory areas,
anyway every parm passed by reference can be accessed.

So, in my opinion, having different sources can be a good solution.

It's not a "masterpiece" :D even though it seems to run properly.

As you can see I used both BY REFERENCE and BY CONTENT parms to enforce a
kinf of program isolation.

Hope this helps.

Best regards.
Massimo

Main program.

      IDENTIFICATION DIVISION.
      PROGRAM-ID. "ZPFATMAI".
      AUTHOR. TOTI.
      ENVIRONMENT DIVISION.
      DATA DIVISION.
      WORKING-STORAGE SECTION.
      01  PGMNAME     PIC X(08) VALUE 'ZPFATTOR'.
      01  RISULTATO   PIC 9(15) VALUE 0.

      LINKAGE SECTION.
      01 PARM-AREA.
        05 PARM-LENGTH   PIC S9(04) COMP.
        05 NUMERO        PIC 9(03).
        05 FILLER        PIC X(200).

      PROCEDURE DIVISION USING PARM-AREA.
          DISPLAY 'INIZIO PROGRAMMA - ZPFATMAI'.
          CALL PGMNAME USING
                       BY REFERENCE RISULTATO
                       BY CONTENT NUMERO.
          DISPLAY 'NUMERO=' NUMERO ' FATTORIALE=' RISULTATO.
      FINE.
          GOBACK.

Recursive routine.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. "ZPFATTOR" RECURSIVE.
       AUTHOR. TOTI.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  PGMNAME     PIC X(08) VALUE 'ZPFATTOR'.
       01 NUMERO-1     PIC 9(03).

       LINKAGE SECTION.
       01 RISULTATO    PIC 9(15).
       01 NUMERO       PIC 9(03).

       PROCEDURE DIVISION USING RISULTATO NUMERO.
           DISPLAY 'INIZIO PROGRAMMA - ZPFATTOR'.
           DISPLAY 'RISULTATO IN INPUT=' RISULTATO.
           DISPLAY 'NUMERO    IN INPUT=' NUMERO.
           IF NUMERO > 1 THEN
             COMPUTE NUMERO-1 = NUMERO - 1
             CALL PGMNAME USING
                          BY REFERENCE RISULTATO
                          BY CONTENT NUMERO-1
             COMPUTE RISULTATO = RISULTATO * NUMERO
           ELSE
             MOVE 1 TO RISULTATO
           END-IF.
           DISPLAY 'RISULTATO IN OUTPUT=' RISULTATO.
       FINE.



2013/7/30 John McKown <john.archie.mck...@gmail.com>

> Given our change control procedures, it would likely not be _allowed_ to
> have multiple COBOL programs in a single source member. But I'm not sure of
> that. This is a way to have RECURSIVE calls, but now we are getting very
> complicated because I'm certain that the programmer will want each separate
> program to have equal access to the WORKING-STORAGE of the "main" routine.
> Which means having all, or most, of the WORKING-STORAGE in a COPY book with
> the EXTERNAL attribute on all the 01 and 77 levels.
>
> And I just had another thought because this might be  a CICS program, the
> programmer didn't say. In which case all of this is very moot.
>
>
> On Tue, Jul 30, 2013 at 9:31 AM, John Gilmore <jwgli...@gmail.com> wrote:
>
> > Peter Farley's point, which I took as a given, is correct.  Such
> > programs need to be compiled independently, although they can of
> > course be batched together with others using process statements.
> >
> > John Gilmore, Ashland, MA 01721 - USA
> >
> > ----------------------------------------------------------------------
> > For IBM-MAIN subscribe / signoff / archive access instructions,
> > send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN
> >
>
>
>
> --
> This is a test of the Emergency Broadcast System. If this had been an
> actual emergency, do you really think we'd stick around to tell you?
>
> Maranatha! <><
> John McKown
>
> ----------------------------------------------------------------------
> For IBM-MAIN subscribe / signoff / archive access instructions,
> send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN
>

----------------------------------------------------------------------
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

Reply via email to