Menu

#425 Implement `OCCURS` in `SCREEN SECTION`

GC 3.x
accepted
nobody
5 - default
2022-11-18
2012-02-23
DarkSetz
No

The OCCURS verb's use in the Screen Section is recognized as correct by the compiler but it is not acted upon at run-time.

A DISPLAY statement of following code produces a window that looks like this:

+------------------------------+
|                              |
+------------------------------+

when it should produce one with ten lines of body between the top and bottom borders instead of just one.

    01  OffD-Maint-Scrn-Skills-SMenu    FOREGROUND-COLOR COLOR-WHITE.
        05  LINE Window-UpperLeft-Corner-Line   COL Window-UpperLeft-Corner-Column  VALUE "+".
        05  PIC X(30)   FROM Dashed-Line.
        05  VALUE "+".
        05  OffD-MSSSM-Body OCCURS 10 TIMES.
            10  LINE PLUS 1 COL Window-UpperLeft-Corner-Column  VALUE "|".
            10  PIC X(30)   FROM Blank-Line.
            10  VALUE "|".
        05  LINE PLUS 1 COL Window-UpperLeft-Corner-Column  VALUE "+".
        05  PIC X(30)   FROM Dashed-Line.
        05  VALUE "+".
1 Attachments

Related

Bugs: #248
Bugs: #347
Bugs: #430
Discussion: In search of a project
Discussion: error in screen section occurs clause.
Discussion: occurs in screen section
Discussion: Screen anomaly???
Patches: #41

Discussion

1 2 > >> (Page 1 of 2)
  • Vincent (Bryan) Coen

    Error still present in v1.1 March 12, 2010

     
  • Simon Sobisch

    Simon Sobisch - 2014-02-26

    Rechecked with GNU Cobol 1.1 release (scrocc.cbl attached), problem still exists.
    With 2.x there is only one instead of 10 lines, too and additional the first "|" in the line is missing.

    Simon

     
    • Vincent (Bryan) Coen

      An issue that was similar if not the same was reported to Roger two
      +years ago by myself against a test program in the lists.
      It also involved occurs & values within screen section.

      I tested it after a fix (by Roger) to confirm it was resolved.
      I am a little puzzled why this has re-appeared, so assume that the v2
      code base is not of the latest that Roger had given out to us for
      testing and no it was not the first release !

      Looks like I must browse the code base between the original and v2.1.

      Before I do so please confirm what version it has been tested against.

      Vince

       

      Last edit: Simon Sobisch 2014-08-05
  • Simon Sobisch

    Simon Sobisch - 2014-08-05

    Still broken with current svn revision in 2.x.

    Here is another sample that doesn't work:

           IDENTIFICATION DIVISION.
           PROGRAM-ID. prog.
    
           SCREEN SECTION.
           01  screen-var LINE 1.
               03  nums COL PLUS 3 PIC 999 OCCURS 3 TIMES.
    
           PROCEDURE DIVISION.
               DISPLAY screen-var END-DISPLAY.
               ACCEPT  omitted    END-ACCEPT.
               STOP RUN.
    

    Simon

     
  • Louis Krupp

    Louis Krupp - 2014-09-05

    Potential patch for groups and fields with OCCURS clause.

     
  • Edward Hart

    Edward Hart - 2016-06-08
    • labels: --> screen section, OCCURS
    • summary: Screen Section Bug - OCCURS verb --> Screen Section Bug - OCCURS clause
    • status: open --> accepted
    • Group: unclassified --> GC 2.0
    • Priority: 5 --> 5 - default
     
  • Edward Hart

    Edward Hart - 2016-06-08
    • assigned_to: Edward Hart
     
  • Simon Sobisch

    Simon Sobisch - 2016-10-12

    Edward, can you please check the patch and commit the fix and upload your updated screenio tests?

     
    • Edward Hart

      Edward Hart - 2016-10-12

      I can't clearly recall reviewing that patch, but I think it failed to account for how screen fields were allocated. I'll check it more thoroughly again, though.

      I had a go myself a few months back. I found two possible approaches:

      • Adding a pointer parameter to the screen functions in libcob to handle arrays. I never did this, because it I didn't have the energy to modify a lot of typeck.c and to change the algorithm used in iterating over screen fields.
      • Treating each table entry as a new field. This meant less change and easier support for higher-dimensioned tables, but at the cost of massive bloat in generated code. I attempted to implement this, but eventually gave up.
       

      Last edit: Edward Hart 2016-10-17
  • Edward Hart

    Edward Hart - 2016-10-17
    • assigned_to: Edward Hart --> nobody
     
  • Edward Hart

    Edward Hart - 2016-10-17

    Louis' patch fails when provided with

           *> ...
           DATA DIVISION.
           SCREEN SECTION.
           01  scr.
               03  scr-table COL + 1 PIC X OCCURS 10 TIMES VALUE "b".
    
           PROCEDURE DIVISION.
               DISPLAY scr AT LINE 1, COL 1 *> Only displays one b at COL 2.
               *> ...
    

    and causes compilation errors when you try to display just one element of a table (specifically, the compiler tries to pass a cob_field * to a function expecting a cob_screen *).

    As such, this bug requires a non-trivial patch to fix. As I now lack the time (and interest) to provide that, I'm removing myself as the owner of this ticket.

     
  • PatMcC

    PatMcC - 2017-06-18

    Hi Edward

    I am going to need a lot of time to get this done but I am interested in fixing this.

    I think this feature has value for adding boxes and lines and such.

    -Pat

     
    • Louis Krupp

      Louis Krupp - 2017-06-21

      I looked at this a couple of years ago. I had a patch (see attached)
      that fixed at least part of the problem at the time, but intervening
      changes to screenio.c have made it pretty useless now. When Edward got
      back to me last October, I said I'd look at it, but I got distracted by
      other things.

      The problem seems to be that cob_screen_puts() calls
      get_screen_item_line_and_col() to return the static line and column
      associated with an item, and those are assigned to cob_current_y and
      cob_current_x. This overrides the line increment that happens in
      cob_screen_moveyx(), so the displayed box is still flat.

      Good luck with this.

      Louis

       

      Last edit: Simon Sobisch 2017-06-21
  • Simon Sobisch

    Simon Sobisch - 2017-07-03

    Note for anyone checking this issue: we have an additional parsing part to do here as the relative line/col checks are currently done directly on the field, but it should likely be postponed until all childs are parsed as the program above may be coded (at least with ACUCOBOL) as

           IDENTIFICATION DIVISION.
           PROGRAM-ID. prog.
    
           SCREEN SECTION.
           01  screen-var LINE 1.
               03  FILLER OCCURS 3 TIMES.
                   05  nums COL PLUS 3 PIC 999.
    
           PROCEDURE DIVISION.
               DISPLAY screen-var END-DISPLAY.
               ACCEPT  omitted    END-ACCEPT.
               STOP RUN.
    

    which in this case results in error: relative LINE/COLUMN clause required with OCCURS. It compiles if the relative position is moved next to the OCCURS clause, but should work with the sample above, too.

    And another part is references to a table:

           IDENTIFICATION DIVISION.
           PROGRAM-ID. prog.
    
           01  DATA-TAB.
               03 DATA-LINE OCCURS 3.
                   05 nums COL PIC 999.
    
           SCREEN SECTION.
           01  screen-var LINE 1.
               03  FILLER OCCURS 3 TIMES COL PLUS 3.
                   05 COL 07 PIC zz9 FROM nums.
    
           PROCEDURE DIVISION.
               DISPLAY screen-var END-DISPLAY.
               ACCEPT  omitted    END-ACCEPT.
               STOP RUN.
    

    Not sure if the rule is "anything referenced with USING/FROM below the OCCURS must be a table item with at least the same size" or "if it is a table item it the same index is used, otherwise no index"...

     
  • Simon Sobisch

    Simon Sobisch - 2017-08-18
    • Group: 2.2 --> GC 2.3
     
  • Simon Sobisch

    Simon Sobisch - 2017-08-18

    Should raise a PENDING("OCCURS in SCREEN SECTION") as the runtime doesn't handle it.

     
    • Edward Hart

      Edward Hart - 2017-08-18

      Done in [r1999].

       
      • Simon Sobisch

        Simon Sobisch - 2017-08-18

        Thank you, nothing more to do here for 2.2.

         
  • Simon Sobisch

    Simon Sobisch - 2017-12-10
    • Group: GC 3.0 --> GC 3.x
     
  • jorge infante

    jorge infante - 2018-12-26

    Hi, all!
    What is the next steps with this "problem"? I'm trying to migrate a lot of programs from mfcobol to opencobol, and, it's a hard work to convert tables in screen section to non-tables fields. Is there a practical workaround?

     
  • Patrick McCavery

    Hi Jorge

    I don't know of a work around but I will give this bug a try over the holiday break. maybe I can figure it out.

    -Pat

     
  • jorge infante

    jorge infante - 2018-12-26

    Thank you, Patrick!

    Please, let me know any news about it.
    And if I can collaborate, gladly

    jorge

     
  • Patrick McCavery

    Hi Guys

    I haven't been so great for a few months but I am pretty sick right now, I think it's the flu. Sorry if this is another low quality post :(

           identification division.
           program-id. "occurs-bug" .
           data division .
           working-storage section.
           01 thing-1 pic x(10) value is "thing 1".
           01 thing-2 pic x(10) value is "thing 2".
           01 thing-3 pic x(10) value is "thing 3".
           01 hold-open pic 9 .
    
           screen section.
    
           01  screen-var line 1.
               03  filler pic x(20) value is "occurs screen" .
          *> line plus 10 works
               03  filler occurs 17 times line plus 10 .
                   05  pic x(10)    line plus 1 using thing-1.
          *> line plus 1 works but does not repeat 17 times
                   05  pic x(10)    line plus 1 using thing-1.
                   05  pic x(10)    line plus 1 using thing-1.
                   05  pic x(10)    line plus 1 using thing-1.
    
           procedure division .
           accept screen-var
    
           goback.
           end program "occurs-bug" .
    

    I inserted fprintf statements in all of the functions in screenio. In cob_prep_input, I have this as well:

    fprintf(fp, "adding str in cob_addnstr(and getch) %s, size is %d\n", data, size);
    

    and there is one at the start of cob_prep_input that prints the value of s->occurs.

    Here is the output of the fprintf statements. I need to looks at this when I am feeling better but I am wondering if the occurs member in the linked list of cob_screens is not being processed in the right order. It's a linked list and if it is looped through already, there is nothing left to process. I am still not sure...

    The cob_addnstr may be a bit misleading as the fprintf statement is not NUL terminated. However it is still also the only time it was printed to the screen

    Here is the output of the fprintf statements

    cob_screen_accept
    extract_line_and_col_vals
    screen_accept
    init_cob_screen_if_needed
    cob_screen_init
    cob_move_cursor
    cob_prep_input
    pausing at start of cob_prep_input, occurs is 0
    cob_screen_moveyx
    cob_move_cursor
    cob_prep_input
    pausing at start of cob_prep_input, occurs is 0
    cob_screen_puts
    get_screen_item_line_and_col
    is_first_screen_item
    get_prev_screen_item
    get_prev_screen_item
    cob_move_cursor
    cob_screen_attr
    cob_addnstr
    raise_ec_on_truncation
    adding str in cob_addnstr(and getch) occurs screen thing 1 thing 1 thing 1 thing 1 , size is 20
    cob_prep_input
    pausing at start of cob_prep_input, occurs is 17
    cob_screen_moveyx
    cob_move_cursor
    cob_prep_input
    pausing at start of cob_prep_input, occurs is 0
    cob_screen_puts
    get_screen_item_line_and_col
    get_prev_screen_item
    get_prev_screen_item
    get_prev_screen_item
    get_prev_screen_item
    cob_move_cursor
    cob_screen_attr

     
  • Patrick McCavery

    Hi Everyone
    Still sick and brain dead here but still trying.
    See these fprintf statemetns:

    cob_prep_input
    pausing at start of cob_prep_input, occurs is 17
    address of cob_screen is is 0x6022e0
    case TYPE_FIELD (TAKE NOTE OF THIS)
    cob_screen_puts
    get_screen_item_line_and_col
    get_prev_screen_item
    get_prev_screen_item
    cob_move_cursor
    cob_screen_attr
    raise_ec_on_truncation
    cob_addch_no_trunc_check

    --Here is the part where thing-1 is added 1 char by char

    addch in cob_addch(and getch) t cob_addch_no_trunc_check
    addch in cob_addch(and getch) h cob_addch_no_trunc_check
    addch in cob_addch(and getch) i cob_addch_no_trunc_check
    addch in cob_addch(and getch) n cob_addch_no_trunc_check
    addch in cob_addch(and getch) g cob_addch_no_trunc_check
    addch in cob_addch(and getch) _ cob_addch_no_trunc_check
    addch in cob_addch(and getch) 1 cob_addch_no_trunc_check
    addch in cob_addch(and getch) _ cob_addch_no_trunc_check
    addch in cob_addch(and getch) _ cob_addch_no_trunc_check

    But look at this code

        case COB_SCREEN_TYPE_VALUE:
    fprintf(fp, "case TYPE_VALUE\n");
            cob_screen_puts (s, s->value, cobsetptr->cob_legacy,
                     ACCEPT_STATEMENT);
            if (s->occurs) {
                for (n = 1; n < s->occurs; ++n) {
                    cob_screen_puts (s, s->value, cobsetptr->cob_legacy,
                             ACCEPT_STATEMENT);
                }
            }
            break;
    

    The code to generate the occurs is in the case: COB_SCREEN_TYPE_VALUE
    which is never reached

    I also changed my test program:

            identification division.
           program-id. "occurs-bug" .
           data division .
           working-storage section.
           01 thing-1 pic x(10) value is "thing 1".
           01 thing-2 pic x(10) value is "thing 2".
           01 thing-3 pic x(10) value is "thing 3".
           01 hold-open pic 9 .
    
           screen section.
    
           01  screen-var line 1.
          *> line plus 10 works
               03  filler occurs 17 times line plus 10 using thing-1.
           procedure division .
           accept screen-var
    
           goback.
           end program "occurs-bug" .
    

    I think there are many problems with this screenio occurs code. I changed my COBOL test program because I can't see how multiple 05 subordinates would be drawn to the screen in it's current state.

    Does anyone know of a revision where the screenio occurs code actually worked?

     

    Last edit: Patrick McCavery 2018-12-31
    • Brian Tiffin

      Brian Tiffin - 2018-12-31

      Yes and no.

      Roger sent me a note, this would be in the eight years ago range, when OCCURS first went into OpenCOBOL. That was, sadly, too many hardrives, web hosts, email providers to even guess at a date range to look at any old archives of opencobol prerel tarballs that someone might have stashed.

      I wrote a quick trial, it passed. And that's about all I can say, Patrick. I know that OpenCOBOL has properly handled SCREEN OCCURS, but the fog of brain doesn't have enough electronic threads at the moment to track down the conversations.

      We don't have access to the actual code repository that was in use at the time, as far as I'm aware. We got post checkout and autotool'ed tarballs back then.

      Sorry for being so nebulous. It has worked, but if it doesn't in rev 1 of the svn copies here, I'm not sure you can go back further without tracking down 8ish year old copies of the opencobol prerel tarballs.

      Blue

       
1 2 > >> (Page 1 of 2)

Log in to post a comment.