Menu

#410 IBM dialect option to allow duplicate data-names (and REDEFINES) in `USING` clause

GC 3.x
accepted
5 - default
2024-06-18
2021-10-27
No

sample code:

 73        LINKAGE SECTION.
...
 91        01  ABCD-IN-KIJNYMD9    PIC 9(08).
 92        01  ABCD-IN-KIJNYMD     REDEFINES ABCD-IN-KIJNYMD9
 93                                    PIC X(08).
 94        01  ABCD-OT-HKSNSYB     PIC X(01).
 95        01  ABCD-OT-HKSNYMD9    PIC 9(08).
 96        01  ABCD-OT-HKSNYMD     REDEFINES ABCD-OT-HKSNYMD9
 97                                    PIC X(08).
 ...
102        PROCEDURE DIVISION USING ABCD-AREA
103                                 ABCD-IN-SYORKBN
104                                 ABCD-IN-KSNKARA
105                                 ABCD-IN-KIJNYMD   *> error, REDEFINES on line 92
106                                 ABCD-OT-HKSNSYB
107                                 ABCD-OT-HKSNYMD   *> error, REDEFINES on line 96

with compilation resulting in:

$ cobc ABCD.cob
105: error: 'ABCD-IN-KIJNYMD' REDEFINES field not allowed here
107: error: 'ABCD-OT-HKSNYMD' REDEFINES field not allowed here

Discussion

  • Arnold Trembley

    Arnold Trembley - 2021-10-27

    Some older IBM COBOL compilers did not allow REDEFINES at the 01 Level, due to IBM's interpretation of the COBOL standard at that time. I know from experience this is true, but I have not been able to find an older manual online to prove it.

    Current IBM COBOL compilers allow REDEFINES at the 01 Level, except for 01 records in the FILE SECTION where all 01 Levels under the same FD have implicit redefinition. I believe the COBOL standard does not allow REDEFINES at the 01 level in the COMMUNICATION SECTION, possibly for the same reason as the FILE SECTION.

    It's possible that GnuCOBOL "strict" syntax configuration settings (i.e. mvs-strict.conf, mf-strict.conf, etc.) may affect this behavior.

    It looks like a bug that could be fixed, if you are migrating from a COBOL compiler that supports redefinition at the 01 Level, and you do not want to make any source code changes.

    If you are learning COBOL, it is trivially easy to modify your source code to enable redefinition at a lower level, or to use group versus elementary definitions to accomplish the same thing.

    For example, the following code accomplishes the same thing as redefinition at the 01 level:

    ==original==
    01 ABCD-IN-KIJNYMD9 PIC 9(08).
    01 ABCD-IN-KIJNYMD REDEFINES ABCD-IN-KIJNYMD9  
            PIC X(08).
    
    ==alternate==
    01 ABCD-IN-KIJNYMD.   *> (group item has implied PIC X) 
             05 ABCD-IN-KIJNYMD9      PIC 9(08). 
    

    Kind regards,

     
    • Vincent (Bryan) Coen

      In GC28-6396-6_IBM_OS_Full_American_National_Standard_COBOL_Apr76.pdf

      REDEFINES Clause
      The REDEFINES clause allows the same computer storage area to contain different data items or provides an alternative grouping or description of the same data. That is, the REDEFINES clause specifies the redefinition of a storage area, not of the data items occupying the area.

      level number data-name-l REDEFINES data-name-2

      The level numbers of data-name-1 and data-name-2 must be identical, but must not be 66 or 88. Data-name-2 is the name associated with the previous data description entry. Data-name-l is an alternate name for the same area. When written, the REDEFINES clause must be the first clause following data-name-l.

      The REDEFINES clause must not be used in level-01 entries in the File Section. Implicit redefinition is provided when more than one level-01 entry follows a file description entry.

      So only excluding 01 in FD and communication section.

      Vince

       

      Last edit: Simon Sobisch 2021-10-28
      • Jonathan Beit-Aharon

        Thank you, Vincent,
        The work-around you offered is exactly what we used... but I should caution you that the MOVE rules for group items are not the same as those for elementary items such as are defined by a PIC X(n) -- see for example a move to an edited string.

        As to the standard reference, is that a reference to a standard published by IBM in April 1976? If so, that is likely to have been the 1974 ANSI standard, or the older 1961 standard. Even if the REDEFINES on level 1 rule was not explicitly relaxed in subsequent standards (1985, 1992 amendment, 2002), it was certainly not enforced by recent IBM mainframe COBOL compilers, which if not a "de facto" standard, are very influential in the market -- it was production code from an IBM mainframe that I was trying to compile using GNU COBOL 3.1.2.

        Again, thank you for the helpful response!
        Jonathan :-)

        --
        "COBOL keeps you young" -- Charles Weigel

         

        Last edit: Simon Sobisch 2021-10-28
        • Vincent (Bryan) Coen

          Text from the manual :

          IBM as Full American National Standard COBOL is designed according to 
          the specifications of the following industry standards:
          
          
          Industry Standards
                IBM OS Full American National standard COBOL is designed according 
          to the specifications of the following industry standards as understood and 
          interpreted by IBM as of April 1976:
          
               * The highest level of American
          
                   National Standard COBOL, X3.23-1968, including all eight 
          modules: Nucleus,
                   Table Handling, Sequential Access, Random Access, Sort, Report 
          Writer,
                   Segmentation, and Library.
          
                *  International Standard ISO/R 1989-1972 Programming Language COBOL
                   which is compatible with, and identical to, American National
                   Standard COBOL, X3.23-1968).
          
                A significant number of IBM extensions are implemented as well.
          

          All of which means swat as it does not relate to modern COBOL compilers such as installed under zOS or for that matter os390.

          The usage of a group item over a elementary numeric item has been used
          for years (ok, say 50) such as :

          01   Fred-x.
                  03 Fred-9     pic 9(6).
          

          The redefinition of a 01 group item in the FD serves no point as all 01 groups below are automatically redefinitions.

          The only issue that might occur depending on age of compiler is that the 01 group level may NOT be allocated if the file is not open.  By memory these compilers are of the age range 1960 - 1970 (or so) so it is wise to treat such as not available until the file is opened and even then to be careful if using variable length data.

          Yes in the past have been bitten from it :(

          I treat GC the same way despite it not being in the same trap = or is it ?

          It is only in resent years that I now accept that COMPUTE is likely bug free :)

          When it first became available it was very flaky - after IBM 1401 but during ICT 1900's.

          Sorry could not be bothered to look up a 1401 Cobol manual (all 50 odd pages of it - My "The" Cobol learning tool around 1961-3).

          Going back to your 01 redefines other than FD areas I can't say I have noticed any error being reported but there again I might not use the method as against using :

          01  Alpha.
                 03  Alpha-one.
          
                 ... what every ...
          
                 03  Beta-one   redefines Alpha-one.
          
                  ... what ever ....
          

          I don't ant to spend the time to look at 1,000 of Cobol programs to see if I have used the 01 level as at my age I have better things to do.  
          -   Hmm, there again a bit of Rexx code might do it for me - have to consider it when bored.

          Shalom,

          Vince

           

          Last edit: Simon Sobisch 2022-09-28
    • Jonathan Beit-Aharon

      Thank you, Arnold!
      I made the needed source modifications and continued.
      Thought I'd let the GNU COBOL community know about this bug, since it has a low priority for me.
      If that priority should rise for me, I'll happily fix the bug and share my changes.
      All the best,
      Jonathan

       

      Last edit: Simon Sobisch 2021-10-28
  • Simon Sobisch

    Simon Sobisch - 2021-10-28
    • Description has changed:

    Diff:

    --- old
    +++ new
    @@ -1,3 +1,5 @@
    +sample code:
    +```cobol
      73        LINKAGE SECTION.
     ...
      91        01  ABCD-IN-KIJNYMD9    PIC 9(08).
    @@ -8,13 +10,16 @@
      96        01  ABCD-OT-HKSNYMD     REDEFINES ABCD-OT-HKSNYMD9
      97                                    PIC X(08).
      ...
    - 102        PROCEDURE DIVISION USING ABCD-AREA
    +102        PROCEDURE DIVISION USING ABCD-AREA
     103                                 ABCD-IN-SYORKBN
     104                                 ABCD-IN-KSNKARA
    -105                                 ABCD-IN-KIJNYMD   <<< error, REDEFINES on line 92
    +105                                 ABCD-IN-KIJNYMD   *> error, REDEFINES on line 92
     106                                 ABCD-OT-HKSNSYB
    -107                                 ABCD-OT-HKSNYMD   <<< error, REDEFINES on line 96
    -
    +107                                 ABCD-OT-HKSNYMD   *> error, REDEFINES on line 96
    +```
    +with compilation resulting in:
    +```
     $ cobc ABCD.cob
     105: error: 'ABCD-IN-KIJNYMD' REDEFINES field not allowed here
     107: error: 'ABCD-OT-HKSNYMD' REDEFINES field not allowed here
    +```
    
     
  • Simon Sobisch

    Simon Sobisch - 2021-10-28
    • labels: --> ibm, cobc
    • summary: Erroneous "error: ... REDEFINES field not allowed here" --> IBM dialect option to allow duplicate data-names (and REDEFINES) in USING clause
    • status: open --> accepted
    • assigned_to: Simon Sobisch
    • Group: unclassified --> GC 3.x
     
  • Simon Sobisch

    Simon Sobisch - 2021-10-28

    All those rules are only for the REDEFINES clause and for data items in general.

    The COBOL standard has, since years a rule for LINKAGE:

    Data-name-1 shall be defined as a level 01 entry or a level 77 entry in the linkage section. A particular user-defined word shall not appear more than once as data-name-1. The data description entry for data-name-1 shall not contain a BASED clause or a REDEFINES clause.
    NOTE 1 This restriction for based items does not prohibit passing based items as arguments.
    NOTE 2 A data item defined subsequently in the linkage section may specify REDEFINES data-name-1.

    So the following is fine:

    102        PROCEDURE DIVISION USING ABCD-AREA
    103                                 ABCD-IN-SYORKBN
    104                                 ABCD-IN-KSNKARA
    105                                 ABCD-IN-KIJNYMD9  *> original item
    106                                 ABCD-OT-HKSNSYB
    107                                 ABCD-OT-HKSNYMD9  *> original item
    

    Same for MF:

    Data-name-3 must be defined as a level 01 or level 77 entry in the Linkage Section. The data description entry for data-name-3 must not contain a REDEFINES clause. A data item elsewhere in the Linkage Section may specify REDEFINES data-name-3.

    I'm quite sure that this is to cater for the general rule that no two items in USING should use the same data-name.

    Note: at least the VAX COBOL74 manual doesn't explicit specify the rule above.

    But IBM is explicit against this, the only thing Enterprise COBOL (4.2, procedure division header, USINGclause) says to this is:

    A data item in the USING phrase of the procedure division header can have a REDEFINES clause in its data description entry.

    and also do not follow the rule that it can be only used once:

    A given identifier can appear more than once in a procedure division USING phrase. The last value passed to it by a CALL or INVOKE statement is used.

    So "yay" a new dialect option - I'm moving this to a FR now.

    The change itself is easy (it would be necessary to do additional tests at runtime, of course). To let the compile pass just adjust cobc/typeck.c, commenting the following lines (which will implicit disable the check for duplicate items, too):

                    if (f->redefines) {
                        cb_error_x (x, _("'%s' REDEFINES field not allowed here"), f->name);
                    }
                    if (CB_PURPOSE_INT (l) == CB_CALL_BY_REFERENCE) {
                        check_list = cb_list_add (check_list, x);
                    }
    
     

    Last edit: Simon Sobisch 2022-03-31
  • Simon Sobisch

    Simon Sobisch - 2021-10-28

    Ticket moved from /p/gnucobol/bugs/782/

     
  • Simon Sobisch

    Simon Sobisch - 2021-10-28
    • labels: ibm, cobc --> ibm, cobc, dialect
     
  • Simon Sobisch

    Simon Sobisch - 2024-06-18
    • labels: ibm, cobc, dialect --> ibm, cobc, dialect, mf
     

Log in to post a comment.