• Need an example CALL USING RETURNING

    From Bruce Axtens@snetxa@hotmail.com to comp.lang.cobol on Sat Apr 6 09:46:48 2024
    From Newsgroup: comp.lang.cobol

    Covid is stealing my sleep and my intelligence

    FRAME.COB copybook's in the source of SOURCE.COB. It's something I saw
    in the FAQ.

    I'm trying to demonstrate to myself how to do user-defined functions.
    --- FRAME.COB
    IDENTIFICATION DIVISION.
    PROGRAM-ID. frame.
    DATA DIVISION.
    working-storage SECTION.
    01 FOO PIC XXX VALUE "FOO".
    01 OOF PIC XXX.
    PROCEDURE DIVISION.
    CALL "SOURCE" USING FOO returning into oof.
    IF OOF NOT = "OOF"
    DISPLAY "FAIL"
    ELSE
    DISPLAY "PASS"
    END-IF.
    STOP RUN.

    COPY "SOURCE.COB".
    END PROGRAM frame.


    --- SOURCE.COB
    PROGRAM-ID. SOURCE.
    DATA DIVISION.
    linkage SECTION.
    01 RES PIC XXX.
    01 FOO PIC XXX.
    PROCEDURE DIVISION USING FOO res.
    display foo.
    MOVE FUNCTION REVERSE(FOO) TO RES.
    EXIT PROGRAM.
    END PROGRAM SOURCE.


    Can someone please point out the screamingly obvious?

    The context for this is that there are some things about CobolCheck that
    are really good and some that suck and this is at the end of one
    rabbithole looking for different ways of testing student code.
    --- Synchronet 3.20a-Linux NewsLink 1.114
  • From Arnold Trembley@arnold.trembley@att.net to comp.lang.cobol on Sat Apr 6 04:38:02 2024
    From Newsgroup: comp.lang.cobol

    On 2024-04-05 8:46 PM, Bruce Axtens wrote:
    Covid is stealing my sleep and my intelligence

    FRAME.COB copybook's in the source of SOURCE.COB. It's something I saw
    in the FAQ.

    I'm trying to demonstrate to myself how to do user-defined functions.
    --- FRAME.COB
           IDENTIFICATION   DIVISION.
           PROGRAM-ID.      frame.
           DATA DIVISION.
           working-storage SECTION.
           01 FOO PIC XXX VALUE "FOO".
           01 OOF PIC XXX.
           PROCEDURE        DIVISION.
               CALL "SOURCE" USING FOO returning into oof.
               IF OOF NOT = "OOF"
                 DISPLAY "FAIL"
               ELSE
                 DISPLAY "PASS"
               END-IF.
               STOP RUN.

           COPY "SOURCE.COB".
           END PROGRAM frame.


    --- SOURCE.COB
           PROGRAM-ID.      SOURCE.
           DATA DIVISION.
           linkage SECTION.
           01 RES PIC XXX.
           01 FOO PIC XXX.
           PROCEDURE        DIVISION USING FOO res.
               display foo.
               MOVE FUNCTION REVERSE(FOO) TO RES.
               EXIT PROGRAM.
           END PROGRAM SOURCE.


    Can someone please point out the screamingly obvious?

    The context for this is that there are some things about CobolCheck that
    are really good and some that suck and this is at the end of one
    rabbithole looking for different ways of testing student code.

    I don't see any user-defined functions in the example.

    The following is based on my (possibly incorrect) reading of the
    GnuCOBOL 3.2 Programmer's Guide.

    A user-defined function must use FUNCTION-ID instead of PROGRAM-ID, and
    must also be declared in the calling program's REPOSITORY in the
    CONFIGURATION SECTION.

    FUNCTION REVERSE is an ISO standard intrinsic function. It's already
    built into the compiler, so it cannot be a user-defined function.

    RETURNING is part of the PROCEDURE DIVISION in the called subprogram or function, and must be declared along with the USING clause. The
    RETURNING item must be defined as USAGE BINARY-LONG, which does NOT have
    a picture clause.

    BINARY-LONG will be either 32 bits or 64 bits, depending on the pointer
    size supported by your GnuCOBOL compiler. GnuCOBOL can be built to use
    either 32-bit or 64-bit addresses.

    So your user-defined function probably needs to look something like this:

    --- SOURCE.COB
    FUNCTION-ID. SOURCE.
    DATA DIVISION.
    linkage SECTION.
    01 RES USAGE BINARY-LONG.
    01 FOO PIC XXX.
    PROCEDURE DIVISION USING FOO RETURNING res.
    display foo.
    MOVE FUNCTION REVERSE(FOO) TO RES.
    EXIT PROGRAM.
    END FUNCTION SOURCE.

    And your calling program probably needs a REPOSITORY clause after the CONFIGURATION SECTION SPECIAL-NAMES paragraph that looks like this:

    REPOSITORY.
    FUNCTION ALL INTRINSIC
    FUNCTION SOURCE.

    Since SOURCE may be a COBOL reserved word, you might need to rename your
    user defined function. If SOURCE is a reserved COBOL word, you will get
    some strange compile time errors.

    FUNCTION ALL INTRINSIC is not required if your GnuCOBOL configuration
    file is IBM-strict or MVS-strict, since that is the default when
    emulating IBM syntax. Otherwise, you would need FUNCTION ALL INTRINSIC
    to allow you to use any or all of the intrinsic functions from
    the 1989 appendix to the 1985 ISO Standard.

    Nested subprograms or user-defined functions inherit the REPOSITORY
    defined in the calling program.

    I cannot guarantee my reading is correct in all details, but I hope that helps!

    Kind regards,
    --
    https://www.arnoldtrembley.com/


    --
    This email has been checked for viruses by Avast antivirus software. www.avast.com
    --- Synchronet 3.20a-Linux NewsLink 1.114
  • From R Daneel Olivaw@Danny@hyperspace.vogon.gov to comp.lang.cobol on Sat Apr 6 13:47:41 2024
    From Newsgroup: comp.lang.cobol

    Bruce Axtens wrote:
    Covid is stealing my sleep and my intelligence

    FRAME.COB copybook's in the source of SOURCE.COB. It's something I saw
    in the FAQ.

    I'm trying to demonstrate to myself how to do user-defined functions.
    --- FRAME.COB
           IDENTIFICATION   DIVISION.
           PROGRAM-ID.      frame.
           DATA DIVISION.
           working-storage SECTION.
           01 FOO PIC XXX VALUE "FOO".
           01 OOF PIC XXX.
           PROCEDURE        DIVISION.
               CALL "SOURCE" USING FOO returning into oof.
               IF OOF NOT = "OOF"
                 DISPLAY "FAIL"
               ELSE
                 DISPLAY "PASS"
               END-IF.
               STOP RUN.

           COPY "SOURCE.COB".
           END PROGRAM frame.


    --- SOURCE.COB
           PROGRAM-ID.      SOURCE.
           DATA DIVISION.
           linkage SECTION.
           01 RES PIC XXX.
           01 FOO PIC XXX.
           PROCEDURE        DIVISION USING FOO res.
               display foo.
               MOVE FUNCTION REVERSE(FOO) TO RES.
               EXIT PROGRAM.
           END PROGRAM SOURCE.


    Can someone please point out the screamingly obvious?

    The context for this is that there are some things about CobolCheck that
    are really good and some that suck and this is at the end of one
    rabbithole looking for different ways of testing student code.

    My experience with Cobol is on mainframes, and before user-defined
    functions were created.
    I'd expect you to be using: CALL "SOURCE" USING FOO OOF.

    The syntax "returning into" is unknown to me, but backward compatibility
    would seem to mandate that the CALL line is as I gave above.
    --- Synchronet 3.20a-Linux NewsLink 1.114
  • From Bruce Axtens@snetxa@hotmail.com to comp.lang.cobol on Sat Apr 6 20:29:06 2024
    From Newsgroup: comp.lang.cobol

    So I finally figured myself out on this one. I wasn't after a function
    at all.

    Some background is in order: I'm a maintainer of the COBOL track at Exercism.org. I've been thinking of changing how we do testing. We've
    been using COBOLCHECK which has been adequate but not without issues. I
    was intrigued by how autoconf was used and that there was an example of
    a COBOL program embedded in COBOL program in the FAQ. I thought to adapt
    that by having each test "COPY" the students work in at compile time. I
    wrote a POC which is being discussed at https://forum.exercism.org/t/rethinking-the-use-of-cobolcheck/10665

    A frame might contain
    ---
    IDENTIFICATION DIVISION.
    PROGRAM-ID. frame.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 WS-ARGUMENT PIC XXX VALUE "FOO".
    01 WS-RESULT PIC XXX.
    PROCEDURE DIVISION.
    CALL "source" USING WS-ARGUMENT WS-RESULT.
    IF WS-RESULT NOT = "OOF"
    DISPLAY "FAIL"
    ELSE
    DISPLAY "PASS"
    END-IF.
    STOP RUN.

    COPY "source.cob".
    END PROGRAM frame.
    ---
    and a student's work
    ---
    IDENTIFICATION DIVISION.
    PROGRAM-ID. source.
    DATA DIVISION.
    LINKAGE SECTION.
    01 LS-RESULT PIC XXX.
    01 LS-ARGUMENT PIC XXX.
    PROCEDURE DIVISION USING LS-ARGUMENT LS-RESULT.
    MOVE FUNCTION REVERSE(LS-ARGUMENT) TO LS-RESULT.
    END PROGRAM source.
    ---
    As said in the Exercism forum post:
    I don’t have any COBOL industry experience. I learned COBOL in 1983
    and loved it but never got to do anything constructive with it until I
    helped get the COBOL track here going. What’s the usual deal out there
    in the “real world”? Do people write standalones or do they learn early how to write callables? What should we be teaching?

    --- Synchronet 3.20a-Linux NewsLink 1.114
  • From docdwarf@docdwarf@panix.com () to comp.lang.cobol on Sat Apr 6 13:04:33 2024
    From Newsgroup: comp.lang.cobol

    In article <uurf6i$22csg$1@dont-email.me>,
    Bruce Axtens <snetxa@hotmail.com> wrote:

    [snip]

    What???s the usual deal out there
    in the ???real world???? Do people write standalones or do they learn early >how to write callables? What should we be teaching?

    You should be teaching what the language is capable of using. I'm not
    sure where this 'real world' is but im my experience every shop has its standards - or waves of standards, and just like each wave leaves its own
    bit of jetsam on the shore each wave of New Standard leaves... stuff in
    the code - and it's up to a Senior Programmer to tell the New Guy 'sure,
    it can be done that way... but the Way We Do It Here is...'

    I've sorked in shops where the SEARCH verb was forbidden, spit out by pre-compiling tools, because 'people get confused by it' (or Chief Senior Programmer didn't understand it). Same with SORT. Same with INSPECT REPLACING because 'you Never Know when the subroutine will be wanted in
    the Online region and that's a Bad Thing.'

    It's frustrating but... their shop, their rules. Find where they keep
    their skels ('templates'), read the code and learn their songs.'

    DD
    --- Synchronet 3.20a-Linux NewsLink 1.114
  • From Bruce Axtens@snetxa@hotmail.com to comp.lang.cobol on Sat Apr 6 21:11:52 2024
    From Newsgroup: comp.lang.cobol

    On 6/4/24 21:04, docdwarf@panix.com wrote:
    Find where they keep
    their skels ('templates'), read the code and learn their songs.'
    Which is essentially what I tell the mentees somewhere in the
    discussions I have with them.

    Yeah, "real world" is an unreal term, I grant you that. I suppose I
    should go and talk to folk who define the pedagogy of Exercism and ask
    them. And contribute to the teaching notes that the other mentors use.

    Bruce

    --- Synchronet 3.20a-Linux NewsLink 1.114
  • From docdwarf@docdwarf@panix.com () to comp.lang.cobol on Sat Apr 6 17:04:49 2024
    From Newsgroup: comp.lang.cobol

    In article <uurhmo$22csf$1@dont-email.me>,
    Bruce Axtens <snetxa@hotmail.com> wrote:
    On 6/4/24 21:04, docdwarf@panix.com wrote:
    Find where they keep
    their skels ('templates'), read the code and learn their songs.'
    Which is essentially what I tell the mentees somewhere in the
    discussions I have with them.

    I was contracted to build some CICS code a few years ago and the 'specs'
    said 'Accept and validate the date.'

    I went to the Group Lead - a surly man who didn't have a moment for anyone
    who wasn't an employee: subordinates to torment, superiors to suck up to
    and peers to backstab - and asked 'What's your standard for this?'

    The response was 'you're a contractor, it's a date routine, how hard can
    it be, stop bothering me.'

    So... I looked at a stack of greenbar and saw where the copylibs were and
    I started to browse them for helpful hints.

    Thirty minutes later the Group Lead brought me into the Corner Office
    Idiot's office and shouted 'I caught this guy browsing through our source libraries, he's probably a spy, looking to steal our code!'

    I picked my jaw up off the floor and said to the COI I received an
    assignment asking for a date routine and I was trying to maintain site standards and decrease duplicate effort.'

    'Yeah, that's the garbage he said to me, too... he's a contractor, he's so smart let him write his own!'

    The COI shrugged and said 'He's the Group Leader and his Group follows his lead.'

    I got back to my desk, called my headhunter and said 'I've just been put
    in an impossible situation and told 'our way or the highway'. I'm taking
    the second option.'

    The headhunter said 'Yeah, we get a lot of that from there. If I see something else I'll call you.'

    Yeah, "real world" is an unreal term, I grant you that.

    Things may be different now, what I related occured when YYYY started with
    19.

    DD
    --- Synchronet 3.20a-Linux NewsLink 1.114
  • From R Daneel Olivaw@Danny@hyperspace.vogon.gov to comp.lang.cobol on Sat Apr 6 22:06:34 2024
    From Newsgroup: comp.lang.cobol

    docdwarf@panix.com wrote:
    In article <uurf6i$22csg$1@dont-email.me>,
    Bruce Axtens <snetxa@hotmail.com> wrote:

    [snip]

    What???s the usual deal out there
    in the ???real world???? Do people write standalones or do they learn early >> how to write callables? What should we be teaching?

    You should be teaching what the language is capable of using. I'm not
    sure where this 'real world' is but im my experience every shop has its standards - or waves of standards, and just like each wave leaves its own
    bit of jetsam on the shore each wave of New Standard leaves... stuff in
    the code - and it's up to a Senior Programmer to tell the New Guy 'sure,
    it can be done that way... but the Way We Do It Here is...'

    I've sorked in shops where the SEARCH verb was forbidden, spit out by pre-compiling tools, because 'people get confused by it' (or Chief Senior Programmer didn't understand it). Same with SORT. Same with INSPECT REPLACING because 'you Never Know when the subroutine will be wanted in
    the Online region and that's a Bad Thing.'

    It's frustrating but... their shop, their rules. Find where they keep
    their skels ('templates'), read the code and learn their songs.'

    DD


    I have never worked on a site where SEARCH or INSPECT REPLACING were forbidden, that's ludicrous.
    SORT is a bit different, some of the programs I wrote ran in Transaction environments, and there were memory constraints. These programs did not normally perform any sorting anyway, but in one case - sorting a table
    in memory - I actually managed to get a C sorting library to work for me. "Transaction environments" could be "Online" in your terminology.
    --- Synchronet 3.20a-Linux NewsLink 1.114
  • From Vincent Coen@VBCoen@gmail.com to Bruce Axtens on Sat Apr 6 23:27:53 2024
    From Newsgroup: comp.lang.cobol

    Hello Bruce!

    Saturday April 06 2024 02:46, Bruce Axtens wrote to All:

    Does not the 2nd element need :

    FUNCTION-ID. SOURCE.

    Instead of PROGRAM-ID
    for a function definition but there again 2nd is a module so does not
    matter as you defined it by PROGRAM-ID.


    Change the name as well as SOURCE is a reserved word.


    The interesting thing about Cobol is there is always multi. ways of doing almost anything even for HELLO WORLD and I have seen a few :)


    Covid is stealing my sleep and my intelligence

    FRAME.COB copybook's in the source of SOURCE.COB. It's something I saw
    in the FAQ.

    I'm trying to demonstrate to myself how to do user-defined functions.
    - --- FRAME.COB
    IDENTIFICATION DIVISION.
    PROGRAM-ID. frame.
    DATA DIVISION.
    working-storage SECTION.
    01 FOO PIC XXX VALUE "FOO".
    01 OOF PIC XXX.
    PROCEDURE DIVISION.
    CALL "SOURCE" USING FOO returning into oof.
    IF OOF NOT = "OOF"
    DISPLAY "FAIL"
    ELSE
    DISPLAY "PASS"
    END-IF.
    STOP RUN.

    COPY "SOURCE.COB".
    END PROGRAM frame.


    - --- SOURCE.COB
    PROGRAM-ID. SOURCE.
    DATA DIVISION.
    linkage SECTION.
    01 RES PIC XXX.
    01 FOO PIC XXX.
    PROCEDURE DIVISION USING FOO res.
    display foo.
    MOVE FUNCTION REVERSE(FOO) TO RES.
    EXIT PROGRAM.
    END PROGRAM SOURCE.


    Can someone please point out the screamingly obvious?

    The context for this is that there are some things about CobolCheck
    that are really good and some that suck and this is at the end of one rabbithole looking for different ways of testing student code.



    Vincent


    --- Synchronet 3.20a-Linux NewsLink 1.114