Menu

SCREEN SECTION ....USING

GnuCOBOL
2020-07-24
2020-07-27
  • Maurizio Bongini

    HI
    ENV : Windows 7 Gnucobol 3.1-dev-0 Arnold binaries 17 may 2020
    I attach a simple program to recreate the problem ...
    DISPLAY LINEA-MOVIMENTO AT 0101. works correctly
    DISPLAY S-RESET . does not display spaces .it diasplay instead all underscores
    I do not know if this is a bug or it works as designed ......
    thanks in advance for the support
    Maurizio


        IDENTIFICATION DIVISION.
        PROGRAM-ID. using1.
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER. COBTEST.
       OBJECT-COMPUTER. COBTEST.
       SPECIAL-NAMES. DECIMAL-POINT IS COMMA.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
       DATA DIVISION.
       FILE SECTION.
       WORKING-STORAGE SECTION.
    
       01 DEBUG1 PIC X .
       01 LINEA-MOVIMENTO .
         02 FILLER PIC X(10) VALUE ALL '_'. 
         02 FILLER PIC X(01) VALUE SPACE .       
         02 FILLER PIC X(20) VALUE ALL'_' .
         02 FILLER PIC X(02) VALUE ALL SPACES .
         02 FILLER PIC X(05) VALUE ALL '_' .
         02 FILLER PIC X(01) VALUE SPACE .
         02 FILLER PIC X(12) VALUE ALL '_' .
         02 FILLER PIC X(01) VALUE SPACE .
         02 FILLER PIC X(02) VALUE ALL '_' .
         02 FILLER PIC X(01) VALUE SPACE .
         02 FILLER PIC X(17) VALUE ALL '_' .
    
       SCREEN SECTION.
    
       01 S-RESET.  
          02 LINE 12 COL 01 PIC X(72) USING LINEA-MOVIMENTO .
          02 LINE 13 COL 01 PIC X(72) USING LINEA-MOVIMENTO .
          02 LINE 14 COL 01 PIC X(72) USING LINEA-MOVIMENTO .
          02 LINE 15 COL 01 PIC X(72) USING LINEA-MOVIMENTO .
          02 LINE 16 COL 01 PIC X(72) USING LINEA-MOVIMENTO .
          02 LINE 17 COL 01 PIC X(72) USING LINEA-MOVIMENTO .
          02 LINE 18 COL 01 PIC X(72) USING LINEA-MOVIMENTO .
          02 LINE 19 COL 01 PIC X(72) USING LINEA-MOVIMENTO .
    
       PROCEDURE DIVISION.
    
       DISPLAY LINEA-MOVIMENTO AT 0101.
       DISPLAY S-RESET .    
       ACCEPT DEBUG1 AT 2480.
       STOP RUN .
    
       END PROGRAM using1.
      *
    
     

    Last edit: Maurizio Bongini 2020-07-24
    • Simon Sobisch

      Simon Sobisch - 2020-07-24

      I'll recheck this next week. In general UNDERLINE should work, can you maybe recheck with the MSYS2 generated binaries he also published? Background: those use ncurses, while the other ones use PDCurses, so if it works in only one there's a good direction to check further... and to possibly find a bug in GnuCOBOL that can be fixed with 3.1 rc2 - or a message that is found to be needed "not our bug" and then can be reported to PDCurses.

       

      Last edit: Simon Sobisch 2020-07-24
  • Joe Reichart

    Joe Reichart - 2020-07-24

    It will display what you assign to it until you re-initialize it.

    DISPLAY LINEA-MOVIMENTO AT 0101.
    move spaces to LINEA-MOVIMENTO
    DISPLAY S-RESET .
    ACCEPT DEBUG1 AT 2480.
    STOP RUN .

     
  • Maurizio Bongini

    HI Simon
    Thanks for the answer ....
    i will check Arnold's site, download the NCURSES version and provide a feedback...
    The problem is only with SPACES if i change SPACE to '-' it works correctly ...

     

    Last edit: Maurizio Bongini 2020-07-25
  • Maurizio Bongini

    Hi Simon
    I installed 64 bit MSYS2 from Arnold Page


    C:\Users\Admin\Documents\GC31-rc1-BDB-M64>cobc -v
    cobc (GnuCOBOL) 3.1-rc1.0
    Built Jul 09 2020 07:15:24 Packaged Jul 01 2020 00:39:38 UTC
    C version (MinGW) "10.1.0"
    loading standard configuration file 'default.conf'


    I compiled the program with the new binaries but results are always the same ,i attach here a copy of the output

     
  • Simon Sobisch

    Simon Sobisch - 2020-07-26

    Just to be sure that I got that right: S-RESET uses LINEA-MOVIMENTO, so it should additional to every earlier display (because neither the DISPLAY S-RESET nor the S-RESET definition) add the underscore + space lines at line 12 + 19 (so the display ends wth those and the same on line 1).

    That's your expectation, correct?

    And the issue is that spaces are only displayed in the first line, not in the other ones, correct?

    Looks like a bug to me.

     
  • Edward Hart

    Edward Hart - 2020-07-26

    Thanks for the report, Mauirizio. I've reproduced the behaviour and found the bug in: GnuCOBOL replaces every space with an underscore because it sees that every field in S-RESET can be used for input. However, it doesn't see that that shouldn't be done in a DISPLAY. I'll commit the fix shortly.

    (If you need a temporary workaround, replacing USING with FROM makes the DISPLAY appear correctly.)

    EDIT: I've created a bug ticket [bugs:#665].

     

    Related

    Bugs: #665


    Last edit: Edward Hart 2020-07-26
  • Maurizio Bongini

    Hi Simon ,Hi Edward
    Thanks for the support ....i will try the bypass ......
    To further diagnose ...if i cange SPACES in LINEA-MOVIMENTO with a minus '-' works correctly
    If you think the fix does not implies a long rework ,then let me know when it will be available....
    Ciao ...Maurizio

     
    • Simon Sobisch

      Simon Sobisch - 2020-07-27

      Edward already did the fix, to actually get it applied you'd need a new build from Arnold (I guess the next one will be in some weeks when rc2 is out) or create it on your own, or use the binary package in the nightly builds (still without ISAM support though).

       
  • Maurizio Bongini

    Ok Simon
    The bypass works ...i will monitor Arnold's site to download next binaries build

     

Log in to post a comment.