Menu

#985 Accept Mouse and display anomalies

GC 3.2
open
nobody
5 - default
2024-08-25
2024-08-24
No

This should probably go under the ticket: #588 Accept/display bugs?

I am experiencing some problems with accept and mouse implementation.
I am using esqlOC in the precompile step and I have -lpdcurses in the compile step.

There are two anomalies that are happening.

First the mouse problem seems like the Special Names CURSOR IS WS-CURSOR is only updating on every fourth click and sometimes only on the eighth click? This is happening on left clicks, right clicks and the wheel clicks. The display statements tell me this. This version of the code that I am posting here actually has many more display statements that I have removed here for clarity. So, I know the path being taken on mouse clicks and function key presses are correct. Can anyone tell me why it seems only the fourth or eighth clicks are being recognized?

The other anomaly has to do with the accept statement. For some reason, the accept at 2417 location changes to the at row/col of the last 'display at' statement that executed? As you can see in this code, I had to add 'display A2-AN at 2417' to put the accept location back to where it is supposed to be. Is this normal? Has anyone else experienced this?

000080 CONFIGURATION SECTION.
       SPECIAL-NAMES.
           CONSOLE IS CRT
           CURSOR IS WS-CURSOR
           CRT STATUS IS WS-CRT-STATUS.

000770 WORKING-STORAGE SECTION.
000810 01  SPECIAL-SWITCHES.
           05  WS-CURSOR.
               10  WS-CURSOR-LINE     PIC 99.
               10  WS-CURSOR-COLUMN   PIC 99.
      *
000860     05  WS-CRT-STATUS.
000870         10  WS-FUNCTION        PIC 99.
000880         10  WS-FUNC-NUMBER     PIC 99.
000890*        10  WS-FUNC-NOT-USED   PIC 99 COMP-X.  <-was in Microfocus code commented out



001360 PROCEDURE DIVISION.
       TRAP-MOUSE-EVENTS.
           COMPUTE MOUSE-FLAGS = COB-AUTO-MOUSE-HANDLING
                               + COB-ALLOW-LEFT-DOWN                     <- This didn't work
                               + COB-SCR-LEFT-PRESSED     <-This works
                               + COB-ALLOW-MIDDLE-DOWN                   <- This didn't work
                               + COB-SCR-MID-PRESSED      <-This works
                               + COB-ALLOW-RIGHT-DOWN                    <- This didn't work
                               + COB-SCR-RIGHT-PRESSED.   <-This works




002610 PAR-160.
              MOVE 0 TO A2-US.
002620        ACCEPT A2-AN  AT 2417 WITH UPDATE
                WITH BACKGROUND-COLOR 7 FOREGROUND-COLOR 0 LOWLIGHT
                AUTO
                ON EXCEPTION
                   MOVE WS-FUNCTION TO FUNCTION-KEY *> One Byte
                   EVALUATE FUNCTION-KEY
      * ---FUNCTION KEYS------------------
                     WHEN USER-FN-KEY                         *> VALUE 10.
                      EVALUATE WS-CRT-STATUS
                         WHEN COB-SCR-F1                      *> VALUE  1001.
                           GO TO PAR-300
                         WHEN COB-SCR-F3
                         WHEN FRM
      *   The connection already exists. SQL Warning message  <- I have yet to resolve this
      *  Enter Password:  (10 chars)                          <- This is correct!
                           GO TO PAR-ACTIVATE-MENU
                         WHEN COB-SCR-F15                     *> VALUE  1015.
                           GO TO PAR-999
                         WHEN OTHER
                           GO TO PAR-160
                       END-EVALUATE     

                     WHEN ADIS-FN-KEY                         *>  VALUE 20.
                       EVALUATE WS-CRT-STATUS
      * ---SPECIAL KEYS------------------
                         WHEN COB-SCR-ESC                     *> VALUE  2005.
      *                    GO TO GO-BACK-ONE-LEVEL
                  DISPLAY "ESC:           " at 2504 ERASE EOL
                  DISPLAY A2-AN    at 2417
                           GO TO PAR-160
      * ---MOUSE SUPPORT------------------
                         WHEN COB-SCR-LEFT-PRESSED            *> VALUE  2041.
                         WHEN COB-SCR-MID-PRESSED             *> VALUE  2044. WHEEL
                         WHEN COB-SCR-RIGHT-PRESSED           *> VALUE  2047.
                  DISPLAY "MS-CRT-STAKUS: " at 2501
                  DISPLAY WS-CRT-STATUS     at 2516
                  DISPLAY "WS-CURSOR: " at 2522
                  DISPLAY WS-CURSOR    at 2534
                  DISPLAY "WS-FUNCTION: " at 2539
                  DISPLAY WS-FUNCTION    at 2552
                  DISPLAY A2-AN    at 2417
                           IF MENU-TYPE = 2                   *> TWO COLUMNS
                              EVALUATE WS-CURSOR-LINE
                                WHEN 3 THRU 23
                                  EVALUATE WS-CURSOR-COLUMN
                                    WHEN 01 THRU 80
                                      GO TO PAR-160  *> Place Holder GO somewhere else!!
                                  END-EVALUATE
                              END-EVALUATE
                              GO TO PAR-160
                           ELSE                               *> ONE COLUMN
                              EVALUATE WS-CURSOR-LINE
                                WHEN 3 THRU 23
                                  EVALUATE WS-CURSOR-COLUMN
                                    WHEN 01 THRU 80
                                      GO TO PAR-160  *> Place Holder GO somewhere else!!
                                  END-EVALUATE
                              END-EVALUATE
                              GO TO PAR-160
                           END-IF
                         WHEN OTHER
                           GO TO PAR-160
                     END-EVALUATE
                   END-EVALUATE
              END-ACCEPT
                  DISPLAY "WS-CRT-SCATUS: " at 2501
                  DISPLAY WS-CRT-STATUS     at 2516
                  DISPLAY "WS-CURSOR: " at 2522
                  DISPLAY WS-CURSOR    at 2534
                  DISPLAY "WS-FUNCTION: " at 2539
                  DISPLAY WS-FUNCTION    at 2552
                  DISPLAY A2-AN    at 2417
      * ESC = 20
      * F1  = 10
      * Mouse = 00
              IF A2-US = 99
                  DISPLAY "3  99: " at 2501
                 GO TO GO-BACK-ONE-LEVEL
              END-IF.
              GO TO PAR-160.

       PAR-162.

Related

Bugs: #985

Discussion

  • Vincent (Bryan) Coen

    Not being an expert on the usage of the mouse but you have not specified the copy lib for the statuses for screen/mouse so include in WS :

       01  All-My-Constants    pic 9(4).
             copy "screenio.cpy".
    

    This copy book sits by default in the gnucobol compiler sources in folder copy.

    Now look in that copybook under "*> Exception keys for mouse handling" where you will find the codes available such as :

    78 COB-SCR-MOUSE-MOVE VALUE 2040.
    78 COB-SCR-LEFT-PRESSED VALUE 2041.
    78 COB-SCR-LEFT-RELEASED VALUE 2042.
    78 COB-SCR-LEFT-DBL-CLICK VALUE 2043.
    78 COB-SCR-MID-PRESSED VALUE 2044.
    78 COB-SCR-MID-RELEASED VALUE 2045.
    78 COB-SCR-MID-DBL-CLICK VALUE 2046.
    78 COB-SCR-RIGHT-PRESSED VALUE 2047.
    78 COB-SCR-RIGHT-RELEASED VALUE 2048.
    78 COB-SCR-RIGHT-DBL-CLICK VALUE 2049.
    78 COB-SCR-SHIFT-MOVE VALUE 2050.
    78 COB-SCR-SHIFT-LEFT-PRESSED VALUE 2051.
    78 COB-SCR-SHIFT-LEFT-RELEASED VALUE 2052.
    78 COB-SCR-SHIFT-LEFT-DBL-CLICK VALUE 2053.
    78 COB-SCR-SHIFT-MID-PRESSED VALUE 2054.
    78 COB-SCR-SHIFT-MID-RELEASED VALUE 2055.
    78 COB-SCR-SHIFT-MID-DBL-CLICK VALUE 2056.
    78 COB-SCR-SHIFT-RIGHT-PRESSED VALUE 2057.
    78 COB-SCR-SHIFT-RIGHT-RELEASED VALUE 2058.
    78 COB-SCR-SHIFT-RIGHT-DBL-CLICK VALUE 2059.
    78 COB-SCR-CTRL-MOVE VALUE 2060.
    78 COB-SCR-CTRL-LEFT-PRESSED VALUE 2061.
    78 COB-SCR-CTRL-LEFT-RELEASED VALUE 2062.
    78 COB-SCR-CTRL-LEFT-DBL-CLICK VALUE 2063.
    78 COB-SCR-CTRL-MID-PRESSED VALUE 2064.
    78 COB-SCR-CTRL-MID-RELEASED VALUE 2065.
    78 COB-SCR-CTRL-MID-DBL-CLICK VALUE 2066.
    78 COB-SCR-CTRL-RIGHT-PRESSED VALUE 2067.
    78 COB-SCR-CTRL-RIGHT-RELEASED VALUE 2068.
    78 COB-SCR-CTRL-RIGHT-DBL-CLICK VALUE 2069.
    78 COB-SCR-ALT-MOVE VALUE 2070.
    78 COB-SCR-ALT-LEFT-PRESSED VALUE 2071.
    78 COB-SCR-ALT-LEFT-RELEASED VALUE 2072.
    78 COB-SCR-ALT-LEFT-DBL-CLICK VALUE 2073.
    78 COB-SCR-ALT-MID-PRESSED VALUE 2074.
    78 COB-SCR-ALT-MID-RELEASED VALUE 2075.
    78 COB-SCR-ALT-MID-DBL-CLICK VALUE 2076.
    78 COB-SCR-ALT-RIGHT-PRESSED VALUE 2077.
    78 COB-SCR-ALT-RIGHT-RELEASED VALUE 2078.
    78 COB-SCR-ALT-RIGHT-DBL-CLICK VALUE 2079.
    78 COB-SCR-WHEEL-UP VALUE 2080.
    78 COB-SCR-WHEEL-DOWN VALUE 2081.
    >78 COB-SCR-WHEEL-LEFT VALUE 2082. reserved
    >78 COB-SCR-WHEEL-RIGHT VALUE 2083. reserved
    78 COB-SCR-SHIFT-WHEEL-UP VALUE 2084.
    78 COB-SCR-SHIFT-WHEEL-DOWN VALUE 2085.
    >78 COB-SCR-SHIFT-WHEEL-LEFT VALUE 2086. reserved
    >78 COB-SCR-SHIFT-WHEEL-RIGHT VALUE 2087. reserved
    78 COB-SCR-CTRL-WHEEL-UP VALUE 2088.
    78 COB-SCR-CTRL-WHEEL-DOWN VALUE 2089.
    >78 COB-SCR-CTRL-WHEEL-LEFT VALUE 2090. reserved
    >78 COB-SCR-CTRL-WHEEL-RIGHT VALUE 2091. reserved
    78 COB-SCR-ALT-WHEEL-UP VALUE 2092.
    78 COB-SCR-ALT-WHEEL-DOWN VALUE 2093.
    >78 COB-SCR-ALT-WHEEL-LEFT VALUE 2094. reserved
    >78 COB-SCR-ALT-WHEEL-RIGHT VALUE 2095. reserved

    Change you init. code in PD to match as needed.

     
  • A David Wulkan

    A David Wulkan - 2024-08-25

    I apologize. The program has the screenio.cpy hard coded in the program. For some reason the COPY statement is not working. Probably, I am setting the wrong the environment variable to search for copybooks? I have two variables set and neither is working so I just copied the screenio.cpy contents into my program.

    SET "COB_COPY_DIR=%apphome%\cobcpy"
    SET "COBCPY_DIR=%apphome%\cobcpy"

    1. I had mouse return code assigned to mouse flags. Should only be COB-ALLOW- codes.
    2. I discovered that I get mouse button pressed events if I hold the button down for an inordinate amount of time? Is there a setting to correct this?
     

    Last edit: A David Wulkan 2024-08-25
  • Vincent (Bryan) Coen

    In my .bashrc file I have (among others) :

    export COBCPY=~/cobolsrc/ACAS/copybooks
    export COB_SCREEN_ESC=YES
    export COB_SCREEN_EXCEPTIONS=YES
    export COB_LIBRARY_PATH=~/bin

    export PATH= etc, etc

    export TMPDIR=~/tmp
    export DB_HOME=.

    Note that the export commands do NOT have any quotes but in any event what is var apphome set to prior to these SET commands AND have you verified that they are set correctly such as by doing a set | less and checking.

    I have not seen anything using COB-ALLOW and COB_AUTO in gnucobol presets. You must only be using what is allowed in GnuCobol and where used before migration remove all MF one's not shown as supported.

    Read the Programmers Guide or Reference along with the content of file NEWS that is in the distributions of GC. The manuals you can get from the SF website at :
    https://gnucobol.sourceforge.io/guides.html under heading of GnuCOBOL Documentation.

    Check the usage of ALL WS vars to confirm that you are using them correctly under GnuCobol and check the report for any warnings or errors. This can be produced when compiling by running cobc -x myprog.cbl -T myprog.prn

    Then look at myprog.prn, although running cobc should be showing any warning error messages .

    Response times for status on ACCEPT / DISPLAY should occur immediately although use of Escape can take up to half a second for some reason at least on my system under Mageia v9 X64 Linux using a AMD FX8350 8 core cpu.

     
    • Simon Sobisch

      Simon Sobisch - 2024-08-26

      The interesting question is: do we have a reason to not switch the default values of those two SCREEN configuration options?

      Any thoughts @btiffin?

      Am 25. August 2024 16:42:23 MESZ schrieb "Vincent (Bryan) Coen" vcoen@users.sourceforge.net:

      In my .bashrc file I have (among others) :

      export COBCPY=~/cobolsrc/ACAS/copybooks
      export COB_SCREEN_ESC=YES
      export COB_SCREEN_EXCEPTIONS=YES
      export COB_LIBRARY_PATH=~/bin

      export PATH= etc, etc

      export TMPDIR=~/tmp
      export DB_HOME=.

      Note that the export commands do NOT have any quotes but in any event what is var apphome set to prior to these SET commands AND have you verified that they are set correctly such as by doing a set | less and checking.

      I have not seen anything using COB-ALLOW and COB_AUTO in gnucobol presets. You must only be using what is allowed in GnuCobol and where used before migration remove all MF one's not shown as supported.

      Read the Programmers Guide or Reference along with the content of file NEWS that is in the distributions of GC. The manuals you can get from the SF website at :
      https://gnucobol.sourceforge.io/guides.html under heading of GnuCOBOL Documentation.

      Check the usage of ALL WS vars to confirm that you are using them correctly under GnuCobol and check the report for any warnings or errors. This can be produced when compiling by running cobc -x myprog.cbl -T myprog.prn

      Then look at myprog.prn, although running cobc should be showing any warning error messages .

      Response times for status on ACCEPT / DISPLAY should occur immediately although use of Escape can take up to half a second for some reason at least on my system under Mageia v9 X64 Linux using a AMD FX8350 8 core cpu.


      [bugs:#985] Accept Mouse and display anomalies

      Status: open
      Group: GC 3.2
      Labels: accept mouse
      Created: Sat Aug 24, 2024 04:05 PM UTC by A David Wulkan
      Last Updated: Sun Aug 25, 2024 12:56 AM UTC
      Owner: nobody

      This should probably go under the ticket: #588 Accept/display bugs?

      I am experiencing some problems with accept and mouse implementation.
      I am using esqlOC in the precompile step and I have -lpdcurses in the compile step.

      There are two anomalies that are happening.

      First the mouse problem seems like the Special Names CURSOR IS WS-CURSOR is only updating on every fourth click and sometimes only on the eighth click? This is happening on left clicks, right clicks and the wheel clicks. The display statements tell me this. This version of the code that I am posting here actually has many more display statements that I have removed here for clarity. So, I know the path being taken on mouse clicks and function key presses are correct. Can anyone tell me why it seems only the fourth or eighth clicks are being recognized?

      The other anomaly has to do with the accept statement. For some reason, the accept at 2417 location changes to the at row/col of the last 'display at' statement that executed? As you can see in this code, I had to add 'display A2-AN at 2417' to put the accept location back to where it is supposed to be. Is this normal? Has anyone else experienced this?

      ~~~
      000080 CONFIGURATION SECTION.
      SPECIAL-NAMES.
      CONSOLE IS CRT
      CURSOR IS WS-CURSOR
      CRT STATUS IS WS-CRT-STATUS.

      000770 WORKING-STORAGE SECTION.
      000810 01 SPECIAL-SWITCHES.
      05 WS-CURSOR.
      10 WS-CURSOR-LINE PIC 99.
      10 WS-CURSOR-COLUMN PIC 99.
      *
      000860 05 WS-CRT-STATUS.
      000870 10 WS-FUNCTION PIC 99.
      000880 10 WS-FUNC-NUMBER PIC 99.
      000890* 10 WS-FUNC-NOT-USED PIC 99 COMP-X. <-was in Microfocus code commented out

      001360 PROCEDURE DIVISION.
      TRAP-MOUSE-EVENTS.
      COMPUTE MOUSE-FLAGS = COB-AUTO-MOUSE-HANDLING
      + COB-ALLOW-LEFT-DOWN <- This didn't work
      + COB-SCR-LEFT-PRESSED <-This works
      + COB-ALLOW-MIDDLE-DOWN <- This didn't work
      + COB-SCR-MID-PRESSED <-This works
      + COB-ALLOW-RIGHT-DOWN <- This didn't work
      + COB-SCR-RIGHT-PRESSED. <-This works

      002610 PAR-160.
      MOVE 0 TO A2-US.
      002620 ACCEPT A2-AN AT 2417 WITH UPDATE
      WITH BACKGROUND-COLOR 7 FOREGROUND-COLOR 0 LOWLIGHT
      AUTO
      ON EXCEPTION
      MOVE WS-FUNCTION TO FUNCTION-KEY > One Byte
      EVALUATE FUNCTION-KEY
      * ---FUNCTION KEYS------------------
      WHEN USER-FN-KEY
      > VALUE 10.
      EVALUATE WS-CRT-STATUS
      WHEN COB-SCR-F1 > VALUE 1001.
      GO TO PAR-300
      WHEN COB-SCR-F3
      WHEN FRM
      * The connection already exists. SQL Warning message <- I have yet to resolve this
      * Enter Password: (10 chars) <- This is correct!
      GO TO PAR-ACTIVATE-MENU
      WHEN COB-SCR-F15
      > VALUE 1015.
      GO TO PAR-999
      WHEN OTHER
      GO TO PAR-160
      END-EVALUATE

                      WHEN ADIS-FN-KEY                         *>  VALUE 20.
                        EVALUATE WS-CRT-STATUS
       * ---SPECIAL KEYS------------------
                          WHEN COB-SCR-ESC                     *> VALUE  2005.
       *                    GO TO GO-BACK-ONE-LEVEL
                   DISPLAY "ESC:           " at 2504 ERASE EOL
                   DISPLAY A2-AN    at 2417
                            GO TO PAR-160
       * ---MOUSE SUPPORT------------------
                          WHEN COB-SCR-LEFT-PRESSED            *> VALUE  2041.
                          WHEN COB-SCR-MID-PRESSED             *> VALUE  2044. WHEEL
                          WHEN COB-SCR-RIGHT-PRESSED           *> VALUE  2047.
                   DISPLAY "MS-CRT-STAKUS: " at 2501
                   DISPLAY WS-CRT-STATUS     at 2516
                   DISPLAY "WS-CURSOR: " at 2522
                   DISPLAY WS-CURSOR    at 2534
                   DISPLAY "WS-FUNCTION: " at 2539
                   DISPLAY WS-FUNCTION    at 2552
                   DISPLAY A2-AN    at 2417
                            IF MENU-TYPE = 2                   *> TWO COLUMNS
                               EVALUATE WS-CURSOR-LINE
                                 WHEN 3 THRU 23
                                   EVALUATE WS-CURSOR-COLUMN
                                     WHEN 01 THRU 80
                                       GO TO PAR-160  *> Place Holder GO somewhere else!!
                                   END-EVALUATE
                               END-EVALUATE
                               GO TO PAR-160
                            ELSE                               *> ONE COLUMN
                               EVALUATE WS-CURSOR-LINE
                                 WHEN 3 THRU 23
                                   EVALUATE WS-CURSOR-COLUMN
                                     WHEN 01 THRU 80
                                       GO TO PAR-160  *> Place Holder GO somewhere else!!
                                   END-EVALUATE
                               END-EVALUATE
                               GO TO PAR-160
                            END-IF
                          WHEN OTHER
                            GO TO PAR-160
                      END-EVALUATE
                    END-EVALUATE
               END-ACCEPT
                   DISPLAY "WS-CRT-SCATUS: " at 2501
                   DISPLAY WS-CRT-STATUS     at 2516
                   DISPLAY "WS-CURSOR: " at 2522
                   DISPLAY WS-CURSOR    at 2534
                   DISPLAY "WS-FUNCTION: " at 2539
                   DISPLAY WS-FUNCTION    at 2552
                   DISPLAY A2-AN    at 2417
       * ESC = 20
       * F1  = 10
       * Mouse = 00
               IF A2-US = 99
                   DISPLAY "3  99: " at 2501
                  GO TO GO-BACK-ONE-LEVEL
               END-IF.
               GO TO PAR-160.
      
        PAR-162.
      

      ~~~


      Sent from sourceforge.net because you indicated interest in https://sourceforge.net/p/gnucobol/bugs/985/

      To unsubscribe from further messages, please visit https://sourceforge.net/auth/subscriptions/

       

      Related

      Bugs: #985

    • Simon Sobisch

      Simon Sobisch - 2024-08-26

      Oh and for the preset: you can use the computed value and set/export that to COB_MOUSE_FLAGS.

       
  • A David Wulkan

    A David Wulkan - 2024-08-25

    Thanks for the help guys. Most of this is my own fault being a GNCobol newbie. I worked on the COPY problem and discovered that COPY works if it is in or after column 12.

    The only anomilie I see now is when I have a DISPLAY at XXYY within the Accept statement (ACCEPT - END-ACCEPT), the DISPLAY at XXYY changes the ACCEPT to now ACCEPT AT XXYY. I have to follow the DISPLAY AT XXYY with another DISPLAY at 2417 so the ACCEPT entry box is where the ACCEPT Statement at should be at 2417.

     
  • Vincent (Bryan) Coen

    Please confirm that this bug report can now be closed.

     

Log in to post a comment.