Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations Mike Lewis on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

How would one use multiple keys in a game?

I/O

How would one use multiple keys in a game?

by  Barok  Posted    (Edited  )
this is a question that is asked often, mostly if you're making a game. now, i'm not claiming i'm an expert on this, but i learned a few things.

One of the main ways to detect multikey input is to make an array like this: kbd(127) the kbd array will hold the status of every key on the keyboard. now, you must capture a key. this is done like this:

keypress = inp(96)

this will tell us which keys are depressed. now, when you press a key it will return a value between 1 and 127 to the variable keypress. if you let go of a key, it will return the value of the key you let go plus 127 (or something like that) so therefore to detect a keypress, you must determine if keypress is actually a keypress.

if keypress < 128 then

kbd(keypress) = 1

else
kbd(keypress - 128) = 0

endif

to get rid of the nasty little beeping problem with the pc speakers, insert this code somewhere.

DEF SEG = &H40
POKE &H1A, PEEK(&H1A + 2)


One of the main problems about multiple key input is stickiness: keys will often "stick", meaning that the program continues reading the key as if it is depressed, which is no fun for the user.

There are many multikey programs made in qb, some with a few problems, while some are perfect. some need the num-lock to be turned off, so try turning off your numlock if you want your multikey program to work properly.

I am in no way an expert, just someone trying to help other people. my explanations may suck, but i managed to find many multikey programs on the net. study them!!!

a multikey routine from toshi himself. it tends to stick quite a bit though, but still worth looking through to learn from.

DECLARE SUB numlockoff ()
'=======================================================
'QBMKEY - Pure QB multiple keyboard press handler
'by Toshihiro Horie (270fps on Athlon 950)
'Public domain, use as you wish.
'=======================================================
DEFINT A-Z
DIM kbd(255), keystate(255)
FOR k = 0 TO 255: keystate(k) = -((k AND 128) = 0): NEXT k

'extra precalcs for demo
DIM wrapx(-1 TO 320), wrapy(-1 TO 200)
wrapx(-1) = 319: FOR k = 0 TO 319: wrapx(k) = k: NEXT: wrapx(320) = 0
wrapy(-1) = 199: FOR k = 0 TO 199: wrapy(k) = k: NEXT: wrapy(200) = 0

numlockoff
SCREEN 13
x = 160: y = 100
LOCATE 1, 1: PRINT "QBMKEY - use arrow keys"
frame& = 0: t1! = TIMER
DO
'clear keyboard buffer every other frame
IF frame& AND 1 THEN DEF SEG = &H40: POKE &H1C, PEEK(&H1A): DEF SEG

'Fill multikey state table
'Each key entry indexed by scancode is either a 1 for depressed
'or a 0 for released.
k = INP(&H60): kbd(k AND 127) = keystate(k)

'Look up left and right arrow in key state table to
'determine x and y velocity.
xv = kbd(77) - kbd(75)
yv = kbd(80) - kbd(72)

'update circle position based on effective velocity
x = wrapx(x + xv)
y = wrapy(y + yv)
'draw circle during vsync
WAIT &H3DA, 8
CIRCLE (xold, yold), 4, 0
CIRCLE (x, y), 4, 13
xold = x: yold = y
frame& = frame& + 1
LOOP UNTIL kbd(1) 'escape key exits

'Display demo keyboard polling and graphics update speed
elapsed! = TIMER - t1!
IF elapsed! <> 0 THEN PRINT frame& / elapsed!; "fps"
END

DEFSNG A-Z
SUB numlockoff
'Set NumLock and other shift keys off
'-----------------------------------------------------------
REM This is absolutely necessary, since the demo code assumes
REM a depressed key will always return a 0 in the lower 7 bits.
DEF SEG = &H40: POKE &H17, 0: DEF SEG
END SUB





this one if made by josh stribling. although it sticks sometimes, it still works well.

DECLARE SUB SETKEYS ()
DECLARE SUB CLEARBUF ()
DECLARE SUB GETKEYS ()

CONST TRUE = -1: FALSE = 0

Dim SHARED KB(128), lastk

Dim SHARED KBUP, KBDOWN, KBLEFT, KBRIGHT, KBESC, KBLSHIFT, KBRSHIFT, KBCTRL, KBSPACE, KBALT
SETKEYS

px = 160
py = 100
Do
ox = px
oy = py
GETKEYS 'GET KEYBOARD INPUT

if KB(KBUP) then
py = py - 1
end if

if KB(KBDOWN) then
py = py + 1
end if

if KB(KBLEFT) then
px = px - 1
end if

if KB(KBRIGHT) then
px = px + 1
end if

if (px <> ox) or (py <> oy) then
'move the character
'draw the screen...
end if

'all your other code here...

Loop Until KB(KBESC) 'END ON ESC
End

Sub CLEARBUF()
DEF SEG = &H40
POKE &H1A, PEEK(&H1A + 2)
End Sub

'This Is the Main Sub that does all the work
Sub GETKEYS()
K = INP(96)
If K Then 'KEY CHANGED
If K < 128 Then 'KEY PRESSED
KB(K) = True 'SET THE KEY
lastk = K 'SET THE LAST KEY PRESSED MARKER
Else '....ELSE...LAST KEY RELEASED
If K = 170 Then 'NOTE: (SC) 170 IS RELEASE LAST KEY PRESSED
KB(lastk) = False 'CLEAR LAST KEY PRESSED
Else '...ELSE...OTHER KEY RELEASED
KB(K - 128) = False 'CLEAR RELEASED KEY
End If
End If
End If
CLEARBUF 'CLEAR REGULAR KEY BUFFER KEY BUFFER (NO BEEPS)
End Sub

Sub SETKEYS()
'These are common keys...
KBUP = 72 'Up Arrow
KBDOWN = 80 'Down Arrow
KBLEFT = 75 'Left Arrow
KBRIGHT = 77 'right Arrow
KBESC = 1 'Esc Key
KBLSHIFT = 42 'Left Shift
KBRSHIFT = 54 'Right Shift
KBCTRL = 29 'Ctrl Key
KBSPACE = 57 'Space Bar
KBALT = 56 'Alt Key
End Sub


This is a very nice multikey routine by Eric Carr. It's small and works very well! comes with a nice example.

'===========================================================================
' Subject: SIMULTANEOUS KEY DEMO Date: 03-18-96 (13:12)
' Author: Eric Carr Code: QB, QBasic, PDS
' Origin: FidoNet QUIK_BAS Echo Packet: KEYBOARD.ABC
'===========================================================================
'Ok..Here is the sample keyboard routine I promised..I haven't tested it on any
'other computer excpet mine, but it should work for anyone.. This program lets
'you move a box around by pressing the arrow keys..The acual routine in only 4
'lines as i have marked..This program requires a minimum of a 486sx 25mhz if
'not compiled to run fast enough for all the keys to be updated..I also
'reprogrammed the internal timer from 18.2 to 30, so I could time it to 30 fps.
'To see if a key is being currently pressed, the variable KS is used (IF
'KS(75)=1 THEN button is pressed). Instead of ASCII, this uses scan codes,
'which you can look at in the QB help..Hope you can understand it! :)

DEFINT A-Z: DIM B(300): CLS

N& = 39772 'Reprogram the timer to 30hz
LB& = N& AND &HFF 'instead of 18.2 (for 30 frames
HB& = (N& / 256) AND &HFF 'per second.)
OUT &H43, &H3C: OUT &H40, LB&: OUT &H40, HB&

DIM KS(255), SC(255), DU(255)
FOR E = 0 TO 127 ' Setup key data table KSC()
SC(E) = E: DU(E) = 1
NEXT
FOR E = 128 TO 255
SC(E) = E - 128: DU(E) = 0
NEXT

SCREEN 13: COLOR 4
LOCATE 10, 3: PRINT "Keyboard input routine by Eric Carr"
COLOR 7: PRINT : COLOR 2
PRINT " Use the arrow keys to move the box."
PRINT "Note that you can press two or more keys"
PRINT " at once for diagnal movement!"
PRINT : COLOR 8: PRINT " Press [Esc] to quit"
X = 150: Y = 100: BX = X: BY = Y
DEF SEG = 0
POKE (1132), 0
GET (X, Y)-(X + 15, Y + 15), B
DO 'main loop
T:
I$ = INKEY$ ' So the keyb buffer don't get full \routine/
I = INP(&H60) ' Get keyboard scan code from port 60h \lines/
OUT &H61, INP(&H61) OR &H82: OUT &H20, &H20 ' \!!!/
KS(SC(I)) = DU(I) ' This says what keys are pressed \!/

IF PEEK(1132) < 1 THEN GOTO T 'If not enough time was passed goto T
POKE (1132), 0 'reset timer again
BX = X: BY = Y
IF KS(75) = 1 THEN XC = XC - 2: IF XC < -15 THEN XC = -15
IF KS(77) = 1 THEN XC = XC + 2: IF XC > 15 THEN XC = 15
IF KS(72) = 1 THEN YC = YC - 2: IF YC < -15 THEN YC = -15
IF KS(80) = 1 THEN YC = YC + 2: IF YC > 15 THEN YC = 15
IF XC > 0 THEN XC = XC - 1 ELSE IF XC < 0 THEN XC = XC + 1
IF YC > 0 THEN YC = YC - 1 ELSE IF YC < 0 THEN YC = YC + 1
Y = Y + YC: X = X + XC
IF X > 300 THEN X = 300 ELSE IF X < 0 THEN X = 0
IF Y > 180 THEN Y = 180 ELSE IF Y < 0 THEN Y = 0
IF X <> BX OR Y <> BY THEN
WAIT 936, 8: PUT (BX, BY), B, PSET
GET (X, Y)-(X + 15, Y + 15), B: LINE (X, Y)-(X + 15, Y + 15), 9, BF
END IF
LOOP UNTIL KS(1) = 1 'loop until [Esc] (scan code 1) is pressed

N& = 65535 'Program the timer back to
LB& = N& AND &HFF '18.2hz before exiting!
HB& = (N& / 256) AND &HFF
OUT &H43, &H3C: OUT &H40, LB&: OUT &H40, HB&

OUT &H61, INP(&H61) OR &H82: OUT &H20, &H20
CLEAR 'need to have this if reprograming the timer
END 'I think this ends the program. I'm not quite sure.. :)


This one was made by Joe huber jr., but not really. the keyboard routine was from eric carr's keyboard handler.

'===========================================================================
' Subject: MULTIKEY FUNCTION UPDATE Date: 05-13-97 (14:46)
' Author: Joe Huber, Jr. Code: QB, QBasic, PDS
' Origin: huberjjr@nicom.com Packet: KEYBOARD.ABC
'===========================================================================
DECLARE SUB KEYTEST (LOWERLIMIT!, UPPERLIMIT!)
DECLARE FUNCTION MULTIKEY (KEYNUM)

'MUTIKEY FUNCTION - LETS YOU TRAP SEVERAL KEYS AT ONCE (BETTER THAN INKEY$!!)
'
'USAGE:
' riable=MULTIKEY(KEYNUM)
'WHERE KEYNUM IS THE KEY YOU WANT TO TRAP
' riable = 1 IF KEY IS DEPRESSED, 0 IF IT ISN'T
'
'CALL KEYTEST(lower,upper)
'Use this to find new keycodes
'(unrem below to test)

' CALL KEYTEST(1, 200)

'Gives all keynums between 1 & 200
'If the 0 by the number becomes a 1, then the key with that keycode is
'currently being depressed

'EMAIL ME AT: huberjjr@nicom.com
'
'HAVE FUN!!!

'



CLS

X = 10: Y = 10
XX = X: YY = Y

DO

RIGHT = MULTIKEY(75) ' GET SOME KEYS' STATUSES
LEFT = MULTIKEY(77)
UP = MULTIKEY(72)
DOWN = MULTIKEY(80)
SPACE = MULTIKEY(57)
ESC = MULTIKEY(1)

IF ESC = 1 THEN END 'TEMINATE WHEN ESCAPE IS PRESSED

IF TIMELOOP = 100 THEN 'THIS MOVES YOU AROUND
IF RIGHT = 1 THEN X = X - 1
IF LEFT = 1 THEN X = X + 1 'THE TIMELOOP RIABLE DELAYS
IF UP = 1 THEN Y = Y - 1 'MOVEMENT WITHOUT SLOWING DOWN
IF DOWN = 1 THEN Y = Y + 1 'INPUT (WITHOUT IT YOU WOULD GO
TIMELOOP = 0 'WAAAAYYY TOO FAST)
END IF

IF X >= 80 THEN X = 80 'KEEPS YOU FROM GOING OFF THE SCREEN AND
IF X <= 0 THEN X = 1 'MAKING AN ERROR
IF Y >= 23 THEN Y = 23
IF Y <= 0 THEN Y = 1


IF SPACE = 1 THEN 'CHANGES YOUTR SHAPE WHEN
LOCATE Y, X: PRINT CHR$(94) 'YOU HIT SPACE
ELSE
LOCATE Y, X: PRINT CHR$(127)
END IF

IF XX <> X OR YY <> Y THEN 'UPDATES YOUR POSITION
LOCATE YY, XX: PRINT " "
LOCATE Y, X: PRINT CHR$(127)
END IF


XX = X: YY = Y 'TELLS ME WHERE I WAS LAST

TIMELOOP = TIMELOOP + 1

LOOP 'LOOP (DUH...) :)

'THANX TO Eric Carr FOR FIGURING OUT HOW TO TRAP SEVERAL KEYS AT ONCE
'EVERYTHING ELSE WRITTEN BY ME,

SUB KEYTEST (LOWERLIMIT, UPPERLIMIT)


DO
X = 1
Y = 1

FOR I = LOWERLIMIT TO UPPERLIMIT
TEST = MULTIKEY(I)
LOCATE Y, X
PRINT TEST; I

IF Y < 23 THEN
Y = Y + 1
ELSE
Y = 1
X = X + 7
END IF
NEXT I

LOOP WHILE MULTIKEY(1) = 0
END
END SUB

FUNCTION MULTIKEY (KEYNUM)

STATIC FIRSTIME, KEYS(), SC(), DU()

IF FIRSTIME = 0 THEN
DIM KEYS(255), SC(255), DU(255)
FOR E = 0 TO 127 ' SC(E) = E: DU(E) = 1 '|
NEXT '|-ERIC CARR'S CODE-------------------- FOR E = 128 TO 255 '| |
SC(E) = E - 128: DU(E) = 0 '| |
NEXT '/ |
FIRSTIME = -1 ' |
END IF ' |
' |
I$ = INKEY$ ' So the keyb buffer don't get full \routine/ \ |
I = INP(&H60) ' Get keyboard scan code from port 60h \lines/ |-/
OUT &H61, INP(&H61) OR &H82: OUT &H20, &H20 ' \!!!/ |
KEYS(SC(I)) = DU(I) ' This says what keys are pressed \!/ /

MULTIKEY = KEYS(KEYNUM)


END FUNCTION


Now this one is one of the best keyboard handlers made by my friend sjzero. instead of checking a range, it checks the and operator instead. it's capable of many things. check it out!


'___
' |he Code Post
' `-' Original Submission
' ===============================================================
' CONTRIBUTOR: Sj Zero
' DESCRIPTION: Simple, yet effective multikey routines
' DATE POSTED: Sat Sep 1 09:39:43 2001
' ===============================================================

'Completely altered QB multikey Keyboard routines by SJ Zero


'Completely altered QB multikey Keyboard routines by SJ Zero
'Original routines by John Anderson(multikey.bas)
'Look for it on QB45.COM to see the differences.

'Here is the perfect pure QB keyboard handler. I fixed the flaws of
'John Andersons original design, and added a few tricks of my own,
'such as testing the AND instead of a range.
'The code may be uglier now, but it does a lot more than the original did,
'such as letting the numlock be active, and the Shifts be used.

'note: The keyspressed$ routine is basically useless, so I didn't change it.
'To use this code in a game, just use a like like:
'if Keyflag%(1) then print "Hey ma, a useless example!"

'Also notice the change I made to the inkey% meant to clear the keyboard
'buffer. Now it clears the whole buffer on every frame. This may not be the
'fastest solution, but it is the least likely to mess up on a computer with
'a cheap keyboard bios.

'One final thing, this must be checked rather often compared to other keyboard
'routines. If too much time passes between readings, the keys tend to stay
'active, which is not any fun for the user.

'Enjoy!

DECLARE FUNCTION KEYSPRESSED$ ()

DIM SHARED Keyflag%(0 TO 127)
DO

li% = i%
i% = INP(&H60)
IF i% = 170 OR i% = 54 OR i% = 42 THEN FOR a = 0 TO 127: Keyflag%(a) = 0: NEXT a
IF (i% AND 128) THEN Keyflag%(i% XOR 128) = 0
IF (i% AND 128) = 0 THEN Keyflag%(i%) = -1
WHILE INKEY$ <> "": WEND
IF i% = 1 THEN END

IF i% <> li% THEN
LOCATE 1, 1: PRINT KEYSPRESSED$
END IF
IF ext% THEN EXIT DO
LOOP
END

FUNCTION KEYSPRESSED$
'A string of all the keys curently being pressed
kp$ = ""
FOR k% = 0 TO 127
IF Keyflag%(k%) THEN
kpa$ = LTRIM$(RTRIM$(STR$(k%))): kl% = LEN(kpa$)
kpa$ = "*" + kpa$
kp$ = kp$ + kpa$
END IF
NEXT k%
kp$ = kp$ + "*"
lk% = LEN(kp$)
kp$ = kp$ + (SPACE$((40 - lk%)))
KEYSPRESSED$ = kp$
END FUNCTION



The alternative is to use an assembler handler, but who wants assembly? ;)

I welcome any complaints, as it'd for sure help me learn. at least there are lost of examples! ;D




Register to rate this FAQ  : BAD 1 2 3 4 5 6 7 8 9 10 GOOD
Please Note: 1 is Bad, 10 is Good :-)

Part and Inventory Search

Back
Top