Menu

How do you see if a key has been pressed.

2022-02-27
2022-02-27
  • Michael F Gleason

    I have been looking for the way to tell if a key has been pressed without having to wait on an accept.
    Like when a game is running, it stays active doing stuff instead of waiting for a key.
    I tried CBL_READ_KBD_CHAR, but that was not what I wanted.

    I'm trying to do something if it takes too long for a reply. I found the TIMEOUT option of accept but don't know how to work it. [ TIMEOUT|TIME-OUT AFTER { integer-5 } ] What goes into integer-5 for what length of time?

    Also trying to build in an interupt from the user when the program is busy doing something else.

    I'm looking for something SIMPLE.

     
  • Anonymous

    Anonymous - 2022-02-27

    From the PG 7.8.1.4 : -

    1. The TIMEOUT option will cause the ACCEPT to wait no more than the specified number of
      seconds for input. The wait count may be specified as a positive integer or a numeric data
      item with a positive value.
     
  • Eugenio Di Lorenzo

    Hi Michael ,
    this is the simplest way I use to make the program do things and stop those things when the user presses a key.
    note in this case with accept omitted keys corresponding to letters or numbers are not allowed.
    let me know if this is what you wanted.

           >>SOURCE FORMAT IS FREE
           REPLACE ==:BCOL:== BY ==with BACKGROUND-COLOR==
                   ==:FCOL:== BY ==FOREGROUND-COLOR==.
    ID DIVISION.
    PROGRAM-ID. ED00TEST is initial.
    *> ***********************************************************************************
    
    *> ************************************************************************************
    ENVIRONMENT DIVISION.
    CONFIGURATION SECTION.
    SPECIAL-NAMES.
       CRT STATUS IS ws-KEY.
    
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    77  K-ENTER       PIC 9(04) VALUE 0000.
    77  K-F1          PIC 9(04) VALUE 1001.
    77  K-F2          PIC 9(04) VALUE 1002.
    77  K-F3          PIC 9(04) VALUE 1003.
    77  K-F4          PIC 9(04) VALUE 1004.
    77  K-F5          PIC 9(04) VALUE 1005.
    77  K-F6          PIC 9(04) VALUE 1006.
    77  K-F7          PIC 9(04) VALUE 1007.
    77  K-F8          PIC 9(04) VALUE 1008.
    77  K-F9          PIC 9(04) VALUE 1009.
    77  K-F10         PIC 9(04) VALUE 1010.
    77  K-F11         PIC 9(04) VALUE 1011.
    77  K-F12         PIC 9(04) VALUE 1012.
    
    *>  Exception keys - PIC 9(04) VALUEs 2xxx.
    77  K-PAGEUP      PIC 9(04) VALUE 2001.
    77  K-PAGEDOWN    PIC 9(04) VALUE 2002.
    77  K-UP          PIC 9(04) VALUE 2003.
    77  K-DOWN        PIC 9(04) VALUE 2004.
    77  K-ESCAPE      PIC 9(04) VALUE 2005.
    77  K-PRINT       PIC 9(04) VALUE 2006.
    77  K-TAB         PIC 9(04) VALUE 2007.
    77  K-BACKTAB     PIC 9(04) VALUE 2008.
    77  K-LEFT        PIC 9(04) VALUE 2009.
    77  K-RIGHT       PIC 9(04) VALUE 2010.
    
    *>  The following keys are *only* returned on ACCEPT OMITTED
    77  K-INSERT      PIC 9(04) VALUE 2011.
    77  K-DELETE      PIC 9(04) VALUE 2012.
    77  K-BACKSPACE   PIC 9(04) VALUE 2013.
    77  K-HOME        PIC 9(04) VALUE 2014.
    77  K-END         PIC 9(04) VALUE 2015.
    
    *>  Input validation - VALUEs 8xxx
    77  K-NO-FIELD    PIC 9(04) VALUE 8000. *> NO DATA FROM ACCEPT ex.a timeout is passed (also 8001)
    77  K-TIMEOUT     PIC 9(04) VALUE 8001.
    *>  Other errors - PIC 9(04) VALUEs 9xxx
    77  K-FATAL       PIC 9(04) VALUE 9000.
    77  K-MAXFIELD    PIC 9(04) VALUE 9001.
    
    01  ws-KEY                  PIC 9(0004) VALUE 9999.
    01  wDAY               pic  x(08).
    01  wString            pic  x(60).
    01  Date-Time          pic  x(20).
    01  wTime              pic  x(08).
    
    *> ***************************************************************************************
    *>                         P R O C E D U R E   D I V I S I O N
    *> ***************************************************************************************
    PROCEDURE DIVISION.
    
      *> sets in order to detect the PgUp, PgDn, PrtSc(screen print), Esc keys
      set environment 'COB_SCREEN_EXCEPTIONS' TO 'Y'.
      set environment 'COB_SCREEN_ESC'        TO 'Y'.
      display ' ' at 0101 with blank screen end-display.
      display " ESC to exit " at 010001 :BCOL: 0 :FCOL: 7.
    
    LoopAccept.
    
       *> ***************************************************************************
       *> loop to display the time every 1 sec  
       *> ***************************************************************************
       perform forever
               accept omitted at 2580 with auto timeout 1 end-accept
               *> accept without value at timeout returns "8001" to CRT-STATUS
               if ws-KEY not = K-TIMEOUT exit perform end-if
    
               *> here you can do whatever you need .. in this case we display the time 
                accept wDay  from date YYYYMMDD
                accept wTime from time
                string wDay(1:4)  '.' wDay(5:2)  '.' wDay(7:2) ' '
                       wTime(1:2) ':' wTime(3:2) ':' wTime(5:2) delimited by size into Date-Time
                display Date-Time at 001001 :BCOL: 0 :FCOL: 7 end-display
    
       end-perform
    
       *> a key was pressed. display which key was pressed ?
       evaluate ws-KEY
                when  K-ESCAPE
                      go EndProgram
                when  other
                    string "key pressed is " ws-KEY delimited by size into wString
                        display wString at 003001 :BCOL: 0 :FCOL: 7 end-display
       end-evaluate
    
       go to LoopAccept
       continue.
    
    EndProgram.
      STOP RUN WITH NORMAL STATUS.
    
     
  • Michael F Gleason

    OK. That works for the most part.
    I added this to my MYMENU0001 program and about 5 more lines of code elsewhere and am getting the results I want.
    I accepted into a screen section item and it works.

     

    Last edit: Michael F Gleason 2022-02-27

Anonymous
Anonymous

Add attachments
Cancel