Menu

#260 allow a user-defined word to be both used as variable and as section/paragraph/entry/program-id name

GC 3.x
accepted
6
2023-09-08
2017-11-16
No

I'm not sure if this is a "defect" in GnuCOBOL or an "extension" in other compilers (for example ACUCOBOL) but for making migrations easier it should be possible to do this (maybe with a compiler configuration option).

       identification division.
       program-id. WORD.
       data division.
       working-storage section.
      *-----------------------------------------------------------------
       77 word pic 9.
      *-----------------------------------------------------------------
       PROCEDURE DIVISION.
       main section.
      *
           move 0 to word
           perform word
      *
           exit program returning word.
      *-----------------------------------------------------------------
       word section.
      *
           add 1 to word
      *
           continue.
      *-----------------------------------------------------------------

leads to

WORD.cbl: in section 'main':
WORD.cbl:16: error: redefinition of 'word'
WORD.cbl:6: error: 'word' previously defined here

Test added as expected failure with [r2272] (which may be wrong if the test should fail the error should be changed to be expected (with -std=cobol2014).

1 Attachments

Related

Bugs: #735
Discussion: redefinition error
Discussion: Question about field and code naming
Discussion: tandy rmcobol
Discussion: tandy rmcobol
Discussion: ACUCOBOL support and compiler warnings/errors (was: GRAPHICAL WINDOW is not implemented)
Discussion: I need displaying Arabic in gnucobol
Discussion: SCREEN SECTION
Wish List: #223

Discussion

  • Simon Sobisch

    Simon Sobisch - 2018-03-14

    Just for reference: ISO/IEC 1989:2002 and newer list under "User-defined words" the types of user-defined words (including level-numbers) and say:

    Within a source element, a given user-defined word may be used as only one type of user-defined word with the following exceptions:

    1. a compilation-variable-name may be the same as any other type of user-defined word
    2. a level-number may be the same as a paragraph-name or a section-name
    3. the same name may be used as any of the following types of user-defined words:
      • constant-name
      • data-name
      • property-name
      • record-key-name
      • record-name

    I don't think we support the same word for "data-name", "record-key-name" and "record-name" (a test would be nice), but it definitely does not allow "program-name", "section-name"/"paragraph-name" and "data-name" to be the same.
    We should gather information which other compilers have the same extension as ACUCOBOL (if any) next....

     

    Last edit: Simon Sobisch 2018-03-14
  • Simon Sobisch

    Simon Sobisch - 2018-05-14

    Duplicate of [feature-requests:#223] which I close in favor of this one.

    Note: Edward said there

    You might want to examine [r1047] and [bugs:#268], which involved the similar problem of allowing redefinition of program-names. However, this problem was mixed up with basic program prototype support, so the [r1047] diff is quite hard to read.

     

    Related

    Bugs: #268
    Wish List: #223

  • David Declerck

    David Declerck - 2022-03-28

    Our customer uses GCOS Cobol, and he does have programs where some paragraphs have the same name as fields or sections, although neigher the Cobol 85 standard nor the GCOS documentation seem to allow it.

    For reference, both the Cobol 85 standard and the GCOS documentation state:

    Within a given source program, but excluding any contained program, the user-defined words are grouped into the following disjoint sets:
    { ..., data-names, ..., paragraph-names, ..., section-names, ... }
    All user-defined words, except segment-numbers and level-numbers, can belong to one and only one of these disjoint sets. Further, all user-defined words within a given disjoint set must be unique, except as specified in the rules for uniqueness of reference.

    The Cobol 2002 and 2014 standards seem to relax this "uniqueness restriction" a bit, as indicated by the excerpt you quote, though the wording is quite ambiguous IMO, leaving us confused about what is actually allowed or not.

     
  • Simon Sobisch

    Simon Sobisch - 2022-03-28

    The MF docs also specify that paragraph-names, sections-names, data-names and other types of user-defined names are grouped into "disjoined sets" by its type and "can belong to one and only one of these disjoint sets".
    If I remember correctly they also support names in more than one group and do handle this the way an overlap of user-defined names with intrinsic function names is supported: "the classification of a specific occurrence of such COBOL words is determined by the context of the clause or phrase in which it occurs. "

    @ddeclerck: Did you investigate the way @edward-h implemented it for program-names referenced above? This is likely "the way to go" to implement it nicely.

     
  • David Declerck

    David Declerck - 2022-03-29

    Actually, I did not have to go that far. In all of our customer's programs (hundreds of files), when a paragraph has the same name as a field, this paragraph is always after the last reference to the field with the same name, so it "just works" (with a small patch to actually allow creating a paragraph with the same name as a field).

    Nevertheless, we'll check with our customer if referencing a field after a paragraph with the same name is accepted by their GCOS compiler (in which case we'll indeed have to use the context to resolve ambiguities).

     
    • Simon Sobisch

      Simon Sobisch - 2022-03-29

      we'll check with our customer if referencing a field after a paragraph with the same name is accepted by their GCOS compiler

      I'm quite sure it will be, but a check never harms.

       
  • David Declerck

    David Declerck - 2022-04-15

    So, we were able to check using the "officiel" Cobol compiler for GCOS, and the results are interesting. It is in fact much simpler than we thought. Basically, paragraphs, sections and fields may have the same name, and the compiler won't complain.

    To resolve ambiguities, the compiler does not seem to be performing any kind of semantic reasoning. Instead, it first looks in the current section (if any), and if the requested identifier is present exactly once, it will use it (no matter if the identifier is also present in other sections or in the data division). If the identifier is present more than once in the current section, it will just fail. Finally, if the identifier is not present in the current section (or if the program does not use sections), then it will simply look for it in the remainder of the program, and fail if present more than once.

     
  • Simon Sobisch

    Simon Sobisch - 2022-05-25
    • labels: --> cobc, acucobol, rm-cobol, gcos
    • assigned_to: David Declerck
    • Group: unclassified --> GC 3.x
    • Priority: 5 - default --> 6
     
  • Bill Fahle

    Bill Fahle - 2023-09-08

    FYI the current IBM COBOL 6.3 zOS compiler does not accept variables named the same as sections. However it does accept two sections with the same name, as long as it's not ambiguous. In other words you can have SECTION A. SECTION B. SECTION A. as long as you don't have a GO TO A. Version 3.1.2 of GNU COBOL does not support repeated section names, and maybe that can be fixed at the same time as this. Likewise, IBM allows the same paragraph name to be reused, even in the same section or without sections, as long as it's not ambiguous. Obviously section names disambiguate paragraph names, but if your paragraph name is unique throughout the program, you don't have to qualify it to go to it from any section. In other words you can have SECTION A. PARA1. PARA2. SECTION B. PARA1. GO TO PARA2. without having to specify GO TO PARA2 IN A.
    Should I write up a separate bug for the section name not being repeatable?

     
    • Simon Sobisch

      Simon Sobisch - 2023-09-08

      FYI the current IBM COBOL 6.3 zOS compiler does not accept variables named the same as sections.

      Thanks for the information - a reason more to have this as a dialect option.
      Can you quote the documentation for that or is this only "seen by testing"?

      For paragraph there is a clear definition - the next paragraph with the same name in the current section (or globally if you don't use sections) is used - those can even be ambiguous (but qualifying them helps).
      This is also supported in GnuCOBOL, at least I think that was the case here.

      You can GO TOsection-names, too, but that's bad style (and by default warned in GC 3.2).

      So you say "sections can also have the same names, as long as they are never referenced" (by PERFORM or GO TO)?
      You'd consider those as "unused" sections, no?

      Note: they should still be executed if the program just falls through...

       
      • Bill Fahle

        Bill Fahle - 2023-09-08

        I don't see documentation on most of this; I found I had to discover it through extensive testing. For ambiguous paragraph names, the IBM compiler issues a severe error (highest besides terminating) but nonetheless finishes the compile and runs the program. It actually discards the offending PERFORM or GO TO line. But I think being more permissive is ok (maybe in the IBM dialect disallow so people don't write programs that won't work on ibm).
        Your final questions are correct, if you don't reference the SECTION directly (with a GO TO or PERFORM) you can reuse the names without a warning. Likewise with paragraphs, if you don't reference the paragraph with a GO TO or PERFORM you can reuse paragraph names all day and they fall through. You can reference reused section names with GO TO PARA1 IN SECTION1 even if there is more than one SECTION1, as long as PARA1 is only in one SECTION1. So they are not entirely unused necessarily. They should definitely be executed if the program falls through. None of this results in so much as a warning in IBM.

        The following program results in an output of

        X + Y = 35
        X 19
        
               IDENTIFICATION DIVISION.
               PROGRAM-ID. SECTST.
               DATA DIVISION.
               WORKING-STORAGE SECTION.
                  77 X PIC 99.
                  77 Y PIC 99.
                  77 Z PIC 99.
               PROCEDURE DIVISION.
               FIRSTY SECTION.
                   MOVE 10 TO  X.
               PARA1.
                   MOVE 25 TO Y.
               SECOND SECTION.
               PARA2.
                   ADD X Y GIVING Z.
               FIRSTY SECTION.
               PARA2.
                   COMPUTE X = X + 4.
               PARA3.
                   DISPLAY "X + Y = " Z.
                   IF X IS EQUAL TO 14
                      COMPUTE X = X + 1
                      PERFORM PARA2 IN FIRSTY.
                   DISPLAY "X " X.
                   STOP RUN.
        
         

        Last edit: Simon Sobisch 2024-09-03

Log in to post a comment.