Menu

#946 ERROR on DISPLAY STATEMENT

unclassified
not-our-bug
Chuck H.
5 - default
2024-06-15
2024-02-10
No

The following example program requires typing two fields on the screen, a name and a code.
If nothing is typed then it displays an error message requiring you to type the single field.
See screenshot.

To view the bug, proceed as follows.

a. When the program asks you to type the name, do not type anything but just press Enter see ERR10.PNG
b. The system displays the error message (using some DISPLAYS) see ERR20.PNG
c. Press Enter again to exit from the message
d. The system prompts you to enter the Name field again
e. do not type anything but just press Enter again
f. The program should display the same error message again.
g. The program executes the same DISPLAY statements again but this time the message is not displayed on the screen.
How come ?

       >>SOURCE FORMAT IS FREE
       REPLACE ==:BCOL:== BY ==with BACKGROUND-COLOR==
               ==:FCOL:== BY ==FOREGROUND-COLOR==.
IDENTIFICATION DIVISION.
program-id. TESTERROR.

ENVIRONMENT DIVISION. 
Configuration Section.
 SPECIAL-NAMES.
   CRT STATUS IS wKeyPressed.

DATA DIVISION.
*> **************************************************************
WORKING-STORAGE SECTION.
*> **************************************************************
  01 Black        constant as 00.
  01 Blue         constant as 01.
  01 Green        constant as 02.
  01 Cyan         constant as 03.
  01 Red          constant as 04.
  01 Magenta      constant as 05.
  01 Orange       constant as 06.
  01 Brown        constant as 06.   *> same color code as yellow
  01 LightGrey    constant as 07.   *> Light Gray

  01 Grey         constant as 08.   *> Dark Gray
  01 LightBlack   constant as 08.   *> same color code as Grey
  01 LightBlue    constant as 09.
  01 LightGreen   constant as 10.
  01 LightCyan    constant as 11.
  01 LightRed     constant as 12.
  01 LightMagenta constant as 13.
  01 Pink         constant as 13.
  01 Yellow       constant as 14.
  01 White        constant as 15.  *> white

01  AnageRec value space.
       03 AnageCodAge pic x(10) value space. *> code AGENT
       03 AnageRagSoc pic x(30) value space. *> NAME

*> Values that may be returned in CRT STATUS (or COB-CRT-STATUS)
78  K-ENTER       VALUE 0000.
78  K-UP          VALUE 2003.
78  K-DOWN        VALUE 2004.
78  K-LEFT        VALUE 2009.
78  K-RIGHT       VALUE 2010.
78  K-ESCAPE      VALUE 2005.
78  K-TAB         VALUE 2007.
78  K-BACKTAB     VALUE 2008.
78  K-PAGEUP      VALUE 2001.
78  K-PAGEDOWN    VALUE 2002.

01  wKeyPressed  PIC  9(04) VALUE 9999.
77  NumFields    pic  9(02) value 2. *> number of fields on screen

01  wBox-bco     pic 9(02) value cyan.
01  wBox-fco     pic 9(02) value black.

01 wRetCode     PIC 9999 value zero.
01 wFunc-NumVal PIC 9999 value zero.

77 Pivot    pic 9(02) value 01.
77 dbc      pic 9(04) value green. *> display backgr.color
77 dfc      pic 9(04) value white. *> display foregr.color
77 abc      pic 9(04) value 00. *> accept  backgr.color
77 afc      pic 9(04) value 15. *> accept  backgr.color
77 Pro      pic x(01) value '_'.
77 wHeader  pic x(80) value space.

01  wString   pic x(31) value space.

01 ER pic x.
   88 NoErrors value 'N'.
   88   Errors value 'Y'.

01  wCursorShow       BINARY-SHORT SIGNED value 2.
01  wCursorHide       BINARY-SHORT SIGNED value 0.

*> SAVE/RESTORE SCREEN VARIABLES
01 wScreenName        PIC X(256) value space.
01 wiScrOk            BINARY-LONG value zero.

01 Btabmess.
  03 Bmess     pic x(30) occurs 20 value space.

*> **************************************************************
*>           P R O C E D U R E   D I V I S I O N
*> **************************************************************
PROCEDURE DIVISION.
    set environment 'COB_SCREEN_EXCEPTIONS' TO 'Y'.
    set environment 'COB_SCREEN_ESC'        TO 'Y'.
    set environment 'COB_LEGACY'            TO '1'

*> ************************************************************************************
*> D I S P L A Y    S C R E E N
*> ************************************************************************************
   string  ' SAMPLE TEST APPLICATION ' delimited by size into wHeader
   display wHeader at 0101 with  Background-Color green Foreground-Color white highlight
   display ' ESC-<Exit>                                                                     '
                   at 2501 with Background-Color green Foreground-Color white
  display ' Name ..................:' at 0501 with  Background-Color dbc Foreground-Color dfc
  display AnageRagSoc                 at 0527 with  Background-Color abc Foreground-Color afc
  display ' Code..:'                  at 0561 with  Background-Color dbc Foreground-Color dfc
  display AnageCodAge                 at 0570 with  Background-Color abc Foreground-Color afc
  continue.

LOOP-ACCEPT.
   *> re-show the cursor
   call static 'curs_set' using by value wCursorShow end-call
   go to acc01 acc02 depending on Pivot.

ACC01.
   *> NAME
   accept AnageRagSoc at 0527 with  Background-Color abc Foreground-Color afc
          update prompt character is pro auto-skip reverse-video
   go EVALUATE-KEY.
ACC02.
   *> CODE
   accept AnageCodAge at 0570 with  Background-Color abc Foreground-Color afc
          update prompt character is pro auto-skip reverse-video
   go EVALUATE-KEY.


EVALUATE-KEY.
     EVALUATE wKeyPressed
        *> ******************************************************************
        *> ENTER = CONTROLS ON SCREEN FIELDS
        *> ******************************************************************
        WHEN K-ENTER
        WHEN K-TAB
        WHEN K-DOWN
                perform CtrFields thru CtrFieldsEx
                if Errors
                   continue
                else
                   *> go to next field on screen
                   compute Pivot = Pivot + 1
                   if Pivot > NumFields move 1 to Pivot end-if
                end-if

        WHEN K-BACKTAB
        WHEN K-UP
                 perform CtrFields thru CtrFieldsEx
                 if Errors
                    continue
                 else
                    *> go to previous field on screen
                    compute Pivot = Pivot - 1
                    *> with following statement, when cursors is on 1st field
                    *> it remains there (non to go - wrap - on last filed)
                    if Pivot < 1 move 1 to Pivot end-if
                 end-if

        *> ******************************************************************
        *> ESCAPE = EXIT
        *> ******************************************************************
        when K-ESCAPE
            go to END-OF-PROGRAM

     END-EVALUATE

     GO LOOP-ACCEPT.

 *> *****************************************************************************
 *>                        E N D     O F    P R O G R A M
 *> *****************************************************************************
 END-OF-PROGRAM.
     Goback.

 *> *****************************************************************************
 *>                 C H E C K     F I E L D S   C O N T E N T
 *> *****************************************************************************
 CtrFields.
     set NoErrors to true
     go to ctr01 ctr02 depending on Pivot.
 CTR01.
     if AnageRagSoc = space
        set Errors to true
        move lightgreen to wbox-bco move white to wbox-fco
        move '111111111111111111111111111111'  to Bmess(1)
        move '        >>> ERROR 1 <<<       '  to Bmess(2)
        move '111111111111111111111111111111'  to Bmess(3)
        move '  Please Type a NAME          '  to Bmess(4)
        move '111111111111111111111111111111'  to Bmess(5)
        move '111111111111111111111111111111'  to Bmess(6)
        move '---- enter to return ---------'  to Bmess(7)
        perform DisplayErrorMessage thru DisplayErrorMessageEx
     end-if
     go CtrFieldsEx.
 CTR02.
     if AnageCodAge = space
        set Errors to true
        move lightred to wbox-bco move yellow to wbox-fco
        move '+----------------------------+'  to Bmess(1)
        move '|       >>> ERROR 2 <<<      |'  to Bmess(2)
        move '|2222222222222222222222222222|'  to Bmess(3)
        move '|     Type a CODE !!!        |'  to Bmess(4)
        move '|2222222222222222222222222222|'  to Bmess(5)
        move '|2222222222222222222222222222|'  to Bmess(6)
        move '+- Enter to return ----------+'  to Bmess(7)
        perform DisplayErrorMessage thru DisplayErrorMessageEx
     end-if
     go CtrFieldsEx.
 CtrFieldsEx. exit.

DisplayErrorMessage.
   move Z'DUMPSCREEN.TMP' to wScreenName
   call static 'scr_dump' using by reference wScreenName returning wiScrOk end-call.
   display Bmess(1) at line 04 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
   display Bmess(2) at line 05 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
   display Bmess(3) at line 06 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
   display Bmess(4) at line 07 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
   display Bmess(5) at line 08 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
   display Bmess(6) at line 09 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
   display Bmess(7) at line 10 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
   accept omitted

   call static 'scr_restore' using by reference wScreenName returning wiScrOk end-call
   call static 'refresh' returning wiScrOk end-call

      *> CALL 'CBL_DELETE_FILE' USING wScreenName
      continue.
DisplayErrorMessageEx. exit.
1 Attachments

Related

Bugs: #946

Discussion

<< < 1 2 3 > >> (Page 2 of 3)
  • Eugenio Di Lorenzo

    Chuck and Simon, first of all I want to thank you both for what you are doing.
    I would say we can wait for the solution from Bill Gray.
    Probably the error was in pdcurses and pdcurses_mod inherited it.
    The most important thing is that the bug will be fixed.

     
  • Chuck H.

    Chuck H. - 2024-06-07

    Eugenio,

    Bill Gray sent me an email with a fix to the source code of pdcursesmod, it has not been implemented as of yet.

    I did run my build process for GNUCOBOL 3.2 release and the patched version of pdcurses and it does fix the problem.

    Before we release any new build, I would prefer to wait for Bill Gray to apply his fix to his Github repository. If you would like a test build let me know via email (via a PM) and I can provide that when I get some time.

        Chuck Haatvedt
    
     
    • Eugenio Di Lorenzo

      Great news !
      I agree with you. It's better if we wait for the release of the new library.
      One thing isn't clear to me.
      Will it then be sufficient to replace pdcurses.dll with the new updated version or do we have to wait for Arnold to make an updated release of the entire compiler suite ?

       
      • Simon Sobisch

        Simon Sobisch - 2024-06-07

        Updated pdcurses.dll is enough, that's the benefit of shared libraries.

         
  • Simon Sobisch

    Simon Sobisch - 2024-06-07
    • labels: screenio, libcob --> screenio, libcob, PDCurses
    • status: pending --> not-our-bug
    • assigned_to: Boris Eng --> Chuck H.
    • Group: GC 3.2 --> unclassified
     
  • Simon Sobisch

    Simon Sobisch - 2024-06-07

    Upstream bug with some discussion and a possible upstream fix:
    https://github.com/Bill-Gray/PDCursesMod/issues/320

    Subscribe there when you want to know about a fix being committed to PDCursesMod - Bill Gray said that a release is very likely to be done shortly after that fix; so anyone may create a new pdcurses.dll from that afterwards.

     
  • Simon Sobisch

    Simon Sobisch - 2024-06-08

    We're back to the analysis... can someone please modify the minimal testprogram to call "curses_trace" USING 1 once before the first scr_dump, then sharing the test (ideally with doing the exact same things as in the video of the upstream bug report so we don't need to create a new one) and upload the resulting file "trace" to the upstream bug.

     
  • Eugenio Di Lorenzo

    Here is the modifed program
    just inserted

       if wSwitch = 0
          move 1 to wSwitch
          call static 'curses_trace' USING 1
       end-if
    

    before first src_dumpas requested.
    Attached is test file ( it is empy).

    Nothing changes about the program behavior.
    Same errore the display does not work.

           >>SOURCE FORMAT IS FREE
           REPLACE ==:BCOL:== BY ==with BACKGROUND-COLOR==
                   ==:FCOL:== BY ==FOREGROUND-COLOR==.
    IDENTIFICATION DIVISION.
    program-id. TESTERROR.
    
    ENVIRONMENT DIVISION.
    Configuration Section.
     SPECIAL-NAMES.
       CRT STATUS IS wKeyPressed.
    
    DATA DIVISION.
    WORKING-STORAGE SECTION.
      01 Black        constant as 00.
      01 Green        constant as 02.
      01 Cyan         constant as 03.
      01 LightGreen   constant as 10.
      01 LightRed     constant as 12.
      01 Yellow       constant as 14.
      01 White        constant as 15.
    
    01 AnageCodAge pic x(10) value space. *> code AGENT
    01 AnageRagSoc pic x(30) value space. *> NAME
    
    78  K-ENTER       VALUE 0000.
    78  K-ESCAPE      VALUE 2005.
    77  wKeyPressed  PIC  9(04) VALUE 9999.
    77  NumFields    pic  9(02) value 2. *> number of fields on screen
    
    01  wBox-bco     pic 9(02) value cyan.
    01  wBox-fco     pic 9(02) value black.
    01  wSwitch      pic 9     value zero.
    
    77 Pivot    pic 9(02) value 01.
    77 dbc      pic 9(04) value green. *> display backgr.color
    77 dfc      pic 9(04) value white. *> display foregr.color
    77 abc      pic 9(04) value 00.    *> accept  backgr.color
    77 afc      pic 9(04) value 15.    *> accept  backgr.color
    77 wHeader  pic x(80) value space.
    01  wString pic x(31) value space.
    01 ER pic x.
       88 NoErrors value 'N'.
       88   Errors value 'Y'.
    
    *> SAVE/RESTORE SCREEN VARIABLES
    01 wScreenName        PIC X(256) value space.
    01 wiScrOk            BINARY-LONG value zero.
    01 wiScrOk9           PIC 9(9) value zero.
    
    01 Btabmess.
      03 Bmess     pic x(30) occurs 20 value space.
    
    *> **************************************************************
    *>           P R O C E D U R E   D I V I S I O N
    *> **************************************************************
    PROCEDURE DIVISION.
        set environment 'COB_SCREEN_EXCEPTIONS' TO 'Y'.
        set environment 'COB_SCREEN_ESC'        TO 'Y'.
        set environment 'COB_LEGACY'            TO '1'
    
    *> *******************************************************************
    *> D I S P L A Y    S C R E E N
    *> *******************************************************************
       string  ' SAMPLE TEST APPLICATION ' delimited by size into wHeader
       display wHeader at 0101 with  Background-Color green Foreground-Color white highlight
       display ' ESC-<Exit>                                                                     '
                       at 2501 with Background-Color green Foreground-Color white
      display ' Name ..................:' at 0501 with  Background-Color dbc Foreground-Color dfc
      display AnageRagSoc                 at 0527 with  Background-Color abc Foreground-Color afc
      display ' Code...................:' at 0701 with  Background-Color dbc Foreground-Color dfc
      display AnageCodAge                 at 0727 with  Background-Color abc Foreground-Color afc
      continue.
    
    LOOP-ACCEPT.
       go to acc01 acc02 depending on Pivot.
    
    ACC01.
       accept AnageRagSoc at 0527 with  Background-Color abc Foreground-Color afc
              update prompt '_' auto-skip reverse-video
       go EVALUATE-KEY.
    ACC02.
       accept AnageCodAge at 0727 with  Background-Color abc Foreground-Color afc
              update prompt '_' auto-skip reverse-video
       go EVALUATE-KEY.
    
    
    EVALUATE-KEY.
         EVALUATE wKeyPressed
    
            WHEN K-ENTER
                    perform CtrFields thru CtrFieldsEx
                    if Errors
                       continue
                    else
                       *> go to next field on screen
                       compute Pivot = Pivot + 1
                       if Pivot > NumFields move 1 to Pivot end-if
                    end-if
    
            when K-ESCAPE
                go to END-OF-PROGRAM
    
         END-EVALUATE
         GO LOOP-ACCEPT.
    
     END-OF-PROGRAM.
         STOP RUN.
    
    
    
    
    
     *> **********************************************************************
     *>                 C H E C K     F I E L D S   C O N T E N T
     *> **********************************************************************
     CtrFields.
         set NoErrors to true
         go to ctr01 ctr02 depending on Pivot.
     CTR01.
         if AnageRagSoc = space
            set Errors to true
            move lightgreen to wbox-bco move white to wbox-fco
            move '111111111111111111111111111111'  to Bmess(1)
            move '>>>>>>>>>>> ERROR 1 <<<<<<<<<<'  to Bmess(2)
            move '111111111111111111111111111111'  to Bmess(3)
            move '  Please Type a NAME          '  to Bmess(4)
            move '111111111111111111111111111111'  to Bmess(5)
            move '111111111111111111111111111111'  to Bmess(6)
            move '---- enter to return ---------'  to Bmess(7)
            perform DisplayErrorMessage thru DisplayErrorMessageEx
         end-if
         go CtrFieldsEx.
     CTR02.
         if AnageCodAge = space
            set Errors to true
            move lightred to wbox-bco move yellow to wbox-fco
            move '+----------------------------+'  to Bmess(1)
            move '|       >>> ERROR 2 <<<      |'  to Bmess(2)
            move '|2222222222222222222222222222|'  to Bmess(3)
            move '|     Type a CODE !!!!!!!!!!!|'  to Bmess(4)
            move '|2222222222222222222222222222|'  to Bmess(5)
            move '|2222222222222222222222222222|'  to Bmess(6)
            move '+- Enter to return ----------+'  to Bmess(7)
            perform DisplayErrorMessage thru DisplayErrorMessageEx
         end-if
         go CtrFieldsEx.
     CtrFieldsEx. exit.
    
    DisplayErrorMessage.
      *> save the screen before message
       if wSwitch = 0
          move 1 to wSwitch
          call static 'curses_trace' USING 1
       end-if
       move Z'DUMPSCREEN.TMP' to wScreenName
       call  static 'scr_dump' using by reference wScreenName returning wiScrOk end-call
    
      *> *************************************************************************
      *> display the error message in a BOX
    
    
      *> these displays works fine only first time !!!
      *> THEY DOES NOT WORK AFTER A SCREEN RESTORE !!!
      *> THEY DOES NOT WORK AFTER A SCREEN RESTORE !!!
      *> THEY DOES NOT WORK AFTER A SCREEN RESTORE !!!
    
      *> *************************************************************************
       display Bmess(1) at line 04 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
       display Bmess(2) at line 05 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
       display Bmess(3) at line 06 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
       display Bmess(4) at line 07 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
       display Bmess(5) at line 08 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
       display Bmess(6) at line 09 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
       display Bmess(7) at line 10 col 10 :BCOL: wbox-bco :FCOL: wbox-fco
       accept omitted
    
      *> restore the screen after ACCEPT OMITTED (the message is read by the user an duser press ENTER)
      *> the RESTORE WORKS FINE !
       call  static 'scr_restore' using by reference wScreenName returning wiScrOk end-call
       call static 'refresh' returning wiScrOk end-call
       CALL 'CBL_DELETE_FILE' USING wScreenName
       continue.
    DisplayErrorMessageEx. exit.
    
     
    • Simon Sobisch

      Simon Sobisch - 2024-06-08

      The attached trace file is zero bytes :-/

       
  • Chuck H.

    Chuck H. - 2024-06-08

    Simon,

    Bill sent us the attached program which exhibits the problem.

    I added a curses_trace(1); statement to the program and the trace file is still a 0 byte file,

    F:\AA-minGW32-static>cobc -x scrtest2.c -lpdcurses

    F:\AA-minGW32-static>set PDC_TRACE_FLUSH=ON

    F:\AA-minGW32-static>set COB_PRE_LOAD=pdcurses

    F:\AA-minGW32-static>scrtest2
    Stuff

    F:\AA-minGW32-static>cobc -x scrtest2.c -lpdcurses

    F:\AA-minGW32-static>scrtest2

    =========>> So I think that Bill has the information needed to call this resolved. I'm not sure that a curses trace file is needed.

     

    Last edit: Chuck H. 2024-06-08
  • Eugenio Di Lorenzo

    I'm lost.
    It is not clear to me what the situation is now for the resolution of this problem.
    Should we wait for a new bug correction to pdcurses_mod from Bill ?

     
  • Simon Sobisch

    Simon Sobisch - 2024-06-10

    I was wrong about this being an upstream (in this case PDCurses) problem.
    We found out that the issue is in the COBOL program of yours as scr_dump() and scr_restore() operate on curscr while libcob uses stdscr, which are used for different things.
    We therefore don't wait for Bill to push a fix either.

    As a general rule of thumb: calling directly into curses functions from withing a COBOL module is quite likely to generate issues as libcob is not aware of changes "outside" and "assumptions" (like the dump + restore storing/restoring the application's screen) are easily wrong.
    Ideally all calls to curses should go to either extended screenio or GnuCOBOL provided system routines.

    @chaat is working on providing two new system routines:

    CBL_GC_SCR_DUMP and CBL_GC_SCR_RESTORE, both take a PIC X(n) (or alphabetic literal) as an argument to a filename and will under the cover do what the functions you've called do - but for stdscr (including the necessary calls to refresh() before the dump / after the restore). Those are very likely usable as a C source that you can just use on the cobc command line for now and quite fast added to GnuCOBOL as builtin function.

    Later on he will likely check if it is possible for him to implement what we already have in the parser: the DISPLAY UPON WINDOW and friends - so plain DISPLAY, not CALL. The checks are not done there, it may be only available if the underlying curses implementation provides panels (that's outside of X/Open curses, but at least available with ncurses and pdcurses).

    He may also find the option to check MF's (and Realia's) dump/restore functions which take two buffers (one for the text, the other for the attributes) along with position and size.

    Note that in any case you need to save/restore the current cursor position independently (not needed if you do an ACCEPT afterwards as this will position the cursor in any case).

     
    • Eugenio Di Lorenzo

      As a general rule of thumb: calling directly into curses functions from withing a COBOL module is quite likely to generate issues as libcob is not aware of changes "outside" and "assumptions" (like the dump + restore storing/restoring the application's screen) are easily wrong.
      Ideally all calls to curses should go to either extended screenio or GnuCOBOL provided system routines.

      .
      Another function of pdcurses that we often need to use is the following:

      HideCursor.
         move 0 to wInt
         call static "curs_set" using by value wInt end-call.
      HideCursorEx. exit.
      

      It is always necessary when viewing on screen: a menu, some buttons, radio buttons, lists to scroll etc etc. in a TUI.
      According to what you wrote (see above) do we also need to generate a new function CBL_GC_CURS_SET?

       

      Last edit: Eugenio Di Lorenzo 2024-06-13
      • Simon Sobisch

        Simon Sobisch - 2024-06-13

        Do I see it correctly that you want to hide the cursor during ACCEPT OMITTED (I guess it is shown then)?

        If this is the case we may either change that in general or add a runtime configuration for that to disable the cursor in this case.

         
        • Eugenio Di Lorenzo

          ACCEPT OMITTED does not return the necessary return codes to evaluate user actions whether with the keyboard or the mouse.
          So we have to use a normal ACCEPT of a "dummy" field of a single character (see for example the various TUI-TOOLS) and wait for a user action which however is not the typing of a character ora a digit but the typing of a cursor key, a TAB key, or a PGUP / DOWN key or mouse key etc etc ....

          Consequently, it is necessary to be able to hide the cursor both for a normal ACCEPT of a dummy field and obviously also for an ACCEPT OMITTED.

           
  • Eugenio Di Lorenzo

    Okay. Now I understand where we are.

    For the new functions CBL_GC_SCR_DUMP and CBL_GC_SCR_RESTORE I could suggest, if possible, adding an additional parameter with the following values:
    0 = the default, dump and restore are done using a file on disk (how it works now)
    1 = dump and restore occur using a working-storage area. This is to speed up the entire dump and restore process.
    In the example you find at: https://sourceforge.net/p/gnucobol/discussion/contrib/thread/51ca343bb8/ I have implemented (and it works well) drag&drop with the mouse using dump&restore that happens for every single mouse movement.

     
  • Chuck H.

    Chuck H. - 2024-06-12

    Eugenio,

     
    • Eugenio Di Lorenzo

      Thanks for the message and the example.
      However, you didn't write how can I do to have these two new functions available when I compile and when I run the program.

       
      • Eugenio Di Lorenzo

        Sorry Chuck, I received the new compiler suite via DROPBOX.
        Now the program you send in the previous post is working correct using new CBL_GC functions !
        Wonderful job !

        PS.I noticed a slight change in the colors.
        Lightred used to be a bright red but now it's almost pink.
        What could be a reason?

         
        • Simon Sobisch

          Simon Sobisch - 2024-06-13

          I guess you commonly use an MinGW package and Chuck sent an MSYS2-MinGW64 one which uses a different "base"?

           
          • Eugenio Di Lorenzo

            I installed Chuck's GnuCOBOL version in one folder and Arnold's version in another folder.
            Looking at the contents of the folders, how do we understand which one uses MINGW or MSYS2-MinGW64.

             
            • Simon Sobisch

              Simon Sobisch - 2024-06-13

              I installed Chuck's GnuCOBOL version in one folder and Arnold's version in another folder.
              Looking at the contents of the folders, how do we understand which one uses MINGW or MSYS2-MinGW64.

              cobcrun --verbose --info

              should give a good hint, also showing if ther are differences in the
              CHTYPE/WIDEness of curses, which can have effect on the symbols printed;
              when looking on the size the other is the size (MSYS2 is much bigger,
              but also quite newer).

               
              • Eugenio Di Lorenzo

                Attached is the cobcrun --verbose --info output from ARNOLD and CHUCK version.
                Can you tell me why the chuck version doesn't display semigraphic characters correctly ? (see my following post)

                 
                • Simon Sobisch

                  Simon Sobisch - 2024-06-14

                  Ah, that's the reason - you have different PDCurses ports enabled:

                  Arnold: PDCursesMod for Windows
                  Chuck: PDCursesMod for VTx00

                  I guess there is a "pdcurses-wincon.dll" in the "bin" folder - just use it to override "pdcurses.dll".

                  I guess there's an issue with the VT port on Windows console to output the right semigraphic characters. Please double check that before removing by not executing inside "pyqode-console" (which is another layer around the screenio) but ideally with both plain Windows cmd.exe and powershell in Windows Terminal.

                  I'd like to open an issue upstream for that part.

                   
                  • Eugenio Di Lorenzo

                    In Chuck's version of the GnuCOBOL compiler
                    - I deleted pdcurses.dll ,
                    - I renamed pdcurses-wincon.dll to pdcurses.dll
                    recompiled the program (executing inside "pyqode-console" using OpenCOBOLIDE ) and now the semigraphic characters are displayed correctly !

                    PS. What would Chuck have to do for this to work properly?

                     

                    Last edit: Eugenio Di Lorenzo 2024-06-14
<< < 1 2 3 > >> (Page 2 of 3)

Log in to post a comment.