AT keyboard interface driver by Lee Davison
[Back]
; suprdupr AT keyboard driver ver$ 0.1 ; PC AT keyboard interface for 3806 L.Davison, 2001/2/3 ; works with 102 key standard and 105 key Win95/98 keyboards ; The main, externally useable routines are ... ; ResetAT resets the keyboard, flags & LEDs ; KeyLEDs sets the keyboard LEDs, is called by ResetAT ; SendAT sends a byte to the keyboard, returns with the response ; ScanAT scans keyboard and get scancode, returns after timeout if no key ; ScanKey scans keyboard & decodes the key, returns after a timeout if no key ; addresses used ... KEYread = Port7 ; keyboard port, o.c. outputs KEYwrite = PDir7 ; keyboard port, o.c. outputs KDA = 7 ; bit 7 is data KCL = 6 ; bit 6 is clock ; bits 0 to 5 are not used by this TxChar = $52 ; transmit character buffer RxChar = $53 ; receive character buffer LEDBits = $54 ; LED status bits ; bit 0 = scroll lock, 1 = LED on ; bit 1 = num lock, 1 = LED on ; bit 2 = caps lock, 1 = LED on ; bits 3 to 7 are unused but may get trashed KeyBits = $55 ; key status bits ; bit 0 = Left shift, 1 = key down ; bit 1 = Left control, 1 = key down ; bit 2 = Left win, 1 = key down ; bit 3 = Left alt, 1 = key down ; bit 4 = Right shift, 1 = key down ; bit 5 = Right control, 1 = key down ; bit 6 = Right win, 1 = key down ; bit 7 = Right alt, 1 = key down RxTwo = $56 ; two code key flag and temporary counter *= $9000 ;; code for testing only. remove for ROM code ; ; LDM #$FF,PDir6 ; output ; LDM #$00,Port6 ; low ; ; SEB 7,Port6 ; pin high ; CLB 7,Port6 ; pin low ; ; JSR ResetAT ; resets the keyboard, flags & LEDs ;Scan_lp: ; LDM #$00,$58 ; LDM #$20,$59 ;Scan_gg: ; JSR ScanKey ; get and decode key ; BCS Scan_ou ; branch if key ; ; DEC $58 ; heartbeat countdown ; BNE Scan_gg ; loop if not done ; ; DEC $59 ; heartbeat countdown ; BNE Scan_gg ; loop if not done ; ; LDA #03 ; heartbeat character on hyperterm ;Scan_ou: ; JSR OUTPUT ; output byte key ; BRA Scan_lp ; loop forever ; ;; end of demo code ; keyboard decoding routine. the entry point is ScanKey for a non ; halting keyboard poll. if there is a key waiting it will be ; returned in RxChar, else, on return, RxChar will be null. ; key pressed was break [pause] key WasBRK: LDA #$07 ; seven more scancodes to ignore ; ($14,$77,$E1,$F0,$14,$F0,$77) STA RxTwo ; copy code count Ploop: LDX #$00 ; 2000uS delay (8Mhz 3806 1w) JSR ScanAD ; long wait and get second scancode DEC RxTwo ; decrement count BNE Ploop ; loop if not all pause bytes done LDA #$03 ; make break = [CTRL-C] STA RxChar ; save key SEC ; flag key RTS ; process lifted key KeyUp: LDX #$00 ; 2000uS delay (8Mhz 3806 1w) JSR ScanAD ; long wait and get second scancode ORA RxTwo ; OR in table half TAY ; set index from scancode LDA ATtable,Y ; get keycode TAX ; save key for now AND #$F0 ; mask top nibble ; CMP #$C0 ; function key ? ; BEQ FuncKeyUP ; was function key, use this branch for you own ; ; function key up handler (X holds char code) CMP #$90 ; bit hold ? BNE ScanKey ; not bit hold, go get next ; ignores other key releases LDA #$00 ; clear A ; was bit hold key (for up or down key) BitHold: STA RxTwo ; save key up/down flag ($90 for down, $00 for up) TXA ; get key back CMP #$98 ; compare with win_menu key BCS ScanKey ; ignore $98 - $9F ; if here key is either, [L_SHIFT], [L_CTRL], ; [L_WIN], [L_ALT], [R_SHIFT], [RCTRL], [R_WIN] ; or [R_ALT] ; rotates a 1 into a byte of 0s to ; toggle the pressed/lifted key's bit AND #$07 ; mask lower 3 bits TAX ; key # to X LDA #$00 ; clear A SEC ; set -1 bit R_Loop: ROL A ; rotate zero bit through A DEX ; decrement bit count BPL R_Loop ; loop if not that key LDX RxTwo ; get key up flag BEQ ClearBit ; branch if was it key up ORA KeyBits ; set the bit BRA SavBits ; branch always ClearBit: EOR #$FF ; make only one bit = 0 AND KeyBits ; clear the bit SavBits: STA KeyBits ; and save it back BCC ScanKey ; go get next scancode (branch always) ; handle num, caps and scroll lock keys SetUnset: TXA ; get key back EOR LEDBits ; toggle the LED bits STA LEDBits ; save new LED bits JSR KeyLEDs ; set the keyboard LEDs ; get a key from the keyboard, exits with null after timeout ; This is the main entry point for this routine ScanKey: JSR ScanAT ; scan keyboard BCS ProcKey ; if key go do processing RTS ; process key from the keyboard ProcKey: CMP #$E1 ; is it pause (break) BEQ WasBRK ; branch if so CMP #$AA ; is it selftest pass BEQ ScanKey ; branch if was ; this bit should onlt be needed if you use scancode set 3 ; CMP #$FF ; is it error or buffer overflow ; BNE NotOF ; branch if not ; JSR ClearOF ; clear overflow ; BRA ScanKey ; get scancode again ; here we have handled startup, errors and [BREAK] NotOF: LDX #$00 ; clear for single key code CMP #$E0 ; is it $E0 (two byte sequence) BNE NotE0 ; branch if not ; LDX #$00 ; 2000uS delay (8Mhz 3806 1w) X is already cleared JSR ScanAD ; long wait and get second scancode LDX #$80 ; set for double key code NotE0: STX RxTwo ; set/clear two code flag CMP #$F0 ; is it $F0 (key up) BEQ KeyUp ; branch if up ; key has been pressed ORA RxTwo ; OR in table half TAY ; set index from scancode LDA ATtable,Y ; get keycode TAX ; save key for now AND #$F0 ; mask top nibble CMP #$80 ; bit set/unset ? BEQ SetUnset ; was bit set/unset CMP #$90 ; bit hold ? BEQ BitHold ; was so go set hold bit CMP #$C0 ; function key ? ; BEQ FuncKey ; was function key, use this branch for you own ; function key down handler (X holds char code) BEQ ScanKey ; was function key, ignore for now ; key is not function, bit change or lock key BBC 2,LEDBits,N_CapsL ; skip CAPS if not set TXA ; get key back CMP #"a"+$80 ; compare with "a" (shiftable) BCC N_CapsL ; branch if less CMP #"z"+$80+1 ; compare with "z"+1 (shiftable) BCS N_CapsL ; branch if >= ; caps lock on and was alpha, so shift it TYA ; copy index EOR #$80 ; do CAPS LOCK TAY ; back to index N_CapsL: TYA ; copy scancode CMP #$CA ; compare with keypad "/" BEQ Shift ; correct keypad "/" CMP #$69 ; compare scancode with lowest numeric pad code BCC NotNumpad ; branch if < CMP #$7E ; compare scancode with highest numeric pad code+1 BCS NotNumpad ; branch if >= (not numeric) ; gets here if numeric pad code BBS 1,LEDBits,N_Shift ; skip if NUM lock set ; (backwards! like it should be) TXA ; get key back BMI Shift ; branch if was numeric (shiftable) ; key wasn't numeric so now check shift keys status' NotNumpad: LDA KeyBits ; get held bit flags AND #$11 ; mask shift bits BEQ N_Shift ; there was no shift applied ; if here then either shift was held (or both) TXA ; get key back BPL N_Shift ; branch if not shiftable Shift: TYA ; copy index EOR #$80 ; do the shift (or NUM LOCK) TAY ; copy to index N_Shift: LDA ATtable,Y ; get keycode CPY #$80 ; check scancode BCS FixPound ; skip if from second half of table (¬ and £) AND #$7F ; clear shiftable bit (lower half of table only) FixPound: TAX ; save key for now LDA KeyBits ; get held bit flags AND #$22 ; mask control bits BEQ NoCtrl ; was no control key applied TXA ; get key back (again) CMP #$40 ; compare with "@" BCC NoCtrl ; branch if <, not in range CMP #$80 ; compare with [DEL]+1 BCS NoCtrl ; branch if >=, not in range ; [CTRL] key held and in range, mask it AND #$1F ; convert to control key TAX ; copy key to X NoCtrl: TXA ; copy key STX RxChar ; save key SEC ; flag key RTS ; scan the keyboard to see if a key is waiting. returns scancode in A ; and RxChar, or $00 if no key waiting. this is the main entry point. ; if the keyboard response seems flaky when holding a key for auto ; repeat then increase the timeout, it helps. This was the shortest ; I could reliably get away with with all the test keyboards. ; possible bytes (apart from scancodes) are ... ; $00 error or buffer overflow (sets 2 and 3) ; $AA Power On Self Test passed (BAT Completed) ; $EE Echo. see echo command (host commands) ; $FA acknowledge ; $FC Power On Self Test failed ; $FE resend ; $FF error or buffer overflow (set 1 only) ; Rx error, try again RxWasNOK: LDA #$FE ; resend command JSR SendAT ; send A to keyboard ; when exiting this routine the clock is pulled low to hold off transmission. ScanAT: LDX #$20 ; set timeout count (150uS, 8MHz 3806 1w) ScanAD: CLB KCL,KEYwrite ; clock high NOP ; give it a chance to rise NOP ; .. WaitH: BBC KCL,KEYread,WaitD ; test clock line and go do rest if it falls NOP ; extend the delay a little NOP ; .. NOP ; enough delay for 8MHz 3806 1w ; NOP ; .. ; NOP ; .. ; NOP ; .. ; NOP ; .. ; NOP ; .. DEX ; else decrement timeout value BNE WaitH ; go wait some more if time is not up yet CLC ; flag no key ; receive timed out, return with carry clear RxTout: SEB KCL,KEYwrite ; drive clock low (hold off more data) LDA #$00 ; clear A STA RxChar ; save in buffer (no character) RTS ; clock is low for start bit WaitD: JSR GetBit ; get start bit from keyboard BCC RxTout ; branch if was timeout LDX #$08 ; eight data bits to get LDY #$01 ; 1's count to one (odd parity) RecByte: JSR GetBit ; get bit from keyboard (data bit) BCC RxTout ; branch if was timeout ASL A ; data bit to Cb BCC NoRx1 ; branch if bit was zero INY ; else increment 1's count NoRx1: ROR RxChar ; bit into receive byte DEX ; decrement bit count BNE RecByte ; loop if more data JSR GetBit ; get bit from keyboard (parity bit) BCC RxTout ; branch if was timeout ASL A ; data bit to Cb PHP ; on stack for now JSR GetBit ; get bit from keyboard (stop bit) SEB KCL,KEYwrite ; drive clock low (hold off more data) TYA ; get computed parity PLP ; restore received parity ADC #$00 ; add received to computed ROR A ; only interested in bit 0 BCS RxWasNOK ; go try again if not ok ; (rx parity <> computed parity) LDA RxChar ; else copy scancode BEQ ClearOF ; branch if was error or buffer overflow SEC ; flag got byte RTS ; gets a bit from the keyboard, received bit is in b7 of A ; Cb = 1 - ok ; Cb = 0 - timed out ; if there was a timeout X is trashed GetBit: TXA ; save X CLC ; flag no bit LDX #$C0 ; set timeout count (1000uS, 8MHz 3806, 1w) GetBw: BBC KCL,KEYread,GetB ; test clock line and go do rest if it falls DEX ; else decrement timeout value BNE GetBw ; go wait some more if time is not up yet RTS GetB: TAX ; restore X LDA KEYread ; get data SEC ; flag bit WaitR: BBC KCL,KEYread,WaitR ; wait for the clock to rise RTS ; sets the pointers to the decode table, resets the keyboard and sets the ; lock LEDs. also clears the status bits for the decoder. ResetAT: LDM #$00,KeyBits ; clear hold bits LDM #$02,LEDBits ; set LED bits (NUM lock on) LDA #$FF ; reset the keyboard JSR SendAT ; send A to keyboard LDA #$F6 ; restore default settings JSR SendAT ; send A to keyboard JSR KeyLEDs ; set keyboard LEDs ClearOF: LDA #$F4 ; clear the buffer BRA SendAT ; send A to keyboard & return ; set the keyboard LEDs from LEDBits KeyLEDs: LDA #$ED ; next byte is LED bits JSR SendAT ; send A to keyboard LDA LEDBits ; get LED bits AND #$07 ; make sure bits 3 to 7 = 0 ; SendAT sends the special codes to the keyboard, codes are .. ; $ED set the LEDs according to the next byte I send ; bit 0 = scroll lock ; bit 1 = num lock ; bit 2 = caps lock ; bits 3-7 must be 0, 1 = LED on ; $EE echo, keyboard will respond with $EE ; $F0 set scan code set, upon sending the keyboard will ; respond with ACK ($FA) and then wait for a second ; byte. sending $01 to $03 determines the code set ; used, sending $00 will return the code set currently ; in use. ; $F2 device identify. on sending the keyboard will respond with ; ACK ($FA) followed by the keyboard device type numbers $AB, ; $83. A mouse on this port would respond with $00,$00. ; $F3 set typematic repeat rate, upon sending the keyboard ; will respond with ACK ($FA) and then wait for a second ; byte, xDDRRRRR. this byte sets the rate where x is unused, ; DD is 1, 2, 3 or 4 250mS delay times and RRRRR is the repeat ; rate where 00000 = 30cps and 11111 = 2cps. ; $F4 keyboard enable, clears the keyboard buffer and starts ; scanning. ; $F5 keyboard disable, clears the keyboard buffer and stops ; scanning. ; $F6 restore default values upon sending the keyboard will ; respond with ACK ($FA) ; $F7 sets all keys typematic. responds with ACK ($FA) ; $F8 sets all keys make/break. responds with ACK ($FA) ; $F9 sets all keys make. responds with ACK ($FA) ; $FA sets all keys typematic/make/break. responds with ACK ($FA) ; $FB set key type typematic. ; $FC set key type make/break. ; $FD set key type make. ; $FE retransmit the last character please upon sending the ; keyboard will respond by resending the last character ; $FF reset, you stupid keyboard SendAT: STA TxChar ; save A in transmit buffer Send_AT: SEB KDA,KEYwrite ; data low LDX #$08 ; eight bits to send CLB KCL,KEYwrite ; clock high (tell keyboard to receive) LDY #$01 ; 1's count to one (odd parity) SendByte: ROR TxChar ; bit into carry BCC NotOne ; skip increment if zero INY ; else increment 1's count NotOne: JSR SendB ; send bit to keyboard DEX ; decrement bit count BNE SendByte ; loop if not all done ROR TxChar ; last bit back into TxChar TYA ; copy parity count LSR A ; parity bit into carry JSR SendB ; send bit to keyboard SEC ; set stop bit JSR SendB ; send bit to keyboard JSR GetBit ; get bit from keyboard (ack bit) LDX #$80 ; 1000uS delay (8Mhz 3806 1w) JSR WaitH ; long wait and get the response CMP #$FE ; compare with not ok response BEQ Send_AT ; if wrong go do it again RTS ; send bit to keyboard, Cb is the bit to send SendB: BBS KCL,KEYread,SendB ; test clock line and wait for it to fall BCC kwr_0 ; branch if data bit = 0 CLB KDA,KEYwrite ; high out to data BRA WaitB ; skip low write kwr_0: SEB KDA,KEYwrite ; low out to data WaitB: BBC KCL,KEYread,WaitB ; test clock line and wait for it to rise ATtable: ; the first byte of the table is unused so RTS ; this RTS can be the first byte ; AT keyboard decoding table ; [Fn] keys are coded $C1 to $CC but not acted on ; Lock keys are .. ; [SCROLL LOCK] $81 ; [NUM LOCK] $82 ; [CAPS LOCK] $84 ; ... and they change flags internal to the decode routine, ; they also toggle the keyboard LEDs ; other non character keys are .. ; [L_SHIFT] $90 ; [L_CTRL] $91 ; [L_WIN] $92 (toggles bit but otherwise ignored) ; [L_ALT] $93 (toggles bit but otherwise ignored) ; [R_SHIFT] $94 ; [R_CTRL] $95 ; [R_WIN] $96 (toggles bit but otherwise ignored) ; [R_ALT] $97 (toggles bit but otherwise ignored) ; [WIN_MENU] $98 (ignored) ; AT keyboard decoding table first part. ; this mostly holds unshifted key values ; the second character in the comments field is usually the shifted ; character for that key ;ATtable: ; .byte $00 ; first byte replaced by RTS above .byte $C9 ; [F9] .byte $00 ; .byte $C5 ; [F5] .byte $C3 ; [F3] .byte $C1 ; [F1] .byte $C2 ; [F2] .byte $CC ; [F12] .byte $00 ; .byte $CA ; [F10] .byte $C8 ; [F8] .byte $C6 ; [F6] .byte $C4 ; [F4] .byte $09 ; [TAB] .byte "`"+$80 ; ` ¬ .byte $00 ; .byte $00 ; .byte $93 ; [L_ALT] .byte $90 ; [L_SHIFT] .byte $00 ; .byte $91 ; [L_CTRL] .byte "q"+$80 ; q Q .byte "1"+$80 ; 1 ! .byte $00 ; .byte $00 ; .byte $00 ; .byte "z"+$80 ; z Z .byte "s"+$80 ; s S .byte "a"+$80 ; a A .byte "w"+$80 ; w W .byte "2"+$80 ; 2 " .byte $00 ; .byte $00 ; .byte "c"+$80 ; c C .byte "x"+$80 ; x X .byte "d"+$80 ; d D .byte "e"+$80 ; e E .byte "4"+$80 ; 4 $ .byte "3"+$80 ; 3 £ .byte $00 ; .byte $00 ; .byte " " ; [SPACE] .byte "v"+$80 ; v V .byte "f"+$80 ; f F .byte "t"+$80 ; t T .byte "r"+$80 ; r R .byte "5"+$80 ; 5 % .byte $00 ; .byte $00 ; .byte "n"+$80 ; n N .byte "b"+$80 ; b B .byte "h"+$80 ; h H .byte "g"+$80 ; g G .byte "y"+$80 ; y Y .byte "6"+$80 ; 6 ^ .byte $00 ; .byte $00 ; .byte $00 ; .byte "m"+$80 ; m M .byte "j"+$80 ; j J .byte "u"+$80 ; u U .byte "7"+$80 ; 7 & .byte "8"+$80 ; 8 * .byte $00 ; .byte $00 ; .byte ","+$80 ; , < .byte "k"+$80 ; k K .byte "i"+$80 ; i I .byte "o"+$80 ; o O .byte "0"+$80 ; 0 ) .byte "9"+$80 ; 9 ( .byte $00 ; .byte $00 ; .byte "."+$80 ; . > .byte $2F+$80 ; / ? .byte "l"+$80 ; l L .byte ";"+$80 ; ; : .byte "p"+$80 ; p P .byte "-"+$80 ; - _ .byte $00 ; .byte $00 ; .byte $00 ; .byte $27+$80 ; ' @ .byte $00 ; .byte "["+$80 ; [ { .byte "="+$80 ; = + .byte $00 ; .byte $00 ; .byte $84 ; [CAPS LOCK] .byte $94 ; [R_SHIFT] .byte $0D ; [RETURN] .byte "]"+$80 ; ] } .byte $00 ; .byte "#"+$80 ; # ~ .byte $00 ; .byte $00 ; ; keys with bit 7 set, but not the /, are only affected by num lock ; these are the num lock on values .byte $00 ; .byte $5C+$80 ; \ | .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $08 ; [BACKSPACE] .byte $00 ; .byte $00 ; .byte "1"+$80 ; 1 keypad .byte $00 ; .byte "4"+$80 ; 4 keypad .byte "7"+$80 ; 7 keypad .byte $00 ; .byte $00 ; .byte $00 ; .byte "0"+$80 ; 0 keypad .byte "."+$80 ; . keypad .byte "2"+$80 ; 2 keypad .byte "5"+$80 ; 5 keypad .byte "6"+$80 ; 6 keypad .byte "8"+$80 ; 8 keypad .byte $1B ; [ESC] .byte $82 ; [NUM LOCK] .byte $CB ; [F11] .byte "+" ; + keypad .byte "3"+$80 ; 3 keypad .byte "-" ; - keypad .byte "*" ; * keypad .byte "9"+$80 ; 9 keypad .byte $81 ; [SCROLL LOCK] .byte $00 ; ; AT keyboard decoding table second part. ; this mostly holds shifted key values of the first half .byte $00 ; .byte $00 ; .byte $00 ; .byte $C7 ; [F7] .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte "¬" ; [SHIFT] ` .byte $00 ; .byte $00 ; .byte $97 ; [R_ALT] .byte $00 ; .byte $00 ; .byte $95 ; [R_CTRL] .byte "Q" ; [SHIFT] q .byte "!" ; [SHIFT] 1 .byte $00 ; .byte $00 ; .byte $00 ; .byte "Z" ; [SHIFT] z .byte "S" ; [SHIFT] s .byte "A" ; [SHIFT] a .byte "W" ; [SHIFT] w .byte $22 ; [SHIFT] 2 .byte $92 ; [L_WIN] .byte $00 ; .byte "C" ; [SHIFT] c .byte "X" ; [SHIFT] x .byte "D" ; [SHIFT] d .byte "E" ; [SHIFT] e .byte "$" ; [SHIFT] 4 .byte "£" ; [SHIFT] 3 .byte $96 ; [R_WIN] .byte $00 ; .byte $00 ; .byte "V" ; [SHIFT] v .byte "F" ; [SHIFT] f .byte "T" ; [SHIFT] t .byte "R" ; [SHIFT] r .byte "%" ; [SHIFT] 5 .byte $98 ; [WIN_MENU] .byte $00 ; .byte "N" ; [SHIFT] n .byte "B" ; [SHIFT] b .byte "H" ; [SHIFT] h .byte "G" ; [SHIFT] g .byte "Y" ; [SHIFT] y .byte "^" ; [SHIFT] 6 .byte $00 ; .byte $00 ; .byte $00 ; .byte "M" ; [SHIFT] m .byte "J" ; [SHIFT] j .byte "U" ; [SHIFT] u .byte "&" ; [SHIFT] 7 .byte "*" ; [SHIFT] 8 .byte $00 ; .byte $00 ; .byte "<" ; [SHIFT] , .byte "K" ; [SHIFT] k .byte "I" ; [SHIFT] i .byte "O" ; [SHIFT] o .byte ")" ; [SHIFT] 0 .byte "(" ; [SHIFT] 9 .byte $00 ; .byte $00 ; .byte ">" ; [SHIFT] . .byte $3F ; / keypad .byte "L" ; [SHIFT] l .byte ":" ; [SHIFT] ; .byte "P" ; [SHIFT] p .byte "_" ; [SHIFT] - .byte $00 ; .byte $00 ; .byte $00 ; .byte "@" ; [SHIFT] ' .byte $00 ; .byte "{" ; [SHIFT] [ .byte "+" ; [SHIFT] = .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $0D ; [ENTER] keypad .byte "}" ; [SHIFT] ] .byte $00 ; .byte "~" ; [SHIFT] # .byte $00 ; .byte $00 ; ; keys marked "& keypad" are only affected by num lock ; these are the num lock off values .byte $00 ; .byte "|" ; [SHIFT] \ .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; [END] & keypad .byte $00 ; .byte $00 ; [CURSOR_LT] & keypad .byte $00 ; [HOME] & keypad .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; [INSERT] .byte $7F ; [DELETE] & keypad .byte $00 ; [CURSOR_DN] & keypad .byte $00 ; .byte $00 ; [CURSOR_RT] & keypad .byte $00 ; [CURSOR_UP] & keypad .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; .byte $00 ; [PAGE_DN] & keypad .byte $00 ; .byte $00 ; .byte $00 ; [PAGE_UP] & keypad ; .byte $00 ; these two bytes are never accessed so don't ; .byte $00 ; need to be defined in the table |