Menu

SCREEN and OCCURS questions

Anonymous
2022-11-16
2022-11-28
  • Anonymous

    Anonymous - 2022-11-16

    Hello all – I have a couple of questions for the group. I see where the OCCURS clause isn’t supported in the SCREEN SECTION. Are there plans to implement it in the future?
    If not, does anyone have any suggestions on how to handle screens that currently use OCCURS (with a different Cobol compiler) to define/display fields dynamically? If it can’t be done natively, are there any third party products that can provide that functionality?

    I’m working on an application migration project and I’d like to use GnuCOBOL, but this might be a show stopper. We have dozens of screens that use OCCURS.
    Below is a stripped down example.

    Thanks in advance for any help you can provide.

       77  A-I PIC 99.
       77  A-II PIC 99.
    
       01  SCREEN-TEST.                                                      
         05  A-WIDGET-TYPE        PIC X(4).                                
         05  A-EACH-LINE      OCCURS 19 TIMES INDEXED BY A-I.                 
           10  A-EACH-WIDGET OCCURS  5 TIMES INDEXED BY A-II.                
             15  A-WIDGET-LOCATION PIC ZZ9.                                 
             15  FILLER          PIC X.                                   
             15  A-WIDGET-NAME   PIC X(10).                               
             15  FILLER          PIC X.
    
          SET A-I, A-II               TO 1.
         PERFORM 97310-LOAD-WIDGETS UNTIL END-OF-INPUT.
    
         97300-LOAD-WIDGETS          SECTION.
         97310-LOAD-WIDGETS.
          PERFORM 51000-READ-WIDGET-RECORD.
          IF END-OF-INPUT
             GO TO EXIT.
          MOVE SORT-WIDGET-LOCATION TO A-WIDGET-LOCATION(A-I,A-II).
          MOVE SORT-SIDGET-NAME TO A-WIDGET-NAME(A-I,A-II).
          SET A-I UP BY 1.
          IF A-I IS GREATER THAN TOTAL-LINES
             SET A-I TO 1
             SET A-II UP BY 1.
        EXIT.
    
     

    Last edit: Simon Sobisch 2022-11-16
    • Simon Sobisch

      Simon Sobisch - 2022-11-16

      Hm, there is neither a SCREEN SECTION nor a DISPLAY/ACCEPT in there.
      Can you please edit the post and drop a note? Also showing cobc -V along with the error message you see would help (at least for others to find that topic later).

       
  • Jeff S

    Jeff S - 2022-11-16

    Sorry, that is the code from the original program, not the one written with GnuCobol. I don't see a way to edit that post, maybe because I was anonymous?

    Here's the program I'm writing with GnuCobol. It's a scaled down version of the original, but I'm just trying to figure out how to handle the logic of adding fields dynamically to display on the screen. The original program has a max of 19 lines with five columns per line (hence 19 and 5 in the OCCURS). I'm just trying to display three fields on one line in the program below. I think once I know how to do that, I can figure out how to display a variable number of fields.

    All this is assuming that SCREEN/OCCURS will work, and I'm inferring it does?

    Thanks a lot for your help with this.

           IDENTIFICATION DIVISION.
           PROGRAM-ID.         TESTP.
    
           ENVIRONMENT DIVISION.
           CONFIGURATION SECTION.
           INPUT-OUTPUT        SECTION.
           FILE-CONTROL.
    
           DATA DIVISION.
    
           FILE SECTION.
    
           WORKING-STORAGE SECTION.
            77  LOC-COUNTER PIC 9.
            77  CL PIC 99.
            77  COL-I PIC 99.
            77  ROW-I PIC 99.
    
           SCREEN SECTION.
    
               01  SCREEN-TEST BLANK SCREEN AUTO-SKIP.
               05  A-EACH-LINE      OCCURS 19 TIMES.
                   10  A-EACH-WIDGET OCCURS 5  TIMES.
                       15  A-WIDGET-LOCATION col CL PIC ZZ9.                        
                       15  A-WIDGET-NAME    col plus 02 PIC X(10).
    
           PROCEDURE DIVISION.
    
           00000-MAIN-CONTROL              SECTION.
           00010-MAIN-CONTROL.
    
            MOVE 1 TO ROW-I,COL-I,CL.
            PERFORM VARYING LOC-COUNTER FROM 1 BY 1 UNTIL LOC-COUNTER > 3
            IF LOC-COUNTER = 1
                    MOVE 1 TO A-WIDGET-LOCATION(ROW-I,COL-I)
                    MOVE "TEST2" TO A-WIDGET-NAME(ROW-I,COL-I)
            END-IF
            IF LOC-COUNTER = 2
                    COMPUTE CL = CL + 2
                    COMPUTE COL-I = COL-I + 1
                    MOVE 2 TO A-WIDGET-LOCATION(ROW-I,COL-I)
                    MOVE "TEST2" TO A-WIDGET-NAME(ROW-I,COL-I)                      
            END-IF
            IF LOC-COUNTER = 3
                    COMPUTE CL = CL + 2
                    COMPUTE COL-I = COL-I + 1
                    MOVE 3 TO A-WIDGET-LOCATION(ROW-I,COL-I)
                    MOVE "TEST3" TO A-WIDGET-NAME(ROW-I,COL-I)
            END-IF
            END-PERFORM.
    
            DISPLAY SCREEN-TEST.
            STOP RUN.
    

    Here's the cobc warnings/errors:

    root@GNUCobol1:/common/s# cobc -x -o testp testp.cbl
    
    infm16scr.cbl:37: warning: OCCURS screen items is not implemented [-Wpending]
    infm16scr.cbl:37: error: relative LINE/COLUMN clause required with OCCURS
    infm16scr.cbl:38: warning: OCCURS screen items is not implemented [-Wpending]
    infm16scr.cbl:38: error: relative LINE/COLUMN clause required with OCCURS
    root@GNUCobol1:/common/s#
    

    Here's the cobc version:

    root@GNUCobol1:/common/s# cobc -V
    
    cobc (GnuCOBOL) 3.1.2.0
    Copyright (C) 2020 Free Software Foundation, Inc.
    License GPLv3+: GNU GPL version 3 or later https://gnu.org/licenses/gpl.html
    This is free software; see the source for copying conditions.  There is NO
    warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
    Written by Keisuke Nishida, Roger While, Ron Norman, Simon Sobisch, Edward Hart
    Built     Sep 14 2021 19:23:38
    Packaged  Dec 23 2020 12:04:58 UTC
    C version "11.2.0"
    

    Again, thank you very much for your help.

     

    Last edit: Simon Sobisch 2022-11-17
    • Simon Sobisch

      Simon Sobisch - 2022-11-18

      There are four parts in this.

      The first one is the syntax checks, currently they happen "too early" (during parsing of the separate internal fields) - in your case on the group, while this check must be postponed to any non-groups the time when this is finished. That is a bug in the parser and I may find some time to look at that before 3.2 final (target for landing: not later than December 23th).
      As a work-around one could comment the syntax check in cobc/parser.c out.

      The second one is the COBOL code itself. I think that has an error because there is no line phrase on A-EACH-LINEand each of the five widgets would start at the same column - so how should that work?

      Maybe the following code would be more reasonable:

                 01  SCREEN-TEST BLANK SCREEN AUTO-SKIP.
                 05  A-EACH-LINE      OCCURS 19 TIMES line plus 1 col cl.
                     10  A-EACH-WIDGET OCCURS 5  TIMES.
                         15  A-WIDGET-LOCATION col plus 01 PIC ZZ9.
                         15  A-WIDGET-NAME     col plus 02 PIC X(10).
      
      • each line increases the current by 1 and starts in column col
      • each widget's two fields should have a relative column


      Note: the original code uses an extension, as the COBOL standard does not allow a MOVE to screen-names which are (in the standard) only used for the "attributes" and the fixed values. If you want to write standard compliant code (which likely is most portable) then you'd have to keep the data in WORKING-STORAGE and use one of the FROM/ TO/USING clauses (but then you'd have used AUTO instead of AUTO-SKIP); this is also checked when compiling with -std=cobol2002.

      Nonetheless it is useful to look at some of the rules in the COBOL standard.
      Syntax rules (aka "the first part"):

      If a screen description entry includes the OCCURS clause...
      * [...] then if it or any item subordinate to it has a description that includes the TO, FROM, or USING clause, that screen description entry shall be part of a table with the same number of dimensions and number of occurrences in each dimension as the identifier representing the receiving or sending operand. [...]
      --> syntax check which we likely don't have yet
      * [... and] also contains the COLUMN clause, then the COLUMN clause shall include the PLUS or MINUS phrase, unless the screen description entry also includes a LINE clause with a PLUS or MINUS phrase.
      * [... and] also contains the LINE clause, then the LINE clause shall include the PLUS or MINUS phrase, unless the screen description entry also includes a COLUMN clause with a PLUS or MINUS phrase.

      General rules:

      During a DISPLAY screen or an ACCEPT screen statement that references a screen item whose description includes the OCCURS clause and whose description or whose subordinate's description includes a FROM, TO, or USING clause, the data values for corresponding table elements are moved from the data table element to the screen table element or from the screen table element to the data table element.
      --> that's something the codegen must insert, I'm quite sure it does not do that that; this is the third part, gain in the compiler, but that's not an issue for the extension which is used here

      General rules (continued):

      If the description of a screen item includes the OCCURS clause, the positioning within the screen record of each occurrence of that screen item is as follows:
      a) If the description of that screen item contains a COLUMN clause, each occurrence behaves as though it had the same COLUMN clause specified.
      b) If that screen item is a group item with a subordinate screen item whose description contains a COLUMN clause with the PLUS or MINUS phrase and that group screen item is subordinate to a screen item whose description contains a LINE clause, each occurrence behaves as though it had the same subordinate entries with the same COLUMN clause specified.

      Following c+d are for the LINE clause, similar to a+b for COLUMN.

      This relative positioning is to be done in the runtime (libcob/screenio.c) and the fourth part.
      Internally this operates on a "cob_screen" which has a single "cob_field" (which then has the OCCURS attribute) and a pointer to the parent/next screen "entry".
      The issue here is that the occurs flag is not completely handled there (Edward seems to have worked on that so it is partially handled, but the state would have to be tested); I'm unlikely to find much more time for this before the 3.2 release though, so you may want to take a look at patching this (I'd start with checking the current code by setting a breakpoint at get_screen_item_line_and_col and have a look how to best handle the missing parts.

      ... after writing most of this I've seen that [feature-requests:#425] is about that and also has non-inspected patches as well as implementation notes attached...

       
  • Jeff S

    Jeff S - 2022-11-28

    Thanks for your help Simon.

    Part 1: We didn’t build from source, the system admin installed the package with apt. The customer would rather not build from source, but we will if we have to. I’ll see if there is an older package available. Does this mean that the compiler does not generate an error in versions earlier than 3.1.2.0?

    Part 2: Thank you, yes that code is indeed more reasonable.

    Part 3: Thank you for showing the rules, that is helpful.

    Part 4: It looks like what I want to do isn’t possible with the current version, is that correct? I’d love to assist with a patch, but that is way beyond my skill level. I would be willing to test the patch that shagr4th created per feature-requests:#425, but I would need some direction on how to install it, etc.

    Thinking about this some more, maybe I’m going about this wrong. Do you or anyone else know of another way to display fields on the screen ‘dynamically’, based on say the number of records in a table?

    Thanks for your help.

     

Anonymous
Anonymous

Add attachments
Cancel