• Order of CONSTANT definition/use in the 2002 standard???

    From Thomas David Rivers@21:1/5 to All on Mon Jul 18 01:41:01 2022
    The COBOL 2002 standard adds constant-entry to the various
    storage sections for defining compile-time constants.

    However, I doesn't (at least in my scouring of the document) define
    *when* these are extent and when they can be used.

    For instance, this seems like a reasonable use:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 B CONSTANT 6.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    PROCEDURE DIVISION.


    Where the constant CON is used for the picture-string in the definition
    of MYDATA.

    But - I can't find where this would be an invalid COBOL program according
    to the 2002 standard:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    01 B CONSTANT 6.
    PROCEDURE DIVISION.

    In this second example, the constant 'B' is used before it is defined.
    But - the 2002 standard doesn't seem to make that illegal.

    Is this a valid COBOL 2002 program? If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?

    - Thanks! -
    - Dave Rivers -


    --
    rivers@dignus.com Work: (919) 676-0847
    Get your mainframe programming tools at http://www.dignus.com

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Bill Gunshannon@21:1/5 to Thomas David Rivers on Mon Jul 18 18:19:53 2022
    On 7/18/22 01:41, Thomas David Rivers wrote:
    The COBOL 2002 standard adds constant-entry to the various
    storage sections for defining compile-time constants.

    However, I doesn't (at least in my scouring of the document) define
    *when* these are extent and when they can be used.

    For instance, this seems like a reasonable use:

          IDENTIFICATION DIVISION.
           PROGRAM-ID. ALPHEDIT.
          ENVIRONMENT DIVISION.
          DATA DIVISION.
           WORKING-STORAGE SECTION.
          01  A CONSTANT 5.
          01  B CONSTANT 6.
          01  CON CONSTANT A + B.
          01  MYDATA PIC 9(CON).
          PROCEDURE DIVISION.


    Where the constant CON is used for the picture-string in the definition
    of MYDATA.

    But - I can't find where this would be an invalid COBOL program according
    to the 2002 standard:

    What makes you think it should be? Compiles just fine with GnuCOBOL.


          IDENTIFICATION DIVISION.
           PROGRAM-ID. ALPHEDIT.
          ENVIRONMENT DIVISION.
          DATA DIVISION.
           WORKING-STORAGE SECTION.
          01  A CONSTANT 5.
          01  CON CONSTANT A + B.
          01  MYDATA PIC 9(CON).
          01  B CONSTANT 6.
          PROCEDURE DIVISION.

    In this second example, the constant 'B' is used before it is defined.
    But - the 2002 standard doesn't seem to make that illegal.

    Using any data item before it is defined is an error and GnuCOBOL flags
    it (in the obscure way it flags most undefined item errors. :-)


    Is this a valid COBOL 2002 program?  If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?


    Not having a copy of the 2002 standard I can't help with that
    but then I wonder why it matters as long as the compilers are
    getting it right. Do you have a compiler that doesn't?

    bill

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Thomas David Rivers@21:1/5 to Bill Gunshannon on Mon Jul 18 03:42:44 2022
    Bill Gunshannon wrote:



    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    01 B CONSTANT 6.
    PROCEDURE DIVISION.

    In this second example, the constant 'B' is used before it is defined.
    But - the 2002 standard doesn't seem to make that illegal.


    Using any data item before it is defined is an error and GnuCOBOL flags
    it (in the obscure way it flags most undefined item errors. :-)


    Is this a valid COBOL 2002 program? If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?


    Not having a copy of the 2002 standard I can't help with that
    but then I wonder why it matters as long as the compilers are
    getting it right. Do you have a compiler that doesn't?

    bill


    Hi Bill!

    *Many* thanks for taking a moment to reply.

    You've hit on the crux of my question - it may intuitively be the rule that
    you can't use a data-definition before it's defined; but that may be an artifact
    of how data-definitions appear before the PROCEDURE division and not
    explicitly stated as such in the standard.

    The absence of an explicit statement about definition-before-use (I've
    perused
    the IBM and Microfocus documentation on this, as well as the 2002 standard)
    seems to be the problem here.

    And - without such a prohibition, the second program (above) would be
    valid,
    and GnuCOBOL would be in error.

    That's really what I'm asking...

    Just what is the fundamental language requirement here - and where is that
    articulated/documented.

    If there is no mention of such a restriction, then the program should compile...

    And - I can think of more convoluted examples that would difficult for
    a compiler
    to untangle without that prohibition, so I'm hoping it exists
    somewhere. The 2002
    standard does restrict the values of the arithmetic-expression-1 to not contain
    a reference to the constant being defined, but the wording of that
    would seem
    to only be a direct reference - where, if we allowed forward references
    to constants -
    one could easily produce a recursive definition, e.g.

    01 A CONSTANT B + C. --- doesn't seem to violate the
    2002 standard restriction
    01 B CONSTANT 5.
    01 C CONSTANT A + 1. --- again, doesn't seem to violate
    the 2002 standard restriction

    An explicit statement regarding definition-before-use would clear this up.

    So - it seems like that portion of the standard (and any other
    documentation)
    could use some clarification?

    I can't think of a similar situation where a data-definition could be
    defined
    to use an identifier that wasn't already defined... so - perhaps this question
    has never been posed for clarification?

    Or - much more likely - I'm missing something somewhere...

    - Dave Rivers -


    --
    rivers@dignus.com Work: (919) 676-0847
    Get your mainframe programming tools at http://www.dignus.com

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From docdwarf@panix.com@21:1/5 to rivers@dignus.com on Tue Jul 19 01:52:44 2022
    In article <62D50EF4.7060309@dignus.com>,
    Thomas David Rivers <rivers@dignus.com> wrote:

    [snip]

    The absence of an explicit statement about definition-before-use (I've
    perused
    the IBM and Microfocus documentation on this, as well as the 2002 standard) seems to be the problem here.

    And - without such a prohibition, the second program (above) would be
    valid,
    and GnuCOBOL would be in error.

    That's really what I'm asking...

    Just what is the fundamental language requirement here - and where is that articulated/documented.

    [snip]

    Or - much more likely - I'm missing something somewhere...

    It used to be coded:

    IF PROGRAM-RUNS
    NEXT SENTENCE
    ELSE
    PERFORM CODE-LIKE-THE-BLAZES
    UNTIL FOOL-THING-WORKS.

    This got upgraded to:

    IF program-runs
    CONTINUE
    ELSE
    PERFORM code-like-the-blazes
    UNTIL fool-thing-works
    END-IF

    What you can think up is more an indication of what you can think up than
    how either the Standard is written or any compiler implements the
    standard.

    (back in The Oldene Dayse I had a strip of greenbar with an error for a
    SEARCH ALL reading EXPECTING WHEN - FOUND WHEN)

    DD

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Rick Smith@21:1/5 to Thomas David Rivers on Tue Jul 19 08:52:31 2022
    On Monday, July 18, 2022 at 5:24:00 PM UTC-4, Thomas David Rivers wrote:
    The COBOL 2002 standard adds constant-entry to the various
    storage sections for defining compile-time constants.

    However, I doesn't (at least in my scouring of the document) define
    *when* these are extent and when they can be used.

    For instance, this seems like a reasonable use:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 B CONSTANT 6.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    PROCEDURE DIVISION.


    Where the constant CON is used for the picture-string in the definition
    of MYDATA.

    But - I can't find where this would be an invalid COBOL program according
    to the 2002 standard:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    01 B CONSTANT 6.
    PROCEDURE DIVISION.

    In this second example, the constant 'B' is used before it is defined.
    But - the 2002 standard doesn't seem to make that illegal.

    Is this a valid COBOL 2002 program? If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?

    The standard says what MUST be done. It does not say HOW to do it.

    During the compilation phase, the compiler may need to make multiple
    passes to resolve incomplete references. These may occur with CONSTANT, TYPEDEF, and SAME AS.

    In particular, if the value of a CONSTANT or length of a TYPEDEF changes
    during those multiple passes, the implementor is free to (and probably
    should) give an error message.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Bill Gunshannon@21:1/5 to Thomas David Rivers on Tue Jul 19 13:22:03 2022
    On 7/18/22 01:41, Thomas David Rivers wrote:
    The COBOL 2002 standard adds constant-entry to the various
    storage sections for defining compile-time constants.

    However, I doesn't (at least in my scouring of the document) define
    *when* these are extent and when they can be used.

    For instance, this seems like a reasonable use:

          IDENTIFICATION DIVISION.
           PROGRAM-ID. ALPHEDIT.
          ENVIRONMENT DIVISION.
          DATA DIVISION.
           WORKING-STORAGE SECTION.
          01  A CONSTANT 5.
          01  B CONSTANT 6.
          01  CON CONSTANT A + B.
          01  MYDATA PIC 9(CON).
          PROCEDURE DIVISION.


    Where the constant CON is used for the picture-string in the definition
    of MYDATA.

    But - I can't find where this would be an invalid COBOL program according
    to the 2002 standard:

          IDENTIFICATION DIVISION.
           PROGRAM-ID. ALPHEDIT.
          ENVIRONMENT DIVISION.
          DATA DIVISION.
           WORKING-STORAGE SECTION.
          01  A CONSTANT 5.
          01  CON CONSTANT A + B.
          01  MYDATA PIC 9(CON).
          01  B CONSTANT 6.
          PROCEDURE DIVISION.

    In this second example, the constant 'B' is used before it is defined.
    But - the 2002 standard doesn't seem to make that illegal.

    Is this a valid COBOL 2002 program?  If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?

    I am sure I could find where this is addressed given a chance to
    read the actual standard. But I am certainly not going to pay
    ISO more than $100 for the opportunity. I expect there is a place
    where the standard addresses undefined data items. But it is
    probably not where you are looking for it.

    bill

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Thomas David Rivers@21:1/5 to Bill Gunshannon on Mon Jul 18 23:43:52 2022
    Bill Gunshannon wrote:


    Is this a valid COBOL 2002 program? If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?


    I am sure I could find where this is addressed given a chance to
    read the actual standard. But I am certainly not going to pay
    ISO more than $100 for the opportunity. I expect there is a place
    where the standard addresses undefined data items. But it is
    probably not where you are looking for it.

    bill


    Hi Bill!

    Your idea about "undefined" was a terrific one - I did look through
    the standard some more. There is even a section B.2 that explicitly
    lists all the undefined behavior.

    Unfortunately - there is no prohibition against a forward reference
    to a constant. There doesn't seem to be a prohibition at all about a
    forward
    reference (although I'm hard-pressed to consider where that might happen?
    Perhaps in a VALUE clause for a pointer data-definition?)

    As far as I can tell, the standard allows forward references to
    as-yet undefined
    constants. So, a compiler would be required (as Rick mentioned) to make
    multiple passes for resolving forward constant references.

    I'm not sure what that would mean for constants that appear in different
    sections? Can a constant in a WORKING STORAGE section reference a
    constant in a LINKAGE section? What does that mean? What does it mean
    if the constant is declared in the LINKAGE section of a sub-program with
    the GLOBAL clause? Can it be referenced in the enclosing program? Can it
    be referenced at a point in the enclosing program when the values of data
    in the LINKAGE section of a sub-program are explicitly undefined? When
    does
    a compile-time constant become "undefined"?

    The 2002 standard only seems to say:

    5) Neither the value of literal-1 nor the value of any of the
    literals in
    arithmetic-expression-1 shall be dependent, directly or
    indirectly,
    upon the value of constant-name-1.

    (constant-name-1 is the name being defined as a constant, with arithmetic-expression-1
    being the value.) And - since they mention "indirectly" - that would
    seem to
    imply the possibility of a forward reference to an as-yet-to-be-defined constant (as I think
    that would be about the only way to "indirectly" reference the constant
    being defined...
    wouldn't it?)

    So - it would seem to explicitly disallow a recursive constant definition
    (so the program snippet I posted is invalid) but - it appears to have
    nothing to say
    about the use of a constant before it's defined... and thus would allow it.

    If that understanding is correct, the GnuCOBOL compiler needs to make an
    adjustment for that. Microfocus implements level-78 "constants", I'm
    not sure
    what they do with any forward reference (if someone happens to have
    that available
    it might be nice to check what they do.)

    But - I think some clarifications of what a "constant" is, and just
    when it is
    defined and available might be useful.

    - Many thanks! -
    - Dave Rivers -


    --
    rivers@dignus.com Work: (919) 676-0847
    Get your mainframe programming tools at http://www.dignus.com

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Bill Gunshannon@21:1/5 to Thomas David Rivers on Tue Jul 19 17:13:19 2022
    On 7/18/22 23:43, Thomas David Rivers wrote:
    Bill Gunshannon wrote:


    Is this a valid COBOL 2002 program?  If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?


    I am sure I could find where this is addressed given a chance to
    read the actual standard.  But I am certainly not going to pay
    ISO more than $100 for the opportunity.  I expect there is a place
    where the standard addresses undefined data items.  But it is
    probably not where you are looking for it.

    bill


    Hi Bill!

     Your idea about "undefined" was a terrific one - I did look through
    the standard some more.  There is even a section B.2 that explicitly
    lists all the undefined behavior.

    "Undefined behavior" is something totally different. You want to
    look for "Undefined Data Item" or something similar.


      Unfortunately - there is no prohibition against a forward reference
    to a constant.

    Now you are calling it something else. If yo keep that up you'll
    never find it. :-) What you are saying would make sense if, like
    Pascal, COBOL had a FORWARD verb. :-) (No, FORWARD can not be used
    for data items, even in Pascal.)

    There doesn't seem to be a prohibition at all about a
    forward
    reference (although I'm hard-pressed to consider where that might happen? Perhaps in a VALUE clause for a pointer data-definition?)

    If use of an undefined data item is covered somewhere in the standard
    then there would be no reason to address a forward reference as at the
    time the reference is made it is an undefined data item. Unless there
    was a FORWARD verb. :-)


      As far as I can tell, the standard allows forward references to
    as-yet undefined
    constants.
    Where does the standard allow that? Where does the standard even
    mention forward references? My guess is it does not and you are
    merely assuming if it doesn't explicitly prohibit it then it allows
    it. Bad assumption. I am pretty sure that the standard does not
    prohibit inline assembler, but I doubt that means it would be allowed.


    So, a compiler would be required (as Rick mentioned) to make multiple passes for resolving forward constant references.

    No, the compiler is only required to do the things explicitly covered
    in the standard. And, as I said, I would be willing to bet that there
    is a specific reference somewhere in the standard to "undefined data
    items".


      I'm not sure what that would mean for constants that appear in different sections?   Can a constant in a WORKING STORAGE section reference a constant in a LINKAGE section?    What does that mean?   What does it mean
    if the constant is declared in the LINKAGE section of a sub-program with
    the GLOBAL clause?  Can it be referenced in the enclosing program?  Can it be referenced at a point in the enclosing program when the values of data
    in the LINKAGE section of a sub-program are explicitly undefined?  When
    does
    a compile-time constant become "undefined"?

     The 2002 standard only seems to say:

         5) Neither the value of literal-1 nor the value of any of the literals in
             arithmetic-expression-1 shall be dependent, directly or indirectly,
             upon the value of constant-name-1.

    (constant-name-1 is the name being defined as a constant, with arithmetic-expression-1
    being the value.)   And - since they mention "indirectly" - that would
    seem to
    imply the possibility of a forward reference to an as-yet-to-be-defined constant (as I think
    that would be about the only way to "indirectly" reference the constant
    being defined...
    wouldn't it?)

     So - it would seem to explicitly disallow a recursive constant definition (so the program snippet I posted is invalid) but - it appears to have
    nothing to say
    about the use of a constant before it's defined... and thus would allow it.

     If that understanding is correct, the GnuCOBOL compiler needs to make an adjustment for that.   Microfocus implements level-78 "constants", I'm
    not sure
    what they do with any forward reference (if someone happens to have that available
    it might be nice to check what they do.)
     But - I think some clarifications of what a "constant" is, and just
    when it is
    defined and available might be useful.


    I still think you are making a mountain out of a molehill. I do not
    think that forward references are allowed. I have never seen any
    mention of them in previous COBOL language references and I am unaware
    of any mention of them in the 2002 standard. You are dealing with an
    undefined data item at the time of its use and the result of that is
    handled by the compiler as it always has been. Being a CONSTANT doesn't
    impart any magical powers. It is still just a data item.

    bill

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Thomas David Rivers@21:1/5 to Bill Gunshannon on Tue Jul 19 01:20:11 2022
    Bill Gunshannon wrote:

    On 7/18/22 23:43, Thomas David Rivers wrote:

    Bill Gunshannon wrote:


    Is this a valid COBOL 2002 program? If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?



    I am sure I could find where this is addressed given a chance to
    read the actual standard. But I am certainly not going to pay
    ISO more than $100 for the opportunity. I expect there is a place
    where the standard addresses undefined data items. But it is
    probably not where you are looking for it.

    bill


    Hi Bill!

    Your idea about "undefined" was a terrific one - I did look through
    the standard some more. There is even a section B.2 that explicitly
    lists all the undefined behavior.


    "Undefined behavior" is something totally different. You want to
    look for "Undefined Data Item" or something similar.


    Hi Bill!!

    I spent some time and looked at every occurence of "undefined" in the standard,
    there didn't seem (to me) to be any kind of statement like that.



    Unfortunately - there is no prohibition against a forward reference
    to a constant.


    Now you are calling it something else. If yo keep that up you'll
    never find it. :-) What you are saying would make sense if, like
    Pascal, COBOL had a FORWARD verb. :-) (No, FORWARD can not be used
    for data items, even in Pascal.)


    Yes - you are right - I did call it something else. It is really
    important to
    have precise terms.

    Let's define a "forward reference" as a reference to a data definition that
    is not yet defined at its use, but is subsequently defined (to distinguish
    it from a name that is never defined.)

    Going back to my very first post on this, this example contains a "forward
    reference" to the constant-name 'B':

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    01 B CONSTANT 6.
    PROCEDURE DIVISION.

    I can't find any reason in the standard why that shouldn't compile. I
    also can't
    find a statement about when the value of a constant is 'defined'.

    The standard, under the "General Rules" for a CONSTANT (section 13.9.3)
    says:

    1) If literal-1 or compilation-variable-name-1 is specified, the
    effect of specifying
    constant-name-1 in other than this entry is as if literal-1 or
    the text represented by
    compilation-variable-name-1 were written where constant- name-1
    is written.

    ...

    3) If arithmetic-expression-1, data-name-1, or data-name-2 is
    specified, the effect of
    writing constant-name-1 in other than this entry is as if an
    integer literal were
    written where constant-name-1 is written. This integer literal
    has the value specified in
    these general rules.

    It doesn't require that the definition be encountered before its use.

    I _think_ this is the about the only situation where "something" can be
    used
    before it's defined. That is, the WORKING STORAGE section appears before
    the PROCEDURE DIVISION, so any undefined (or unqualifiable) name is simply
    undefined when encountered in the PROCEDURE DIVISION.

    So, the reason I'm concerned about this, is I _think_ this is the first
    time such
    a situation could arise in COBOL? (I'd like to be found wrong on that
    idea, if
    someone cares to provide an example... )




    There doesn't seem to be a prohibition at all about a
    forward
    reference (although I'm hard-pressed to consider where that might
    happen?
    Perhaps in a VALUE clause for a pointer data-definition?)


    If use of an undefined data item is covered somewhere in the standard
    then there would be no reason to address a forward reference as at the
    time the reference is made it is an undefined data item. Unless there
    was a FORWARD verb. :-)


    Yes - that is a good point, I can't find anything in the standard that
    talks about that in terms of the point-of-reference. The standard seems
    to talk about compilation-data-name as being defined or not, but
    nothing else.

    I'm with you on the intuition that there must be something in the
    standard
    that speaks to this - but I can't find it.



    As far as I can tell, the standard allows forward references to
    as-yet undefined
    constants.

    Where does the standard allow that? Where does the standard even
    mention forward references? My guess is it does not and you are
    merely assuming if it doesn't explicitly prohibit it then it allows
    it. Bad assumption. I am pretty sure that the standard does not
    prohibit inline assembler, but I doubt that means it would be allowed.


    So, a compiler would be required (as Rick mentioned) to make
    multiple passes for resolving forward constant references.


    No, the compiler is only required to do the things explicitly covered
    in the standard. And, as I said, I would be willing to bet that there
    is a specific reference somewhere in the standard to "undefined data
    items".



    I'm not sure what that would mean for constants that appear in
    different
    sections? Can a constant in a WORKING STORAGE section reference a
    constant in a LINKAGE section? What does that mean? What does it
    mean
    if the constant is declared in the LINKAGE section of a sub-program with
    the GLOBAL clause? Can it be referenced in the enclosing program?
    Can it
    be referenced at a point in the enclosing program when the values of
    data
    in the LINKAGE section of a sub-program are explicitly undefined?
    When does
    a compile-time constant become "undefined"?

    The 2002 standard only seems to say:

    5) Neither the value of literal-1 nor the value of any of the
    literals in
    arithmetic-expression-1 shall be dependent, directly or
    indirectly,
    upon the value of constant-name-1.

    (constant-name-1 is the name being defined as a constant, with
    arithmetic-expression-1
    being the value.) And - since they mention "indirectly" - that
    would seem to
    imply the possibility of a forward reference to an
    as-yet-to-be-defined constant (as I think
    that would be about the only way to "indirectly" reference the
    constant being defined...
    wouldn't it?)

    So - it would seem to explicitly disallow a recursive constant
    definition
    (so the program snippet I posted is invalid) but - it appears to have
    nothing to say
    about the use of a constant before it's defined... and thus would
    allow it.

    If that understanding is correct, the GnuCOBOL compiler needs to
    make an
    adjustment for that. Microfocus implements level-78 "constants",
    I'm not sure
    what they do with any forward reference (if someone happens to have
    that available
    it might be nice to check what they do.)
    But - I think some clarifications of what a "constant" is, and just
    when it is
    defined and available might be useful.


    I still think you are making a mountain out of a molehill. I do not
    think that forward references are allowed. I have never seen any
    mention of them in previous COBOL language references and I am unaware
    of any mention of them in the 2002 standard. You are dealing with an undefined data item at the time of its use and the result of that is
    handled by the compiler as it always has been. Being a CONSTANT doesn't impart any magical powers. It is still just a data item.

    bill

    Yeah - maybe I am... but with the strange phrase in the standard about
    directly or indirectly referencing the name being defined, it seems to me
    that the authors were actually _intending_ to allow a forward-reference
    (as that would be the only way to arrive at an indirect reference - I
    think.)
    So, if the intent is to allow a forward reference, and there isn't anything
    in the standard that disallows it, would it then be safe to say it's
    allowed?

    Also - there are some questions I still have about constants defined in
    a sub-program's WORKING STORAGE or LINKAGE sections with the GLOBAL
    clause attached. Are such constants visible in the containing program?
    The standard is clared that such data is "undefined" when the sub-program
    is not active (which makes absolute sense) but does not prohibit the
    reference
    to them. Only that if you do, you are entering the "realm of undefined" if
    the sub-program is not active (also, this begs a question about _which_ one
    you are referencing if the sub-program is at all RECURSIVE - but that's a
    different question.) So - what does this mean about CONSTANTs defined
    in such sections? Are they globally visible at compile-time - or only intended
    to be visible when the sub-program is active? I can't imagine that's
    the intent,
    but that seems to be what one can consider from the verbiage in the
    standard.

    If the standard is really just a "set of guidelines" - then, I guess
    I'll just have
    to be disappointed.

    I was hoping someone from the committee might be lurking here with
    some rationale, or perhaps could tell me where my interpretation is wrong
    and why it is wrong... clearly, like you say, I'm confused somewhere....

    Of course - it may all be moot - how many COBOL 2002 compliant
    implementations
    are there? If no-one bothers to implement the features the way the
    standard
    indicates, then what's the point? I may be absolutely making the problem
    bigger than reality suggests.

    - Dave Rivers -

    p.s. Does anyone know a way to contact the COBOL standard committee to
    ask about this stuff? Is there a newsgroup or other facility
    where the
    committee members might "hang out"? Perhaps I need to be redirected
    to such a forum...

    --
    rivers@dignus.com Work: (919) 676-0847
    Get your mainframe programming tools at http://www.dignus.com

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Rick Smith@21:1/5 to Thomas David Rivers on Tue Jul 19 16:43:12 2022
    On Tuesday, July 19, 2022 at 5:53:17 PM UTC-4, Thomas David Rivers wrote:
    Bill Gunshannon wrote:

    On 7/18/22 23:43, Thomas David Rivers wrote:

    Bill Gunshannon wrote:


    Is this a valid COBOL 2002 program? If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?



    I am sure I could find where this is addressed given a chance to
    read the actual standard. But I am certainly not going to pay
    ISO more than $100 for the opportunity. I expect there is a place
    where the standard addresses undefined data items. But it is
    probably not where you are looking for it.

    bill


    Hi Bill!

    Your idea about "undefined" was a terrific one - I did look through
    the standard some more. There is even a section B.2 that explicitly
    lists all the undefined behavior.


    "Undefined behavior" is something totally different. You want to
    look for "Undefined Data Item" or something similar.
    Hi Bill!!

    I spent some time and looked at every occurence of "undefined" in the standard,
    there didn't seem (to me) to be any kind of statement like that.


    Unfortunately - there is no prohibition against a forward reference
    to a constant.


    Now you are calling it something else. If yo keep that up you'll
    never find it. :-) What you are saying would make sense if, like
    Pascal, COBOL had a FORWARD verb. :-) (No, FORWARD can not be used
    for data items, even in Pascal.)
    Yes - you are right - I did call it something else. It is really
    important to
    have precise terms.

    Let's define a "forward reference" as a reference to a data definition that is not yet defined at its use, but is subsequently defined (to distinguish
    it from a name that is never defined.)

    Going back to my very first post on this, this example contains a "forward reference" to the constant-name 'B':
    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    01 B CONSTANT 6.
    PROCEDURE DIVISION.
    I can't find any reason in the standard why that shouldn't compile. I
    also can't
    find a statement about when the value of a constant is 'defined'.

    The standard, under the "General Rules" for a CONSTANT (section 13.9.3)
    says:

    1) If literal-1 or compilation-variable-name-1 is specified, the
    effect of specifying
    constant-name-1 in other than this entry is as if literal-1 or
    the text represented by
    compilation-variable-name-1 were written where constant- name-1
    is written.

    ...

    3) If arithmetic-expression-1, data-name-1, or data-name-2 is
    specified, the effect of
    writing constant-name-1 in other than this entry is as if an
    integer literal were
    written where constant-name-1 is written. This integer literal
    has the value specified in
    these general rules.

    It doesn't require that the definition be encountered before its use.

    I _think_ this is the about the only situation where "something" can be
    used
    before it's defined. That is, the WORKING STORAGE section appears before
    the PROCEDURE DIVISION, so any undefined (or unqualifiable) name is simply undefined when encountered in the PROCEDURE DIVISION.

    So, the reason I'm concerned about this, is I _think_ this is the first
    time such
    a situation could arise in COBOL? (I'd like to be found wrong on that
    idea, if
    someone cares to provide an example... )

    Forward references have been part of COBOL since, like, forever.

    For the ENVIRONMENT DIVISION, forward references occur for
    FILE STATUS and RECORD KEY names. In the DATA DIVISION
    FILE SECTION file-description-entry, the record-clause may refer
    to a data-item in the WORKING-STORAGE SECTION for the length
    of a record read or to be written. In the PROCEDURE DIVISION,
    forward references to procedure-names are normal.

    What is different with 2002, is the need to resolve all references
    in the WORKING-STORAGE SECTION by potentially making multiple
    passes before processing the PROCEDURE DIVISION.

    There doesn't seem to be a prohibition at all about a
    forward
    reference (although I'm hard-pressed to consider where that might
    happen?
    Perhaps in a VALUE clause for a pointer data-definition?)


    If use of an undefined data item is covered somewhere in the standard
    then there would be no reason to address a forward reference as at the
    time the reference is made it is an undefined data item. Unless there
    was a FORWARD verb. :-)
    Yes - that is a good point, I can't find anything in the standard that
    talks about that in terms of the point-of-reference. The standard seems
    to talk about compilation-data-name as being defined or not, but
    nothing else.

    I'm with you on the intuition that there must be something in the
    standard
    that speaks to this - but I can't find it.


    As far as I can tell, the standard allows forward references to
    as-yet undefined
    constants.

    Where does the standard allow that? Where does the standard even
    mention forward references? My guess is it does not and you are
    merely assuming if it doesn't explicitly prohibit it then it allows
    it. Bad assumption. I am pretty sure that the standard does not
    prohibit inline assembler, but I doubt that means it would be allowed.

    The standard doesn't mention forward references because they are
    part of COBOL, or indeed any programming language.

    So, a compiler would be required (as Rick mentioned) to make
    multiple passes for resolving forward constant references.


    No, the compiler is only required to do the things explicitly covered
    in the standard. And, as I said, I would be willing to bet that there
    is a specific reference somewhere in the standard to "undefined data items".



    I'm not sure what that would mean for constants that appear in
    different
    sections? Can a constant in a WORKING STORAGE section reference a
    constant in a LINKAGE section? What does that mean? What does it
    mean
    if the constant is declared in the LINKAGE section of a sub-program with >> the GLOBAL clause? Can it be referenced in the enclosing program?
    Can it
    be referenced at a point in the enclosing program when the values of
    data
    in the LINKAGE section of a sub-program are explicitly undefined?
    When does
    a compile-time constant become "undefined"?

    The 2002 standard only seems to say:

    5) Neither the value of literal-1 nor the value of any of the
    literals in
    arithmetic-expression-1 shall be dependent, directly or
    indirectly,
    upon the value of constant-name-1.

    (constant-name-1 is the name being defined as a constant, with
    arithmetic-expression-1
    being the value.) And - since they mention "indirectly" - that
    would seem to
    imply the possibility of a forward reference to an
    as-yet-to-be-defined constant (as I think
    that would be about the only way to "indirectly" reference the
    constant being defined...
    wouldn't it?)

    So - it would seem to explicitly disallow a recursive constant
    definition
    (so the program snippet I posted is invalid) but - it appears to have
    nothing to say
    about the use of a constant before it's defined... and thus would
    allow it.

    If that understanding is correct, the GnuCOBOL compiler needs to
    make an
    adjustment for that. Microfocus implements level-78 "constants",
    I'm not sure
    what they do with any forward reference (if someone happens to have
    that available
    it might be nice to check what they do.)
    But - I think some clarifications of what a "constant" is, and just
    when it is
    defined and available might be useful.


    I still think you are making a mountain out of a molehill. I do not
    think that forward references are allowed. I have never seen any
    mention of them in previous COBOL language references and I am unaware
    of any mention of them in the 2002 standard. You are dealing with an undefined data item at the time of its use and the result of that is handled by the compiler as it always has been. Being a CONSTANT doesn't impart any magical powers. It is still just a data item.

    bill

    Yeah - maybe I am... but with the strange phrase in the standard about directly or indirectly referencing the name being defined, it seems to me that the authors were actually _intending_ to allow a forward-reference
    (as that would be the only way to arrive at an indirect reference - I
    think.)
    So, if the intent is to allow a forward reference, and there isn't anything in the standard that disallows it, would it then be safe to say it's
    allowed?

    Also - there are some questions I still have about constants defined in
    a sub-program's WORKING STORAGE or LINKAGE sections with the GLOBAL
    clause attached. Are such constants visible in the containing program?
    The standard is clared that such data is "undefined" when the sub-program
    is not active (which makes absolute sense) but does not prohibit the reference
    to them. Only that if you do, you are entering the "realm of undefined" if the sub-program is not active (also, this begs a question about _which_ one you are referencing if the sub-program is at all RECURSIVE - but that's a different question.) So - what does this mean about CONSTANTs defined
    in such sections? Are they globally visible at compile-time - or only intended
    to be visible when the sub-program is active? I can't imagine that's
    the intent,
    but that seems to be what one can consider from the verbiage in the
    standard.

    A CONSTANT, defined anywhere in the DATA DIVISION, may be referenced
    anywhere a value may be used in the DATA DIVISION (and as I recall, possibly
    in the ENVIRONMENT DIVISION). It may be referenced in the PROCEDURE
    DIVISION.

    If the CONSTANT has the GLOBAL attribute, it may be referenced in any
    contained program; however, it may not be referenced in any containing
    program.

    If the standard is really just a "set of guidelines" - then, I guess
    I'll just have
    to be disappointed.

    I was hoping someone from the committee might be lurking here with
    some rationale, or perhaps could tell me where my interpretation is wrong
    and why it is wrong... clearly, like you say, I'm confused somewhere....

    Of course - it may all be moot - how many COBOL 2002 compliant implementations
    are there? If no-one bothers to implement the features the way the
    standard
    indicates, then what's the point? I may be absolutely making the problem bigger than reality suggests.

    The 2002 standard was not broadly implemented. Most are using the
    current 2014 standard. The next revision, currently 202X, may be approved
    this year.

    p.s. Does anyone know a way to contact the COBOL standard committee to
    ask about this stuff? Is there a newsgroup or other facility
    where the
    committee members might "hang out"? Perhaps I need to be redirected
    to such a forum...

    AFAIK the committee members communicate using a restricted access
    site. Any questions about the standard would have to be sent "snail mail"
    to the committee through INCITS (for the US) or ISO (international). I don't have specific information and haven't cared to look for it.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Arnold Trembley@21:1/5 to Bill Gunshannon on Tue Jul 19 20:03:22 2022
    On 7/19/2022 12:22 PM, Bill Gunshannon wrote:
    On 7/18/22 01:41, Thomas David Rivers wrote:
    (SNIP)

    I am sure I could find where this is addressed given a chance to
    read the actual standard.  But I am certainly not going to pay
    ISO more than $100 for the opportunity.  I expect there is a place
    where the standard addresses undefined data items.  But it is
    probably not where you are looking for it.

    bill




    I think this link to a copy of the 2014 standard still works, and it is
    still free. It's an 8 megabyte PDF.

    http://www.open-std.org/jtc1/sc22/open/ISO-IECJTC1-SC22_N4561_ISO_IEC_FCD_1989__Information_technol.pdf

    Watch out for the URL wrapping around...

    --
    https://www.arnoldtrembley.com/

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Thomas David Rivers@21:1/5 to Rick Smith on Tue Jul 19 15:53:11 2022
    Rick Smith wrote:

    Forward references have been part of COBOL since, like, forever.

    For the ENVIRONMENT DIVISION, forward references occur for
    FILE STATUS and RECORD KEY names. In the DATA DIVISION
    FILE SECTION file-description-entry, the record-clause may refer
    to a data-item in the WORKING-STORAGE SECTION for the length
    of a record read or to be written. In the PROCEDURE DIVISION,
    forward references to procedure-names are normal.



    Many thanks Rick for pointing these out!

    What is different with 2002, is the need to resolve all references
    in the WORKING-STORAGE SECTION by potentially making multiple
    passes before processing the PROCEDURE DIVISION.



    Yes - that's what I was kinda getting at, albeit very indirectly;
    but if you can allow a forward reference then multiple passes would
    be needed.

    So, then, we can assert that the example I posted with the forward
    reference _should_ compile by a 2002/2014 conforming compiler?






    The standard doesn't mention forward references because they are
    part of COBOL, or indeed any programming language.



    They aren't part of many programming languages - which is where I
    was coming from. Many languages require a declaration/definition
    before a use.





    A CONSTANT, defined anywhere in the DATA DIVISION, may be referenced
    anywhere a value may be used in the DATA DIVISION (and as I recall, possibly >in the ENVIRONMENT DIVISION). It may be referenced in the PROCEDURE
    DIVISION.

    If the CONSTANT has the GLOBAL attribute, it may be referenced in any >contained program; however, it may not be referenced in any containing >program.



    Yes - I was wondering why the constants aren't part of a new section,
    instead
    of sprinkled-in with the other data-definitions from the existing
    section. It
    was somewhat confusing, to me, that constants "live" in WORKING STORAGE,
    LOCAL STORE or LINKAGE. Is this simply an artifact of being a data-definition
    and those various sections cause no distinction in a CONSTANT
    data-definition?
    (I _think_ that's what you are saying above?)




    The 2002 standard was not broadly implemented. Most are using the
    current 2014 standard. The next revision, currently 202X, may be approved >this year.



    Oh my! I didn't even realize - I've since made a trip to the ANSI store
    for the 2014 standard... thanks for pointing that out!



    p.s. Does anyone know a way to contact the COBOL standard committee to
    ask about this stuff? Is there a newsgroup or other facility
    where the
    committee members might "hang out"? Perhaps I need to be redirected
    to such a forum...



    AFAIK the committee members communicate using a restricted access
    site. Any questions about the standard would have to be sent "snail mail"
    to the committee through INCITS (for the US) or ISO (international). I don't >have specific information and haven't cared to look for it.



    *Many* thanks for your response! It was very helpful!

    - Dave Rivers -

    --
    rivers@dignus.com Work: (919) 676-0847
    Get your mainframe programming tools at http://www.dignus.com

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Vincent Coen@21:1/5 to All on Wed Jul 20 15:05:24 2022
    Hello Thomas!

    Wednesday July 20 2022 14:36, I wrote to Thomas David Rivers:

    Follow on - [bugs:#846] Forward var reference using arithmetic fails

    So will see what is said about this and you can follow up if registered on Sourceforge at https://sourceforge.net/p/gnucobol/bugs/846/


    Vincent

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Vincent Coen@21:1/5 to All on Wed Jul 20 14:36:31 2022
    Hello Thomas!

    Monday July 18 2022 06:41, Thomas David Rivers wrote to All:

    Second example does not work for GC v3.2 so cobc code is not searching
    forwards when parsing sources in this instance HOWEVER that said I would suggest it is a bug.

    Since the 60's (By my 75 year old memory) I have not noticed that the requirement for the need for backward references to a vars is required.

    For other programming languages going back to the same time frame it has
    been and no I cannot remember what one's.

    It does depend on the way parsing works for a specific compiler or
    assembler.

    You example of code will be used to create a bug / ticket for the GC v3.2 compiler so will see what the GC programmers have to say on it.

    As personally it should work.

    Small point here though, where forward references of vars are used such as
    file status vars are used and defined later (for obvious reasons) this is picked up as normal BUT they do not use any form of computation etc.

    In your example it does so it might be that the initial parsing is
    rejecting it before it can get to any later stage of pre-processing.

    That said why would you not define before usage any way, if nothing else it keeps program logic flow easier to read.

    See also examples of CDF usage.

    Vince



    The COBOL 2002 standard adds constant-entry to the various
    storage sections for defining compile-time constants.

    However, I doesn't (at least in my scouring of the document) define
    *when* these are extent and when they can be used.

    For instance, this seems like a reasonable use:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 B CONSTANT 6.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    PROCEDURE DIVISION.


    Where the constant CON is used for the picture-string in the
    definition of MYDATA.

    But - I can't find where this would be an invalid COBOL program
    according to the 2002 standard:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    01 B CONSTANT 6.
    PROCEDURE DIVISION.

    In this second example, the constant 'B' is used before it is defined.
    But - the 2002 standard doesn't seem to make that illegal.

    Is this a valid COBOL 2002 program? If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?

    - Thanks! -
    - Dave Rivers -


    --
    rivers@dignus.com Work: (919) 676-0847
    Get your mainframe programming tools at http://www.dignus.com



    Vincent

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Rick Smith@21:1/5 to Thomas David Rivers on Wed Jul 20 10:26:35 2022
    On Wednesday, July 20, 2022 at 8:57:14 AM UTC-4, Thomas David Rivers wrote:
    Rick Smith wrote:

    Forward references have been part of COBOL since, like, forever.

    For the ENVIRONMENT DIVISION, forward references occur for
    FILE STATUS and RECORD KEY names. In the DATA DIVISION
    FILE SECTION file-description-entry, the record-clause may refer
    to a data-item in the WORKING-STORAGE SECTION for the length
    of a record read or to be written. In the PROCEDURE DIVISION,
    forward references to procedure-names are normal.


    Many thanks Rick for pointing these out!
    What is different with 2002, is the need to resolve all references
    in the WORKING-STORAGE SECTION by potentially making multiple
    passes before processing the PROCEDURE DIVISION.


    Yes - that's what I was kinda getting at, albeit very indirectly;
    but if you can allow a forward reference then multiple passes would
    be needed.

    So, then, we can assert that the example I posted with the forward
    reference _should_ compile by a 2002/2014 conforming compiler?

    I don't know to which example you refer, but I think Vincent is probably addressing that issue.

    The standard doesn't mention forward references because they are
    part of COBOL, or indeed any programming language.


    They aren't part of many programming languages - which is where I
    was coming from. Many languages require a declaration/definition
    before a use.

    Forward references for data definitions, yes, many; but not labels (except Pascal as I recall). In particular, any two-pass assembler may use forward references to data definitions as well as labels.

    The point, with regard to the COBOL standard, is that the standard requires that some items, DIVISIONs, SECTIONs, parts of the formats of various
    elements, etc., to appear in a certain order. Where the standard is silent on order, it is the obligation of the compiler developer to make it work for the purpose of claiming conformance to the standard.

    A CONSTANT, defined anywhere in the DATA DIVISION, may be referenced >anywhere a value may be used in the DATA DIVISION (and as I recall, possibly >in the ENVIRONMENT DIVISION). It may be referenced in the PROCEDURE >DIVISION.

    If the CONSTANT has the GLOBAL attribute, it may be referenced in any >contained program; however, it may not be referenced in any containing >program.


    Yes - I was wondering why the constants aren't part of a new section,
    instead
    of sprinkled-in with the other data-definitions from the existing
    section. It
    was somewhat confusing, to me, that constants "live" in WORKING STORAGE, LOCAL STORE or LINKAGE. Is this simply an artifact of being a
    data-definition
    and those various sections cause no distinction in a CONSTANT data-definition?
    (I _think_ that's what you are saying above?)

    There was a CONSTANT SECTION in the COBOL language definition prior
    to the 1968 standard.

    The 2002 standard was not broadly implemented. Most are using the
    current 2014 standard. The next revision, currently 202X, may be approved >this year.


    Oh my! I didn't even realize - I've since made a trip to the ANSI store
    for the 2014 standard... thanks for pointing that out!

    [snip]

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From docdwarf@panix.com@21:1/5 to rivers@dignus.com on Wed Jul 20 23:10:14 2022
    In article <62D63F0B.9060009@dignus.com>,
    Thomas David Rivers <rivers@dignus.com> wrote:
    Bill Gunshannon wrote:

    On 7/18/22 23:43, Thomas David Rivers wrote:

    Bill Gunshannon wrote:


    Is this a valid COBOL 2002 program? If not, can someone point me to >>>>> the phrase/definition in the 2002 standard that makes it invalid?



    I am sure I could find where this is addressed given a chance to
    read the actual standard. But I am certainly not going to pay
    ISO more than $100 for the opportunity. I expect there is a place
    where the standard addresses undefined data items. But it is
    probably not where you are looking for it.

    bill


    Hi Bill!

    Your idea about "undefined" was a terrific one - I did look through
    the standard some more. There is even a section B.2 that explicitly
    lists all the undefined behavior.


    "Undefined behavior" is something totally different. You want to
    look for "Undefined Data Item" or something similar.


    Hi Bill!!

    I spent some time and looked at every occurence of "undefined" in the
    standard,
    there didn't seem (to me) to be any kind of statement like that.



    Unfortunately - there is no prohibition against a forward reference
    to a constant.


    Now you are calling it something else. If yo keep that up you'll
    never find it. :-) What you are saying would make sense if, like
    Pascal, COBOL had a FORWARD verb. :-) (No, FORWARD can not be used
    for data items, even in Pascal.)


    Yes - you are right - I did call it something else. It is really
    important to
    have precise terms.

    Let's define a "forward reference" as a reference to a data definition that is not yet defined at its use, but is subsequently defined (to distinguish
    it from a name that is never defined.)

    Going back to my very first post on this, this example contains a "forward reference" to the constant-name 'B':

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    01 B CONSTANT 6.
    PROCEDURE DIVISION.

    I can't find any reason in the standard why that shouldn't compile. I
    also can't
    find a statement about when the value of a constant is 'defined'.

    The standard, under the "General Rules" for a CONSTANT (section 13.9.3)
    says:

    1) If literal-1 or compilation-variable-name-1 is specified, the
    effect of specifying
    constant-name-1 in other than this entry is as if literal-1 or
    the text represented by
    compilation-variable-name-1 were written where constant- name-1
    is written.

    ...

    3) If arithmetic-expression-1, data-name-1, or data-name-2 is
    specified, the effect of
    writing constant-name-1 in other than this entry is as if an
    integer literal were
    written where constant-name-1 is written. This integer literal
    has the value specified in
    these general rules.

    It doesn't require that the definition be encountered before its use.

    I _think_ this is the about the only situation where "something" can be
    used
    before it's defined. That is, the WORKING STORAGE section appears before the PROCEDURE DIVISION, so any undefined (or unqualifiable) name is simply undefined when encountered in the PROCEDURE DIVISION.

    So, the reason I'm concerned about this, is I _think_ this is the first
    time such
    a situation could arise in COBOL? (I'd like to be found wrong on that
    idea, if
    someone cares to provide an example... )




    There doesn't seem to be a prohibition at all about a
    forward
    reference (although I'm hard-pressed to consider where that might
    happen?
    Perhaps in a VALUE clause for a pointer data-definition?)


    If use of an undefined data item is covered somewhere in the standard
    then there would be no reason to address a forward reference as at the
    time the reference is made it is an undefined data item. Unless there
    was a FORWARD verb. :-)


    Yes - that is a good point, I can't find anything in the standard that
    talks about that in terms of the point-of-reference. The standard seems
    to talk about compilation-data-name as being defined or not, but
    nothing else.

    I'm with you on the intuition that there must be something in the
    standard
    that speaks to this - but I can't find it.



    As far as I can tell, the standard allows forward references to
    as-yet undefined
    constants.

    Where does the standard allow that? Where does the standard even
    mention forward references? My guess is it does not and you are
    merely assuming if it doesn't explicitly prohibit it then it allows
    it. Bad assumption. I am pretty sure that the standard does not
    prohibit inline assembler, but I doubt that means it would be allowed.


    So, a compiler would be required (as Rick mentioned) to make
    multiple passes for resolving forward constant references.


    No, the compiler is only required to do the things explicitly covered
    in the standard. And, as I said, I would be willing to bet that there
    is a specific reference somewhere in the standard to "undefined data
    items".



    I'm not sure what that would mean for constants that appear in
    different
    sections? Can a constant in a WORKING STORAGE section reference a
    constant in a LINKAGE section? What does that mean? What does it
    mean
    if the constant is declared in the LINKAGE section of a sub-program with >>> the GLOBAL clause? Can it be referenced in the enclosing program?
    Can it
    be referenced at a point in the enclosing program when the values of
    data
    in the LINKAGE section of a sub-program are explicitly undefined?
    When does
    a compile-time constant become "undefined"?

    The 2002 standard only seems to say:

    5) Neither the value of literal-1 nor the value of any of the
    literals in
    arithmetic-expression-1 shall be dependent, directly or
    indirectly,
    upon the value of constant-name-1.

    (constant-name-1 is the name being defined as a constant, with
    arithmetic-expression-1
    being the value.) And - since they mention "indirectly" - that
    would seem to
    imply the possibility of a forward reference to an
    as-yet-to-be-defined constant (as I think
    that would be about the only way to "indirectly" reference the
    constant being defined...
    wouldn't it?)

    So - it would seem to explicitly disallow a recursive constant
    definition
    (so the program snippet I posted is invalid) but - it appears to have
    nothing to say
    about the use of a constant before it's defined... and thus would
    allow it.

    If that understanding is correct, the GnuCOBOL compiler needs to
    make an
    adjustment for that. Microfocus implements level-78 "constants",
    I'm not sure
    what they do with any forward reference (if someone happens to have
    that available
    it might be nice to check what they do.)
    But - I think some clarifications of what a "constant" is, and just
    when it is
    defined and available might be useful.


    I still think you are making a mountain out of a molehill. I do not
    think that forward references are allowed. I have never seen any
    mention of them in previous COBOL language references and I am unaware
    of any mention of them in the 2002 standard. You are dealing with an
    undefined data item at the time of its use and the result of that is
    handled by the compiler as it always has been. Being a CONSTANT doesn't
    impart any magical powers. It is still just a data item.

    bill

    Yeah - maybe I am... but with the strange phrase in the standard about directly or indirectly referencing the name being defined, it seems to me that the authors were actually _intending_ to allow a forward-reference
    (as that would be the only way to arrive at an indirect reference - I
    think.)
    So, if the intent is to allow a forward reference, and there isn't anything in the standard that disallows it, would it then be safe to say it's
    allowed?

    Also - there are some questions I still have about constants defined in
    a sub-program's WORKING STORAGE or LINKAGE sections with the GLOBAL
    clause attached. Are such constants visible in the containing program?
    The standard is clared that such data is "undefined" when the sub-program
    is not active (which makes absolute sense) but does not prohibit the
    reference
    to them. Only that if you do, you are entering the "realm of undefined" if the sub-program is not active (also, this begs a question about _which_ one you are referencing if the sub-program is at all RECURSIVE - but that's a different question.) So - what does this mean about CONSTANTs defined
    in such sections? Are they globally visible at compile-time - or only
    intended
    to be visible when the sub-program is active? I can't imagine that's
    the intent,
    but that seems to be what one can consider from the verbiage in the
    standard.

    If the standard is really just a "set of guidelines" - then, I guess
    I'll just have
    to be disappointed.

    I was hoping someone from the committee might be lurking here with
    some rationale, or perhaps could tell me where my interpretation is wrong
    and why it is wrong... clearly, like you say, I'm confused somewhere....

    Of course - it may all be moot - how many COBOL 2002 compliant
    implementations
    are there? If no-one bothers to implement the features the way the
    standard
    indicates, then what's the point? I may be absolutely making the problem bigger than reality suggests.

    - Dave Rivers -

    p.s. Does anyone know a way to contact the COBOL standard committee to
    ask about this stuff? Is there a newsgroup or other facility
    where the
    committee members might "hang out"? Perhaps I need to be redirected
    to such a forum...

    --
    rivers@dignus.com Work: (919) 676-0847
    Get your mainframe programming tools at http://www.dignus.com

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From pete dashwood@21:1/5 to Thomas David Rivers on Thu Jul 28 01:39:56 2022
    On 18/07/2022 17:41, Thomas David Rivers wrote:
    The COBOL 2002 standard adds constant-entry to the various
    storage sections for defining compile-time constants.

    However, I doesn't (at least in my scouring of the document) define
    *when* these are extent and when they can be used.

    For instance, this seems like a reasonable use:

          IDENTIFICATION DIVISION.
           PROGRAM-ID. ALPHEDIT.
          ENVIRONMENT DIVISION.
          DATA DIVISION.
           WORKING-STORAGE SECTION.
          01  A CONSTANT 5.
          01  B CONSTANT 6.
          01  CON CONSTANT A + B.
          01  MYDATA PIC 9(CON).
          PROCEDURE DIVISION.


    Where the constant CON is used for the picture-string in the definition
    of MYDATA.

    But - I can't find where this would be an invalid COBOL program according
    to the 2002 standard:

          IDENTIFICATION DIVISION.
           PROGRAM-ID. ALPHEDIT.
          ENVIRONMENT DIVISION.
          DATA DIVISION.
           WORKING-STORAGE SECTION.
          01  A CONSTANT 5.
          01  CON CONSTANT A + B.
          01  MYDATA PIC 9(CON).
          01  B CONSTANT 6.
          PROCEDURE DIVISION.

    In this second example, the constant 'B' is used before it is defined.
    But - the 2002 standard doesn't seem to make that illegal.

    Is this a valid COBOL 2002 program?  If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?

       - Thanks! -
      - Dave Rivers -


    Please excuse the simple question of an old man:

    Don't constants in COBOL need to be defined in the DATA DIVISION after WORKING-STORAGE as...
    DATA DIVISION.
    ... WORKING-STORAGE SECTION.
    ...
    CONSTANT SECTION.
    ...
    PROCEDURE DIVISION.
    etc...?

    I'm not familiar with the 2002 standard in COBOL and I don't have a copy
    of it, but in the flavours of COBOL I have seen where CONSTANTS are
    supported, they do require to be defined in the CONSTANT SECTION.

    Having so defined them, they then acquire a "read only" quality and
    cannot be set to anything other than the initial value. (Compiler
    diagnostic if you try...)

    Of course, with the never-ending efforts to make COBOL more like
    NOT-COBOL, this constraint may well have been abolished.

    Might be worth checking what the 2002 standard says about the CONSTANT
    SECTION (if anything...)

    Cheers,

    Pete.

    --
    I used to write *COBOL*; now I can do *anything*...

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Robert Jones@21:1/5 to dash...@enternet.co.nz on Thu Jul 28 07:19:33 2022
    On Wednesday, July 27, 2022 at 2:39:56 PM UTC+1, dash...@enternet.co.nz wrote:
    On 18/07/2022 17:41, Thomas David Rivers wrote:
    The COBOL 2002 standard adds constant-entry to the various
    storage sections for defining compile-time constants.

    However, I doesn't (at least in my scouring of the document) define
    *when* these are extent and when they can be used.

    For instance, this seems like a reasonable use:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 B CONSTANT 6.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    PROCEDURE DIVISION.


    Where the constant CON is used for the picture-string in the definition
    of MYDATA.

    But - I can't find where this would be an invalid COBOL program according to the 2002 standard:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    01 B CONSTANT 6.
    PROCEDURE DIVISION.

    In this second example, the constant 'B' is used before it is defined.
    But - the 2002 standard doesn't seem to make that illegal.

    Is this a valid COBOL 2002 program? If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?

    - Thanks! -
    - Dave Rivers -


    Please excuse the simple question of an old man:

    Don't constants in COBOL need to be defined in the DATA DIVISION after WORKING-STORAGE as...
    DATA DIVISION.
    ... WORKING-STORAGE SECTION.
    ...
    CONSTANT SECTION.
    ...
    PROCEDURE DIVISION.
    etc...?

    I'm not familiar with the 2002 standard in COBOL and I don't have a copy
    of it, but in the flavours of COBOL I have seen where CONSTANTS are supported, they do require to be defined in the CONSTANT SECTION.

    Having so defined them, they then acquire a "read only" quality and
    cannot be set to anything other than the initial value. (Compiler
    diagnostic if you try...)

    Of course, with the never-ending efforts to make COBOL more like
    NOT-COBOL, this constraint may well have been abolished.

    Might be worth checking what the 2002 standard says about the CONSTANT SECTION (if anything...)

    Cheers,

    Pete.

    --
    I used to write *COBOL*; now I can do *anything*...
    The CONSTANT RECORD clause may be specified at the 01 level anywhere in the Working-Storage and Linkage sections in the 2014 standard.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Robert Jones@21:1/5 to Robert Jones on Sat Jul 30 15:41:56 2022
    On Thursday, July 28, 2022 at 3:19:35 PM UTC+1, Robert Jones wrote:
    On Wednesday, July 27, 2022 at 2:39:56 PM UTC+1, dash...@enternet.co.nz wrote:
    On 18/07/2022 17:41, Thomas David Rivers wrote:
    The COBOL 2002 standard adds constant-entry to the various
    storage sections for defining compile-time constants.

    However, I doesn't (at least in my scouring of the document) define *when* these are extent and when they can be used.

    For instance, this seems like a reasonable use:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 B CONSTANT 6.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    PROCEDURE DIVISION.


    Where the constant CON is used for the picture-string in the definition of MYDATA.

    But - I can't find where this would be an invalid COBOL program according to the 2002 standard:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    01 B CONSTANT 6.
    PROCEDURE DIVISION.

    In this second example, the constant 'B' is used before it is defined. But - the 2002 standard doesn't seem to make that illegal.

    Is this a valid COBOL 2002 program? If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?

    - Thanks! -
    - Dave Rivers -


    Please excuse the simple question of an old man:

    Don't constants in COBOL need to be defined in the DATA DIVISION after WORKING-STORAGE as...
    DATA DIVISION.
    ... WORKING-STORAGE SECTION.
    ...
    CONSTANT SECTION.
    ...
    PROCEDURE DIVISION.
    etc...?

    I'm not familiar with the 2002 standard in COBOL and I don't have a copy
    of it, but in the flavours of COBOL I have seen where CONSTANTS are supported, they do require to be defined in the CONSTANT SECTION.

    Having so defined them, they then acquire a "read only" quality and
    cannot be set to anything other than the initial value. (Compiler diagnostic if you try...)

    Of course, with the never-ending efforts to make COBOL more like
    NOT-COBOL, this constraint may well have been abolished.

    Might be worth checking what the 2002 standard says about the CONSTANT SECTION (if anything...)

    Cheers,

    Pete.

    --
    I used to write *COBOL*; now I can do *anything*...
    The CONSTANT RECORD clause may be specified at the 01 level anywhere in the Working-Storage and Linkage sections in the 2014 standard.
    I should have added that there is also a constant entry that consists of a single elementary item with the keyword CONSTANT, which is what I now think was the subject of the question. It may be anywhere in the data division.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From pete dashwood@21:1/5 to Robert Jones on Sun Aug 21 14:10:36 2022
    On 29/07/2022 02:19, Robert Jones wrote:
    On Wednesday, July 27, 2022 at 2:39:56 PM UTC+1, dash...@enternet.co.nz wrote:
    On 18/07/2022 17:41, Thomas David Rivers wrote:
    The COBOL 2002 standard adds constant-entry to the various
    storage sections for defining compile-time constants.

    However, I doesn't (at least in my scouring of the document) define
    *when* these are extent and when they can be used.

    For instance, this seems like a reasonable use:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 B CONSTANT 6.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    PROCEDURE DIVISION.


    Where the constant CON is used for the picture-string in the definition
    of MYDATA.

    But - I can't find where this would be an invalid COBOL program according >>> to the 2002 standard:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    01 B CONSTANT 6.
    PROCEDURE DIVISION.

    In this second example, the constant 'B' is used before it is defined.
    But - the 2002 standard doesn't seem to make that illegal.

    Is this a valid COBOL 2002 program? If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?

    - Thanks! -
    - Dave Rivers -


    Please excuse the simple question of an old man:

    Don't constants in COBOL need to be defined in the DATA DIVISION after
    WORKING-STORAGE as...
    DATA DIVISION.
    ... WORKING-STORAGE SECTION.
    ...
    CONSTANT SECTION.
    ...
    PROCEDURE DIVISION.
    etc...?

    I'm not familiar with the 2002 standard in COBOL and I don't have a copy
    of it, but in the flavours of COBOL I have seen where CONSTANTS are
    supported, they do require to be defined in the CONSTANT SECTION.

    Having so defined them, they then acquire a "read only" quality and
    cannot be set to anything other than the initial value. (Compiler
    diagnostic if you try...)

    Of course, with the never-ending efforts to make COBOL more like
    NOT-COBOL, this constraint may well have been abolished.

    Might be worth checking what the 2002 standard says about the CONSTANT
    SECTION (if anything...)

    Cheers,

    Pete.

    --
    I used to write *COBOL*; now I can do *anything*...
    The CONSTANT RECORD clause may be specified at the 01 level anywhere in the Working-Storage and Linkage sections in the 2014 standard.

    OK, Thanks for that, Robert.

    Pete.

    --
    I used to write *COBOL*; now I can do *anything*...

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From pete dashwood@21:1/5 to Robert Jones on Sun Aug 21 14:11:32 2022
    On 31/07/2022 10:41, Robert Jones wrote:
    On Thursday, July 28, 2022 at 3:19:35 PM UTC+1, Robert Jones wrote:
    On Wednesday, July 27, 2022 at 2:39:56 PM UTC+1, dash...@enternet.co.nz wrote:
    On 18/07/2022 17:41, Thomas David Rivers wrote:
    The COBOL 2002 standard adds constant-entry to the various
    storage sections for defining compile-time constants.

    However, I doesn't (at least in my scouring of the document) define
    *when* these are extent and when they can be used.

    For instance, this seems like a reasonable use:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 B CONSTANT 6.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    PROCEDURE DIVISION.


    Where the constant CON is used for the picture-string in the definition >>>> of MYDATA.

    But - I can't find where this would be an invalid COBOL program according >>>> to the 2002 standard:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. ALPHEDIT.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 A CONSTANT 5.
    01 CON CONSTANT A + B.
    01 MYDATA PIC 9(CON).
    01 B CONSTANT 6.
    PROCEDURE DIVISION.

    In this second example, the constant 'B' is used before it is defined. >>>> But - the 2002 standard doesn't seem to make that illegal.

    Is this a valid COBOL 2002 program? If not, can someone point me to
    the phrase/definition in the 2002 standard that makes it invalid?

    - Thanks! -
    - Dave Rivers -


    Please excuse the simple question of an old man:

    Don't constants in COBOL need to be defined in the DATA DIVISION after
    WORKING-STORAGE as...
    DATA DIVISION.
    ... WORKING-STORAGE SECTION.
    ...
    CONSTANT SECTION.
    ...
    PROCEDURE DIVISION.
    etc...?

    I'm not familiar with the 2002 standard in COBOL and I don't have a copy >>> of it, but in the flavours of COBOL I have seen where CONSTANTS are
    supported, they do require to be defined in the CONSTANT SECTION.

    Having so defined them, they then acquire a "read only" quality and
    cannot be set to anything other than the initial value. (Compiler
    diagnostic if you try...)

    Of course, with the never-ending efforts to make COBOL more like
    NOT-COBOL, this constraint may well have been abolished.

    Might be worth checking what the 2002 standard says about the CONSTANT
    SECTION (if anything...)

    Cheers,

    Pete.

    --
    I used to write *COBOL*; now I can do *anything*...
    The CONSTANT RECORD clause may be specified at the 01 level anywhere in the Working-Storage and Linkage sections in the 2014 standard.
    I should have added that there is also a constant entry that consists of a single elementary item with the keyword CONSTANT, which is what I now think was the subject of the question. It may be anywhere in the data division.

    OK, thanks.

    Pete.


    --
    I used to write *COBOL*; now I can do *anything*...

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)