Joystick, Mouse and Keyboard

This article is heavy on interrupt usage; see this page for some extreme hardcore hand-holding action.

Joystick Support

Built-in functions

According to the online help, QB offers two functions to obtain gamepad status. STRIG() returns the buttons status (2 per controller) and STICK() returns the value of the X and Y axis of the analog stick (1 per controller.) Before it can return any value, STICK() must be called once with a value of 0.

Gamepads with 1 stick and 4 buttons (such as the Gravis Gamepad) are basically two joysticks duct-taped together:

The following code demonstrates how these functions work. Make sure the gamepad is plugged in before launching DOSBox (or turning on your computer,) because they are not plug-and-play as far as I can tell. If no controller is found, installed or connected, the X and Y axis should return 0 (they would return a value around 128 otherwise.)

TYPE gpStruct
  x AS INTEGER ' Analog stick x value
  y AS INTEGER ' Analog stick y value
  b AS INTEGER ' Button status
END TYPE

DIM gp(1) AS gpStruct

CLS
DO
  ' Get sticks of both joysticks
  gp(0).x = STICK(0)
  gp(0).y = STICK(1)
  gp(1).x = STICK(2)
  gp(1).y = STICK(3)

  ' Get buttons of both joysticks
  gp(0).b = -(STRIG(1) + (STRIG(5) * 2))
  gp(1).b = -(STRIG(3) + (STRIG(7) * 2))

  ' Show status of both joysticks
  LOCATE 1, 1
  FOR i% = 0 TO 1
    PRINT "Gamepad #"; i%
    PRINT "Stick ("; gp(i%).x; ", "; gp(i%).y; ")"
    PRINT "Buttons: "; (gp(i%).b AND 1); " "; (gp(i%).b AND 2)
    PRINT
  NEXT i%
LOOP UNTIL LEN(INKEY$)

END

The "button status change" functions may only be useful if you plan to use STRIG() as an event-trapping statement. In this mode, a process running in the background picks up on button presses and jumps to the specified label. This method requires the use of GOSUB (label must be in the main module) and seems to cause some delay. I would recommend you staying away from this method like the haunted house on the hill your friends keep saying it's going to be fun to visit, but deep down you know some kind of poltergeist will get you one by one and you, lone survivor of the blood-thirsty demonic ghoul, will end up with Halloween-induced PTSD for the rest of your life. Anyway, here's an example for your edification... and now that you know how to do it, don't:

ON STRIG(0) GOSUB Apress: STRIG(0) ON
ON STRIG(2) GOSUB Xpress: STRIG(2) ON
ON STRIG(4) GOSUB Bpress: STRIG(4) ON
ON STRIG(6) GOSUB Ypress: STRIG(6) ON

DIM score(3) AS INTEGER

CLS
DO
  LOCATE 1, 1
  PRINT "A"; score(0)
  PRINT "B"; score(1)
  PRINT "X"; score(2)
  PRINT "Y"; score(3)
LOOP UNTIL (INKEY$ = CHR$(27))

STRIG(0) OFF
STRIG(2) OFF
STRIG(4) OFF
STRIG(6) OFF

END

Apress:
  score(0) = score(0) + 1
  RETURN

Bpress:
  score(1) = score(1) + 1
  RETURN

Xpress:
  score(2) = score(2) + 1
  RETURN

Ypress:
  score(3) = score(3) + 1
  RETURN

Using BIOS interrupts

Interrupt &H15 function &H84 can be used to obtain joysticks status. To do so, we set the AH register to &H84 and select a sub-function with the DX register. Sub-function 0 returns the X and Y axis of the analog stick of both joysticks, and sub-function 1 returns the release status of all 4 possible buttons (bit is enabled if the button is released, hence the XORing in the following snippet:)

' $INCLUDE: 'QB.BI'

TYPE gpStruct
  x AS INTEGER ' Analog stick x value
  y AS INTEGER ' Analog stick y value
  b AS INTEGER ' Button status
END TYPE

DIM gp(1) AS gpStruct
DIM regs AS RegTypeX ' registers for interrupt

CLS
DO
  ' Get sticks of both joysticks
  regs.ax = &H8400
  regs.dx = 1
  CALL INTERRUPTX(&H15, regs, regs)
  gp(0).x = regs.ax
  gp(0).y = regs.bx
  gp(1).x = regs.cx
  gp(1).y = regs.dx

  ' Get buttons of both joysticks
  regs.ax = &H8400
  regs.dx = 0
  CALL INTERRUPTX(&H15, regs, regs)
  gp(0).b = 3 XOR ((regs.ax AND &H30) \ 16)
  gp(1).b = 3 XOR ((regs.ax AND &HC0) \ 64)

  ' Show status of both joysticks
  LOCATE 1, 1
  FOR i% = 0 TO 1
    PRINT "Gamepad #"; i%
    PRINT "Stick ("; gp(i%).x; ", "; gp(i%).y; ")"
    PRINT "Buttons: "; (gp(i%).b AND 1); " "; (gp(i%).b AND 2)
    PRINT
  NEXT i%
LOOP UNTIL LEN(INKEY$)

END

"The Way Your Grandpa Did It" (polling port &H0201)

Before there was any BIOS joystick interrupt function available, programmers would read the joystick port at &H0201. It's a much faster alternative since the BIOS reading function would lock interrupts for 1ms at a time... but it's also a lot harder to pull off. The byte returned by the port is always structured as follows:

On the bright side, you can read port &H0201 any time and mask bits 7 to 4 to obtain all 4 buttons status (the bit is enabled if the button is released.) The bad news is that you won't be able to get a proper value for each axis right off the box and you won't even know whether the stick is at rest, moving left or moving right. But first things first, here's a tiny example for catching buttons:

DIM b AS INTEGER

CLS
DO
  b = NOT INP(&H201)
  LOCATE 1, 1
  PRINT "Joy1 button1: "; (b AND 16) > 0
  PRINT "Joy1 button2: "; (b AND 32) > 0
  PRINT "Joy2 button1: "; (b AND 64) > 0
  PRINT "Joy2 button2: "; (b AND 128) > 0
LOOP UNTIL (INKEY$ = CHR$(27))

END

And now for the stick... you have to reset the X and Y axis to 0 and then send one byte of information (anything) to port &H0201 to start a reading session. From there, the joystick will respond with the X and Y status of both sticks for a short amount of time (I think I've read 20 microseconds somewhere, but don't quote me on that - just remember it's very short.) The information is stored in bits 3 to 0 found at port &H0201; for each bit enabled, increase the matching axis value. If all 4 bits are disabled, then you should stop reading the port. In theory (emphasis on "theory",) here's how it goes:

DIM joy1X AS INTEGER, joy1Y AS INTEGER
DIM joy2X AS INTEGER, joy2Y AS INTEGER

CLS
DO
  joy1X = 0: joy1Y = 0
  joy2X = 0: joy2Y = 0

  OUT &H201, 0                  ' Start polling session
  DO
    tmp = INP(&H201)            ' Joystick will return info for
    joy1X = joy1X + (tmp AND 1) ' a short amount of time. The CPU
    joy1Y = joy1Y + (tmp AND 2) ' speed will dictate how many
    joy2X = joy2X + (tmp AND 4) ' reads can be achieved in that
    joy2Y = joy2Y + (tmp AND 8) ' time frame. Slower computers will
  LOOP WHILE (tmp AND &HF)      ' lack resolution.

  LOCATE 1
  PRINT "Joy1: "; joy1X; ", "; joy1Y \ 2
  PRINT "Joy2: "; joy2X \ 4; ", "; joy2Y \ 8
LOOP UNTIL (INKEY$ = CHR$(27))

END

If you run the above code on different computers, in QBASIC 1.1, QuickBASIC 4.5, and compiled, you will notice huge variations in the results. In DOSBox, a 3000 cycles CPU returns results in range 1 to 27. With unlimited cycles, the same program returns values in range 10 to 790! It's expected since an Intel Core i7 will process the few operations in the loop faster than an Intel 80386, thus managing to read the port more often.

To account for that difference, games would ask the user to calibrate the joystick by holding the stick in the upper left and lower right position, then at rest. This would provide min-max values that can be reached according to computer speed. This is a good and easy solution if you know the computer speed won't change, but expect issues if the user decides to crank up CPU cycles at runtime in DOSBox. The other alternative would be timing how long the loop lasts, count the number of reads, and average values from there.

I've seen some code using an array to store the data read from port &H0201 so it can be processed later. This will increase the number of reads on slower computers, but it's not possible to know if the array will be large enough for faster CPUs; a loop limited to the upper bound of the array may crop high values, thus increasing the joystick sensitivity. Alternatively, it is possible to catch the stick of only one controller at a time, reducing the number of operations in the loop and providing a higher resolution (this is a good idea if the game you're working on only uses one paddle anyway.)

One more thing: the above code assumes a joystick is plugged in; if none is available, port &H0201 returns &HFF. It means the loop won't ever exit and the program will crash with a variable overflow. Although it is tempting to only check for the joystick presence once and assume it will remain plugged in for the whole time the program is running, this might not be the case.

Deadzone and joystick arthrosis

If we assume the X axis value can range from 0 (left) to 255 (right,) then a value of 127 should be returned when the stick is at rest. That makes sense. However, in practice that is rarely the case because analog sticks tend to deteriorate after a while and they can no longer access the whole range of values they should, or tend not to get back to their central position. This area where the stick will return a value that is not perfectly central even though it is expected to be, is called the deadzone.

If you're not taking the deadzone into account when coding your program, you may end up with unintended movements. This program will show you how far away the stick is lingering from the center, give you an idea of how much range it can cover, and what would happen if you tried to control a character using unfiltered values (something such as "IF x < 127 THEN moveLeft" would force the character to move left on its own.) If you can find the time to write some kind of program to calibrate the gamepad, you'd probably end up with something like this, which forces X,Y coordinates to be in range -127 to 126 and makes sure values within the deadzone are ignored. The filtering function also provides normalized X,Y coordinates which are extremely helpful for precise control.

Essentially, you need to gauge how large the deadzone is (user input,) convert X,Y coordinates into a vector, subtract the deadzone length from the movement vector, rescale the vector to have the maximum length the thumbstick can reach.

Mouse Support

Using CALL ABSOLUTE (interrupt call in assembly)

I like to start these articles by providing an example of QBASIC's native instructions at work but in this case there's none. QBASIC has built-in instructions for digital pens and joysticks, but not for your run-of-the-mill pointing device. Go figure. Anyway, to enable mouse support, most QB programmers used some assembly code similar to the one found in mouseDriver():

DIM x AS INTEGER, y AS INTEGER
DIM lb AS INTEGER, rb AS INTEGER

CLS
IF (MouseInit%) THEN
  mouseShow
  DO
    mouseStatus lb, rb, x, y
    LOCATE 1, 1: PRINT "(" + LTRIM$(STR$(x)) + "," + STR$(y) + ") - LB:"; lb, "RB:"; rb
  LOOP UNTIL (INKEY$ = CHR$(27))
ELSE
  PRINT "Mouse not found"
END IF

END

' Send AX, BX, CX and DX registers to interrupt &H33
SUB mouseDriver (AX AS INTEGER, BX AS INTEGER, CX AS INTEGER, DX AS INTEGER) STATIC
  DIM aASM(28) AS INTEGER, offset AS INTEGER, sASM AS STRING

  DEF SEG = VARSEG(aASM(0))
  offset = VARPTR(aASM(0))

  IF (LEN(sASM) = 0) THEN
    sASM =        "5589E58B5E0C8B07508B5E0A8B07508B"
    sASM = sASM + "5E088B0F8B5E068B175B581E07CD3353"
    sASM = sASM + "8B5E0C8907588B5E0A89078B5E08890F"
    sASM = sASM + "8B5E0689175DCA080000"

    FOR i% = 0 TO LEN(sASM) \ 2 - 1
      POKE offset + i%, VAL("&H" + MID$(sASM, 1 + i% * 2, 2))
    NEXT i%
  END IF

  CALL ABSOLUTE(AX, BX, CX, DX, offset)

  DEF SEG
END SUB

' Initialize mouse (set AX register to 0, test return value)
FUNCTION mouseInit%
  DIM AX AS INTEGER

  AX = 0
  mouseDriver AX, 0, 0, 0
  MouseInit% = AX
END FUNCTION

' Show mouse (set AX register to 1)
SUB mouseShow
  mouseDriver 1, 0, 0, 0
END SUB

' Get mouse (set AX register to 3, test return values)
SUB mouseStatus (lb AS INTEGER, rb AS INTEGER, x AS INTEGER, y AS INTEGER)
  DIM BX AS INTEGER, CX AS INTEGER, DX AS INTEGER

  mouseDriver 3, BX, CX, DX
  lb = ((BX AND 1) <> 0)
  rb = ((BX AND 2) <> 0)
  x = CX
  y = DX
END SUB

Using interrupts (with CALL INTERRUPTX)

Internally, the assembly code found in mouseDriver() feeds the AX, BX, CX and DX registers to Interrupt &H33. In fact, the whole code can be rewritten to use CALL INTERRUPTX instead to the exact same effect:

'$INCLUDE: 'QB.BI'

DIM SHARED regs AS RegTypeX

DIM x AS INTEGER, y AS INTEGER
DIM lb AS INTEGER, rb AS INTEGER

CLS
IF (mouseInit%) THEN
  mouseShow
  DO
    mouseStatus lb, rb, x, y
    LOCATE 1, 1: PRINT "(" + LTRIM$(STR$(x)) + "," + STR$(y) + ") - LB:"; lb, "RB:"; rb
  LOOP UNTIL (INKEY$ = CHR$(27))
ELSE
  PRINT "Mouse not found"
END IF

END

' Initialize mouse (set AX register to 0, test return value)
FUNCTION mouseInit%
  regs.AX = 0
  CALL INTERRUPTX(&H33, regs, regs)
  mouseInit% = regs.AX
END FUNCTION

' Show mouse (set AX register to 1)
SUB mouseShow
  regs.AX = 1
  CALL INTERRUPTX(&H33, regs, regs)
END SUB

' Get mouse (set AX register to 3, test return values)
SUB mouseStatus (lb AS INTEGER, rb AS INTEGER, x AS INTEGER, y AS INTEGER)
  regs.AX = 3
  CALL INTERRUPTX(&H33, regs, regs)
  lb = ((regs.BX AND 1) <> 0)
  rb = ((regs.BX AND 2) <> 0)
  x = regs.CX
  y = regs.DX
END SUB

Direct handler call (interrupt with CALL ABSOLUTE)

Then, there's another method, which is... peculiar. I've only encountered it once in some demo code. Instead of relying on CALL INTERRUPTX, it searches for Interrupt &H33 vector and runs the handler code via CALL ABSOLUTE. First, PEEK two bytes at 0000:00CE (&H33 * 4 + 2) and 0000:00CC (&H33 * 4) to obtain the segment and offset to the mouse handler and then use CALL ABSOLUTE to pass the AX, BX, CX and DX registers and execute it. The mouseDriver() routine used in the first example could therefore be replaced with:

SUB mouseDriver (AX AS INTEGER, BX AS INTEGER, CX AS INTEGER, DX AS INTEGER) STATIC
  DIM segment AS INTEGER, offset AS INTEGER

  IF (segment = 0) THEN
    DEF SEG = 0
    offset = CVI(CHR$(PEEK(204)) + CHR$(PEEK(205)))
    segment = CVI(CHR$(PEEK(206)) + CHR$(PEEK(207)))
    DEF SEG
    IF (segment = 0) THEN EXIT SUB
  END IF

  DEF SEG = segment
  CALL ABSOLUTE(AX, BX, CX, DX, offset + 2)
  DEF SEG
END SUB

It is a ballsy approach but if you're truly hell-bent on rejecting CALL INTERRUPTX or hand-written assembly, it works. Now, just don't take it too far. Finally, in case you need it, here are the most useful AX values for interrupt &H33, many of which weren't used in the previous code snippets:

Keyboard Support

That one function everyone uses at some point

If you have no other choice, INKEY$ is a semi-reliable solution to keyboard handling. This function reads a character from the keyboard and returns it as a string. The string may be NULL (no length) if no key is pressed, one byte long if the key is a standard ASCII code, or two bytes long for extended characters (the first byte is always 0, while the second byte is a scancode.) Here's how it goes:

DIM kUser AS STRING, kType AS STRING
DIM kShow AS STRING, kCode AS INTEGER

CLS
PRINT "Press any key..."

DO
  kUser = INKEY$

  SELECT CASE LEN(kUser)
    CASE 1
      kType = "Standard ASCII"
      kCode = ASC(kUser)
      SELECT CASE kCode
        CASE 8
          kShow = "Backspace"
        CASE 9
          kShow = "Tab"
        CASE 13
          kShow = "Enter"
        CASE 27
          kShow = "Escape"
        CASE 32
          kShow = "Space"
        CASE ELSE
          kShow = kUser
      END SELECT
    CASE 2
      kType = "Extended Character"
      kCode = ASC(RIGHT$(kUser, 1))
      RESTORE dataScanCode
      FOR i% = 1 TO kCode
        READ kShow
      NEXT i%
  END SELECT

  IF LEN(kUser) THEN
    CLS
    PRINT "Type: " + kType
    PRINT "Code:"; kCode
    PRINT " Key: " + kShow
  END IF
LOOP UNTIL (kShow = "Escape")

END

dataScanCode:
  DATA "Escape", "1", "2", "3", "4", "5", "6", "7", "8", "9"
  DATA "0", "Minus", "Equal", "Backspace", "Tab", "Q", "W", "E", "R", "T"
  DATA "Y", "U", "I", "O", "P", "Left Backet", "Right Bracket", "Enter", "Control", "A"
  DATA "S", "D", "F", "G", "H", "J", "K", "L", "Semicolon", "Quote"
  DATA "Tilde", "Left Shift", "Backslash", "Z", "X", "C", "V", "B", "N", "M"
  DATA "Comma","Period","Slash","Right Shift","Multiply","Alt","Space","Caps Lock","F1","F2"
  DATA "F3", "F4", "F5", "F6", "F7", "F8", "F9", "F10", "Num Lock", "ScrollLock"
  DATA "Home", "Up", "Page Up", "","Left", "", "Right", "Plus", "End", "Down"
  DATA "Page Down", "Insert", "Delete", "", "", "", "", "", "", ""
  DATA "", "", "", "", "", "", "", "", "", ""
  DATA "", "", "", "", "", "", "", "", "", ""
  DATA "", "", "", "", "", "", "", "", "", ""
  DATA "", "", "", "", "", "", "", "", "", ""
  DATA "", "", "F11", "F12"

It's easy to use but clumsy: for starter INKEY$ will not return special keys like Alt, Control and Shift. Second, when a key is held, INKEY$ will fire NULL at seemingly random. Finally, INKEY$ doesn't allow multiple key presses at once which can be a problem for action video games. Thankfully, there IS a better way to handle key presses.

Putting keys in line

Before going further, let's talk a bit (just a tiny little bit) about keyboards. For starter, you should know that there's a circular 32 bytes long buffer stored at 0040:001E, and every key hit is stored there as a word (2 bytes.) Because it is circular, two words (stored at 0040:001A and 0040:001C) are used to keep track of the head and tail respectively. Head points to the next word in the buffer to be read, and Tail points to the word where the next key press must be stored. This buffer is used by INKEY$ to obtain its return values.

This buffer exists so that programs can process keys at their own pace, should they fall behind. On VERY old computers (you can try that all day in DOSBox but it won't work,) when too many keys are pressed at once, it freezes and beeps as it waits for some free cycles to process the buffer and clear some room for more keys. In order to avoid this freeze, you may either call INKEY$ as often as possible to clear the buffer or you may empty the buffer yourself by simply POKEing the head pointer to the tail pointer as so:

CONST kbSeg = &H40
CONST kbHead = &H1A
CONST kbTail = &H1C
CONST kbBuffer = &H1E

CLS
PRINT "Press CTRL+PAUSE or CTRL+SCROLL LOCK to exit"
DEF SEG = kbSeg

DO
  ' Print keyboard buffer
  LOCATE 1, 1
  FOR i% = 0 TO 15
    IF (i% = (PEEK(kbHead) - 30) \ 2) THEN
      COLOR 0, 7
    ELSE
      COLOR 7, 0
    END IF
    PRINT CHR$(PEEK(kbBuffer + (i% * 2)));
  NEXT i%

  ' Clear keyboard buffer
  POKE kbHead, PEEK(kbTail)
LOOP

DEF SEG

END

The code above doesn't contain a single key-trapping procedure such as INPUT or INKEY$, yet the buffer is filled as you press keys on your keyboard. That's because every time a key is pressed or released, somewhere, there's a function silently listening to the keyboard and filling the circular buffer so INKEY$ can read it.

Reading port &H60

Keyboards are not equipped with memory, so they don't hold information. Everything is on the computer side. When a key is pressed or released, the keyboard only sends one byte of information to port &H60 containing the key scan code and its status: key has been released (bit 7 is set) or has been pressed (bit 7 is not set.) I need to stress out the past tense because port &H60 will not update until next key status change and doesn't reflect the current status of any key specifically.

So here's the problem: reading port &H60 in a loop won't be sufficient because it will only catch the last key status change "whenever the program can," while it should be reading port &H60 "whenever there's a change happening." Quickly releasing multiple keys may rapid-fire changes on port &H60, some of which may go unnoticed because the program is busy doing something else:

CONST kbSeg = &H40                    ' Memory segment of keyboard buffer
CONST kbHead = &H1A                   ' Memory offset to keyboard buffer's head
CONST kbTail = &H1C                   ' Memory offset to keyboard buffer's tail

DIM keyStroke(127) AS INTEGER         ' Status of all keys
DIM keyStat AS INTEGER                ' Last key status
DIM keyPressed AS INTEGER             ' Last key status - is pressed
DIM keyScanCode AS INTEGER            ' Last key status - scan code

DO
  keyStat = INP(&H60)                 ' Read the last key status change on port 0x60
  keyPressed = keyStat < 128          ' Value is at least 128 if bit 7 (released) is set
  keyScanCode = keyStat AND &H7F      ' Masking bits 0-6 to obtain scan code
  keyStroke(keyScanCode) = keyPressed ' Store key status for later use

  DEF SEG = kbSeg                     ' Set current memory segment to 0x40
  POKE kbHead, PEEK(kbTail)           ' Apply tail value to head (erase key buffer)
  DEF SEG                             ' Reset to default memory segment

  LOCATE 1
  FOR i% = 0 TO 127                   ' Loop through keyStroke() elements
    PRINT keyStroke(i%);              ' Display status of key with scan code i%
    IF (((i% + 1) AND 15) = 0) THEN   ' If we've displayed 16 scan codes,
      PRINT                           ' Get another line
    END IF
  NEXT i%
LOOP UNTIL keyStroke(1)               ' Loop until ESCAPE (scan code 1) is pressed

END

So the question is "how do I know when port &H60 should be read?" Well, that's what Interrupt Service Register &H09 (ISR 9) is for. This interrupt is called every time port &H60 changes. So what we need to do is create our own routine, get its memory address, and use it to hook our own code to ISR 9's vector. To keep things sane, we'll also have to get the memory address of the default routine so we can restore it when our program terminates.

Hijacking ISR 9's vector

This is where things get tricky because QuickBASIC doesn't have a way to provide the memory address of a routine, which we desperately need. What we could do however, is write the routine in assembly, store it in a buffer, get the memory address of that buffer and hook it to ISR 9; exactly what Milo Sedlacek did with his MultiKey function. His code, divided in 4 parts, contains a header starting at &H0000 (which would jump to the relevant part of the code and store two pointers,) an installer at &H0020 (which sets the new interrupt vector,) an uninstaller at &H0042 (which sets the old interrupt vector,) and the actual interrupt handler at &H0056.

Ideally, we want to do as much as possible in QuickBASIC; the installer and uninstaller sections can easily be replaced with CALL INTERRUPTX: to set an interrupt vector, we call interrupt &H21 and use AH = &H25, AL = ISR number, DS = segment where handler code resides, and DX = offset where handler code resides. To get an interrupt vector (so we can revert back to the default handler after we're done,) we also call interrupt &H21 but use AH = &H35 and AL = ISR number (we obtain the segment and offset where the handler resides in the returned ES and BX registers.)

Now, modifying the keyboard handler at that level means that the default handler is no longer available and thus, INKEY$ and INPUT won't work until the original ISR 9 vector is restored. In fact, not even the DOS prompt will work until the ISR 9 vector is restored, so don't forget to reset it before your program exits... (or crashes.) Here's the final result:

'$INCLUDE:'QB.BI'

DEFINT A-Z

DIM SHARED MULTIKEY(128) AS INTEGER       ' Key strokes, required by multikeyINIT()
DIM SHARED regs as RegTypeX               ' Shared registers for CALL INTERRUPTX

''
'' A variation of Milo Sedlacek's MULTIKEY()
''
SUB multikeyINIT (enable AS INTEGER) STATIC
  DIM segment AS INTEGER, offset AS INTEGER
  DIM aASM(37) AS INTEGER, sASM AS STRING

  ' Ready ASM code
  IF (LEN(sASM) = 0) THEN
    ' ASM code (minus jump header)
    sASM =        "FB9C505351521E560657E460B401A880"
    sASM = sASM + "7404B400247FD0E088C3B700B0002E03"
    sASM = sASM + "1E06002E8E1E040086E08907E4610C82"
    sASM = sASM + "E661247FE661B020E6205F075E1F5A59"
    sASM = sASM + "5B589DCF"

    ' Jump header
    aASM(0) = &H05E9
    aASM(2) = VARSEG(MULTIKEY(0))
    aASM(3) = VARPTR(MULTIKEY(0))

    ' Main code
    DEF SEG = VARSEG(aASM(0))
    offset = VARPTR(aASM(0)) + 8
    FOR i% = 0 TO LEN(sASM) \ 2 - 1
      POKE offset + i%, VAL("&H" + MID$(sASM, 1 + i% * 2, 2))
    NEXT i%
    DEF SEG

    ' Preserve initial vector
    regs.AX = &H3509
    CALL INTERRUPTX(&H21, regs, regs)
    segment = regs.ES
    offset = regs.BX
  END IF

  ' Hook ISR 9 to new code (or restore initial vector)
  regs.AX = &H2509
  IF (enable) THEN
    regs.DS = VARSEG(aASM(0))
    regs.DX = VARPTR(aASM(0))
  ELSE
    regs.DS = segment
    regs.DX = offset
  END IF
  CALL INTERRUPTX(&H21, regs, regs)

  ' Clear array
  FOR i% = 0 TO 127
    MULTIKEY(i%) = 0
  NEXT i%

  ' Clear keyboard buffer and flags
  DEF SEG = 0
  POKE (&H41A), PEEK(&H41C)           ' Clear circular buffer
  POKE &H417, (PEEK(&H417) AND &HF0)  ' Clear SHIFT press
  DEF SEG
END SUB

Keyboard flags

One last option for the road. When writing his Space Invaders port, James Eibisch solved keyboard controls in a clever way: instead of using INKEY$, polling port &H60 or hijacking ISR 9, he read the byte located at address 0000:0417, which contains the keyboard flags. He used Ctrl to move left, Alt to move right and Shift to attack; it's perfect for a simple arcade game since this system doesn't clog the circular key buffer like INKEY$ does and it requires no response time:

DIM b AS INTEGER

CLS
LOCATE 1
PRINT "Right shift down"
PRINT " Left shift down"
PRINT "       Ctrl down"
PRINT "        Alt down"
PRINT "     Scroll lock"
PRINT "        Num lock"
PRINT "       Caps lock"
PRINT "          Insert"

DO
  DEF SEG = 0
  b = PEEK(&H417)
  LOCATE 1
  FOR i% = 0 TO 7
    LOCATE , 18
    IF (b AND 2 ^ i%) THEN PRINT "on " ELSE PRINT "off"
  NEXT i%
LOOP UNTIL (INKEY$ = CHR$(27))
DEF SEG

END

By the way, 0000:0417 can be read and written to. For instance, it is possible to turn Caps Lock on or off by reading the byte, masking all bits but bit 6, enabling or disabling bit 6 (if you want Caps Lock on or off,) and writing the value back.