PS/2 tipkovnica

Rasprava o PIC mikrokontrolerima, PIC projekti i drugo vezano za PIC-eve...

Moderators: pedja089, stojke369, [eDo], trax

Post Reply
febo26
Pravo uznapredovao :)
Pravo uznapredovao :)
Posts: 207
Joined: 12-08-2008, 19:58

PS/2 tipkovnica

Post by febo26 »

Da li se neko igrao s PS2 tipkovnicom od kompjutera da je upotrijebi za komunikaciju s PIC procesorom.
Htio bih malo unaprijediti onaj svoj displej s MAX7219 chipom i 8x8 matricnim displejom.Taj projekat radi savrseno , 20 dana bez prekida vrti text i nema problema s njime
Posto se u onom primjeru text nalazi u samom kodu i nemoze se prepraviti bez ponovnog kompajliranja htio bih napraviti tu mogucnost da se text unese pomocu PS2 tipkovnice.

Skinuo sam jedan primjer koda s PICBASIC pro foruma kako komunicirati s tipkovnicom ali za sada je problem sto mogu na LCD displeju prikazati samo jedno slovo koje je pritisnuto.Trenutno nemam ideju kako napraviti string znakova tako da imam cijelu rijec ili recenicu.

Evo primjera za PIC18F452 komunikacija s PS2 tipkovnicom na LCD se prikazuje pritisnuto slovo s tipkovnice

Code: Select all

'****************************************************************
'*  Name    : PS2interface.bas  (PicBasic Pro Compiler)         *
'*  Author  : Michael St. Pierre                                *
'*  Notice  : Copyright (c) 2005 Mytek Controls                 *
'*          : fr*e to Use                                       *
'*  Date    : 11/11/2005                                        *
'*  Version : 1.2  (PIC18F series - 2734 bytes)                 *
'*  Notes   : Interrupt buffered PS2/AT keyboard interface and  *
'*          : keyscan-to-ascii decoder.                         *
'*          :                                                   *
'*          : Revision History:                                 *
'*          : V1.2  Added Pause/Break (ascii $EF) and Print     *
'*          :       Screen (ascii $80) key decode routines.     *
'*          :       Also added example of using alt register    *
'*          :       for doing Ctrl+Alt+Delete reset.            *
'*          :                                                   *
'*          : V1.1  Changed code in KBmain to allow for Shifted *
'*          :       actions from the number keypad.             *
'*          :       If not in NumLock Mode:                     *
'*          :           Shift + keypad key = Number (0,1,2,3..) *
'*          :       If in NumLock Mode:                         *
'*          :           Shift+ keypad key = Non-Shifted         *
'*          :           Navigation Key (i.e.; left arrow = $94) *
'*          :                                                   *
'*          : V1.0  NEW (11/09/05)                              *
'*          :                                                   *
'****************************************************************
DEFINE OSC 20
DEFINE INTLHAND myintL
DEFINE HSER_TXSTA 20h
DEFINE HSER_BAUD 9600


DEFINE LCD_BITS 4      ' LCD broj Bita na liniji 4 ili 8
DEFINE LCD_DREG PORTD' LCD data port
DEFINE LCD_DBIT 0      ' LCD pocetni bit podataka 0 ili 4(od kojeg pina na mikrokontroleru pocinje 0 bit podataka)
DEFINE LCD_RSREG PORTD ' LCD registar select port
DEFINE LCD_RSBIT 4     ' LCD registar select bit (na koji pin na mikrokontroleru je povezan RS bit)
DEFINE LCD_EREG PORTD  ' LCD enable port
DEFINE LCD_EBIT 5      ' LCD enable bit(na koji pin na mikrokontroleru je povezan E bit)
DEFINE LCD_LINES 2     'LCD koristi 2 reda za ispis 2x16 lcd

   TRISA = $00     'Postavi sve pinove porta A kao IZLAZNI  
   TRISB = %00000000  'Postavi sve pinove porta B kao ulazne  
   TRISC = %11111111    'Postavi sve pinove porta C kao IZLAZNI 
   TRISD = %11111111     'Postavi sve pinove porta D kao izlazne 
   TRISE = %111    'Postavi sve pinove porta E kao ulazne
   ADCON1 = 7	   ' PORTA i PORTE su digitalni  ISKLJUCI KOMPARATORE I ANALOGNE ULAZE


'===========================================================================
' Equates
'===========================================================================

'PIC18F series aliases
INT2IP  VAR INTCON3.7   ' INT2 external interrupt priority bit
INTEDG2 VAR INTCON2.4   ' External interrupt-2 edge select bit
INT2IF  VAR INTCON3.1   ' INT2 external interrupt flag
INT2IE  VAR INTCON3.4   ' INT2 external interrupt enable
IPEN    VAR RCON.7      ' Interrupt priority enable

'I/O port assignments
KBCLK   VAR PORTB.2    ' keyboard's I/O clock line (INT2 input)
KBDAT   VAR  PORTB.4    ' keyboard's I/O data line

'Variables for saving state in interrupt handler
wsave	VAR	BYTE bankA system         ' Saves W
ssave	VAR	BYTE bankA system	      ' Saves STATUS
fsave	VAR	WORD bankA system	      ' Saves FSR0


'Keyboard (Low Priority) Interrupt Handler equates
KBbufsize con 10                    ' keyboard buffer size
KBcnt var byte bankA                ' bit counter for keyboard data
KBbuf var byte[KBbufsize] bankA     ' keyboard ring buffer
KBindxI var byte bankA              ' keyboard buffer Input index pointer
KBindxO var byte bankA              ' keyboard buffer Output index pointer
KBcode var byte bankA               ' temporary storage for scan code

'Ketboard Handler equates
LED var byte
scrlock var LED.0       ' If true, scroll lock is on (active)
numlock var LED.1       ' If true, num lock is on (active)
caplock var LED.2       ' If true, caps lock is on (active)
pscrlck var LED.3       ' If true, scroll lock pressed
pnumlck var LED.4       ' If true, numlock pressed 
pcaplck var LED.5       ' If true, caps lock pressed

keystat var byte
Lshift var keystat.0    ' If true, left Shift pressed
Rshift var keystat.1    ' If true, right Shift pressed
L_ctrl var keystat.2    ' If true, left Ctrl pressed
R_ctrl var keystat.3    ' If true, right Ctrl pressed
L_alt var keystat.4     ' If true, left Alt pressed
R_alt var keystat.5     ' If true, right Alt pressed
keydec var keystat.6    ' If true, a key has been decoded

scancode var byte       ' temporary storage for raw keyboard scan code
keycode var byte        ' temporary storage for converted scancode
ascii var byte          ' temporary storage for Ascii equivalent
parity var byte         ' used during getkey for Parity tracking
bitcnt var byte         ' bit counter for putkey routines
shift var bit           ' If true, either shift key is pressed
ctrl var bit            ' If true, either control key is pressed
alt var bit             ' If true, either alt key is pressed

KBrelease var bit       ' flags the release of a standard key
KBextend var bit        ' flags that an extended key has been pressed
KBrelextend var bit     ' flags the release of an extended key
enav var bit            ' flags navigation key as extended version

KB_timeout var byte
TOvalue con $FF         ' loop count in timeout routine
TOcntDLY con 10         ' delay per iteration of loop
init var bit            ' flag to use timeout test alternate return path 

ktable var word         ' translation table index

'variables used by test routine
A var byte
B var byte
temp var byte

Goto start  ' Jump past interrupt routine to program start

'===========================================================================
' Interrupt Handler (Low Priority)
'===========================================================================
' Keyboard "getkey" handler

;                                    KB_getkey
;                            Keyboard to Host Protocol
;                 ___   _   _   _   _   _   _   _   _   _   _   ___
;          CLOCK     |_| |_| |_| |_| |_| |_| |_| |_| |_| |_| |_| 
;
;          DATA    | S | 0 | 1 | 2 | 3 | 4 | 5 | 6 | 7 | P | E |
;
;              S = start bit = 0    P = odd parity   E = stop bit = 1
;                      data valid on falling edge of clock


' The getkey handler responds to a high-to-low transition of the KBCLK line,
' which is the INT2 interrupt connection. Each time this occurs, data bits
' coming in through the KBDAT line (RB4) are temporarily stored in the KBcode
' variable. When a valid stop bit has been received, the data is transferred
' to a ring buffer KBbuf. This information will be later extracted by the
' PicBasic routine mod_keybd.bas and translated into ASCII and ASCIIE code.

'===========================================================================

asm
myintL

; save the state of critical registers
    movwf	wsave            ; Save W
    swapf	STATUS,W         ; Swap STATUS to W
    clrf	STATUS           ; bank 0, regardless of current bank
    movwf	ssave            ; Save swapped STATUS

; save the FSR value because it gets changed below	
    movf    FSR0L, W
    movwf   fsave
    movf    FSR0H, W
    movwf   fsave+1

;===========================================================================
;AT Keyboard Service Routine
	;*** check start bit ***
KB_getkey
    movf    _KBcnt,W        ; check keyboard scan code bit counter
    bnz     KB_getdat       ; branch if not zero (start bit)
    btfsc   _KBDAT          ; test start bit of keyboard data input
    goto    KB_abort        ; no valid start bit, abort
    goto    KB_exit         ; exit

	;*** keyboard scan code acquisition ***
KB_getdat
    movf    _KBcnt,W        ; get keyboard scan code bit counter
    sublw   d'8'            ; w = d'8' - KBDcnt (*)
    bnc     KB_parity       ; branch if negative (carry == 0)
    btfss   _KBDAT          ; Test keyboard data input
    bcf     _KBcode,7       ; clear bit 7 if KBDAT = 0
    btfsc   _KBDAT          ; Test keyboard data input
    bsf     _KBcode,7       ; set bit 7 if KBDAT = 1	
    bz      KB_exit         ; exit on zero (zero flag still valid from (*))
    rrncf   _KBcode,F       ; shift new bits right (do this only 7 times)
    goto    KB_exit         ; exit

	;*** check for parity and stop bit ***
KB_parity
    movf    _KBcnt,W        ; get keyboard scan code counter
    sublw   d'9'            ; w = d'9' - KBDcnt
    bnc     KB_stop         ; branch if negative (carry == 0)
    goto    KB_exit         ; ignore parity bit

	;*** check stop bit ***
KB_stop
    btfss   _KBDAT          ; check if stop bit is valid
    goto    KB_abort        ; if not set, abort

	;*** increment the buffer input index & test for buffer overrun ***
    incf    _KBindxI,W
    subwf   _KBindxO,W      ; subtract indexes to test buffer
    btfsc   STATUS,Z        ; check for zero (KBindxI = KBindxO)
    goto    KB_stall        ; if error stall keyboard

	;*** increment the buffer input index ***
    incf    _KBindxI,F
    movf    _KBindxI,W
    sublw   _KBbufsize-1    ; test if index is outside the ring buffer
    btfss   STATUS,C        ; if it is...
    clrf    _KBindxI        ; reset it

    ; Set FSR0 with the location of the next empty location in buffer
    LFSR    FSR0, _KBbuf    ; set counter base address

    ; Read and store the character from the USART		
    movf	_KBindxI, W	    ; W = offset value for the next empty location
    movff	_KBcode, PLUSW0	; Move the character in KBcode to address (FSR0+W)
                                                    
	;*** stall keyboard ***
	; to prevent the arrival of more data before having finished decoding
KB_stall                    ; hold keyboard (with keyboard clk low):
    bcf     TRISB,2         ; set clkline to output (back to input externally)
    bcf     _KBCLK          ; set keyboard clk line low (stall)
    bcf     _INT2IE         ; disable keyboard IRQ (re-enabled externally)
    goto    KB_term	        ; terminate successfully

KB_abort
    clrf    _KBcode         ; abort / invalid data
KB_term
    clrf    _KBcnt          ; reset keyboard scan code acquisition counter
    goto    KB_end          ; terminate execution of keyboard IRQ
KB_exit
    incf    _KBcnt,F        ; increment acquisition counter
KB_end
    bcf     _INT2IF         ; clear INT2 interrupt flag

;restore registers
    movf	fsave, W
    movwf	FSR0L
    movf	fsave+1, W
    movwf	FSR0H
    swapf	ssave,W         ; Retrieve the swapped STATUS value
    movwf	STATUS          ; Restore it to STATUS
    swapf	wsave,F         ; Swap the stored W value
    swapf	wsave,W         ; Restore it to W
    retfie                  ; Return from the interrupt

endasm


'===========================================================================
' Intitialize keyboard module, check for keyboard presence, and enable IRQ
'===========================================================================
start:
    Clear

'Check for presence of keyboard
startupKB:
    init = 1
    Gosub modstart_KBinit   ' initialize & start keyboard module
    If KB_timeout = TOvalue Then
; *** error code goes here *** (keyboard not present on start-up)
    Endif

    Pause 1000              ' allow time for keyboard to settle prior to
                            ' enabling keyboard interrupts.

'Set-up Interrupts
    INTEDG2 = 0             ' INT2 (KBCLK) interrupt on falling edge
    INT2IP = 0              ' INT2 (KBCLK) set as low priority interrupt
    INT2IF = 0              ' INT2 (KBCLK) clear flag
    INT2IE = 1              ' INT2 (KBCLK) interrupt enabled

    IPEN = 1                ' Enable priority levels on interrupts
    INTCON = %11000000      ' Enable all interrupts!

'===========================================================================
' mainloop - This is the Main Program Loop where multiple tasks can be called
'===========================================================================

mainloop:
    Gosub KBmain  
    
    lcdout $FE,2,"PROBA"              ' Do keyboard decode routine and if
' ----------------------------    a key has been pressed then a jump
'  *** other tasks here ***
' ----------------------------    will be made to "modstart_prnt2scrn".
    Goto mainloop               ' Else, keep looping!


'===========================================================================
' modstart_prnt2scrn -  This is where the decoded keyboard's ascii result
'                       can be processed, printed, ect.
'                       In this case we are running a simple Test Routine
'                       which will output the unaltered ascii character and
'                       its 2 digit hex equivalent through the hardware USART.
'===========================================================================
modstart_prnt2scrn:
    If keydec Then              ' check if decoded key is present
    keydec = 0                  ' If so... reset key decoded flag.

    If alt Then                 ' If Alt key down,
        If ascii = $DF Then     ' and Ctrl+Delete Key pressed,
        'hserout["RESET",$0D,$0A]
        Pause 500
        @   reset               ' do software reset!
        Endif
    Endif

    Gosub dec2hex               ' create 2 digit hex value from ascii,
                                ' and send formatted info out RS232.
                                
    ' serial output example: ascii = A ($41)
                                 
   ' hserout["ascii = ",ascii," ($",A,B,")",$0D,$0A]
    lcdout $FE,2,"ASCII=" ,ASCII
    Endif
    'PAUSE 500
    Return

'convert decimal to 2 digit hex (AB)
dec2hex:
    temp = ascii/16
    Gosub dec2hex_tbl
    A = temp
    temp = ascii//16
    Gosub dec2hex_tbl
    B = temp
    Return
dec2hex_tbl:    
    Lookup temp,["0123456789ABCDEF"],temp
    Return

;===============================================================================
; modstart_keybd - Initialization Entry Point for Keyboard Decoding Module.
;===============================================================================

modstart_KBinit:
    Input KBCLK         ' set-up keyboard clock
    Input KBDAT         ' and keyboard data lines as digital inputs.
    KB_timeout = 0      ' initialize some registers... 
    KBcnt = 0
                        ' No attempt will be made to reset the keyboard as it
                        ' would still be in POST or BAT tests if power were
                        ' applied at the same time as the PIC.
    
;===============================================================================
; rstflag - Resets Status and LED Flags.
;===============================================================================

rstflag:
    keystat = 0
    LED = 0
    Goto LEDshow

;===============================================================================    
; KBmain - Main Entry Point for Keyboard Decoding Module.
;===============================================================================

KBmain:
    If KBindxO = KBindxI Then KBexit    ' if key buffer is empty then exit

' update combined shift/ctrl/alt registers from individual registers
    If Lshift or Rshift Then
    shift = 1
    Else
    Shift = 0
    Endif
    If L_ctrl or R_ctrl Then
    ctrl = 1
    Else
    ctrl = 0
    Endif
    If L_alt or R_alt Then
    alt = 1
    Else
    alt = 0
    Endif

' check to see if this is a key coming up
    If KBrelease Then release               ' release code previously sent
    If KBextend Then extend                 ' extended code previously sent
    If KBrelextend Then rel_ext             ' ext/release code previously sent
        
' go get keyboard byte from ring buffer for interpretation
    Gosub getbuf
    
' check for special codes
    Select Case scancode
    Case $F0            ' key has been released
    KBrelease = 1
    Goto KBexit

    Case $FE            ' key resend requested
    Gosub putkey
    Goto kbmain
    
    Case $FF            ' keyboard error
    Gosub putkey
    Goto rstflag
    
    Case $AA            ' successful completion of BAT
    Goto rstflag
    
    Case $E0            ' Extended key pressed
    KBextend = 1
    Goto KBexit
    
    Case $29            ' Space bar pressed
    ascii = $20
    Goto dec_done

    Case $0D            ' Tab key pressed
    ascii = $09
    Goto dec_done

    Case $66            ' Backspace key pressed
    ascii = $08
    Goto dec_done

    Case $5A            ' Enter key pressed
    ascii = $0D
    Goto dec_done
    
    Case $12            ' Left shift key pressed
    Lshift = 1
    
    Case $59            ' Right shift key pressed
    Rshift = 1
    
    Case $14            ' Left Ctrl key pressed
    L_ctrl = 1
    
    Case $11            ' Left Alt key pressed
    L_alt = 1
    
    Case $58            ' Caps lock key pressed
    If pcaplck = 0 Then caps
    pcaplck = 1
    
    Case $77            ' Numlock key pressed
    If ascii = $EF Then KBexit  'leave if actually Pause/Break key
    If pnumlck = 0 Then nums
    pnumlck = 1
    
    Case $7E            ' Scroll lock key pressed
    If pscrlck = 0 Then scrl
    pscrlck = 1

    Case $E1            ' Pause/Break key pressed
    If ascii = $EF Then ' if we have already done this,
        ascii = 0       ' erase ascii variable,
        Goto KBexit     ' and leave!
    Else
        ascii = $EF     ' Else, decode it,
        Goto dec_done   ' and leave!
    Endif
    End Select
    
' no special codes received, so verify byte as legal
    If scancode > $83 Then KBexit         ' if it exceeds table boundry leave!

' translation of keyboard scan code to our keycode
    Gosub keycode_tbl                     ' Else, translate it to keycode
    If keycode = $80 Then KBexit          ' Check it, and if it is un-
                                          ' decodeable then leave!
    If keycode < $31 Then KBmain1         ' if true, decode for ascii
                                          ' (not navigation or keypad)
' checking for keypad specific entries
    ascii = 0
    If keycode > $3F Then                   ' start of keypad number assignments
        If keycode < $4B Then               ' end of keypad number assignments+1
            If numlock Then                 ' Are we in numlock mode?
                If ctrl = 0 Then            ' Is there a control key down? 
                    If shift = 0 Then       ' If non-shifted numpad key,
                        If keycode = $4A Then   ' If it is the delete key,
                        ascii = "."             ' change it to a period.
                        Else                    ' Else... 
                        keycode = keycode - $20 ' re-index for numbers 0-9
                        Goto KBmain1            ' and go through standard decode.
                        Endif
                    Else                        ' Else if a shifted numpad key,
                        If keycode = $4A Then   ' If it is shift+delete,
                        ascii = $7F             ' make it standard delete
                        Else                    ' Else...
                        ascii = keycode + $50   ' make it standard nav key
                        Endif
                    Endif
                Endif
            Else                            ' If we are not in numlock mode,
                If shift Then               ' and if the shift key is down,
                    If keycode = $4A Then   ' and the delete key is down,
                    ascii = "."             ' change it to a period.
                    Endif
                Endif            
            Endif
        Endif
    Endif
    If ascii != 0 Then dec_done             ' if we have a decoded key use it!
    Goto navkey

KBmain1:
' if this is a ctrl+key situation then decode as such    
    If ctrl Then
    If keycode < $1B Then ascii = keycode   ' ascii control char
    If keycode > $1A Then Gosub ctrl_tbl    ' special char decode
    Goto dec_done
    Endif

' Here is where we sort out the Caps-lock v.s. Shift dilema
    Select Case caplock
    Case 0  ' cap lock OFF
        If shift = 0 Then
            If keycode < $1B Then           ' if alphanumeric...
                ascii = keycode + $60       ' convert to ascii lowercase alpha
            Else                            ' if punctuation...
                Gosub noshift_tbl           ' get non-shifted value
            Endif
        Else
            If keycode < $1B Then           ' if alphanumeric...
                ascii = keycode + $40       ' convert to ascii uppercase alpha
            Else                            ' if punctuation...
                Gosub shift_tbl             ' get shifted value
            Endif
        Endif
    Case 1  ' cap lock ON
        If shift = 0 Then
            If keycode < $1B Then           ' if alphanumeric...
                ascii = keycode + $40       ' convert to ascii uppercase alpha
            Else                            ' if punctuation...
                Gosub noshift_tbl           ' get non-shifted value
            Endif
        Else
            If keycode < $1B Then           ' if alphanumeric...
                ascii = keycode + $60       ' convert to ascii lowercase alpha
            Else                            ' if punctuation...
                Gosub shift_tbl             ' get shifted value
            Endif        
        Endif
    End Select
   
' decoding of key is complete by the time it reaches this point
dec_done:
    keydec = 1                              'key decoded, set flag
    Gosub modstart_prnt2scrn

' Check to see if there are any more bytes left to process in the
' ring buffer. If there is, go get it and process it!
KBexit:
    If KBindxO != KBindxI Then KBmain       ' more bytes left 
    Input KBCLK                             ' release clock line
    INT2IE = 1                              ' re-enable IRQ
    Return

getbuf:
    KBindxO = KBindxO + 1                   ' increment index
    If KBindxO => KBbufsize Then KBindxO = 0
    scancode = KBbuf[KBindxO]               ' fetch next scancode
    Return

;===============================================================================
; scrl -    Toggle Status of Scroll lock and Echo to Keyboard
;===============================================================================

scrl:
    pscrlck = 1            'set flag to prevent routine recall
    LED = (LED ^ %001)     'toggle Scroll lock flag
    Goto LEDshow

;===============================================================================
; nums -    Toggle Status of Num lock and Echo to Keyboard.
;===============================================================================
    
nums:
    pnumlck = 1            'set flag to prevent routine recall
    LED = (LED ^ %010)     'toggle Num lock flag
    Goto LEDshow

;===============================================================================
; caps -    Toggle Status of Caps lock and Echo to Keyboard.
;===============================================================================

caps:
    pcaplck = 1            'set flag to prevent routine recall
    LED = (LED ^ %100)     'toggle Caps lock flag
    Goto LEDshow

;===============================================================================
; extend -  An Extended key has been pressed.
;===============================================================================    

extend:
    KBextend = 0
    Gosub getbuf
    Select Case scancode
    Case $F0        'an extended key has been released
    KBrelextend = 1
    Goto KBexit
    
    Case $11        'Right Alt pressed
    R_alt = 1
    
    Case $14        'Right Ctrl pressed
    R_ctrl = 1
    
    Case $5A        'Enter key on Numpad pressed
    ascii = $0D
    Goto dec_done
    
    Case $4A        '"/" on Numpad pressed
    ascii = "/"
    Goto dec_done

    Case $71        'Delete on Nav keys pressed
    keycode = $4A
    Goto navkey1

    Case $7C        '2nd half of Print Screen key
    ascii = $80
    Goto dec_done
    End Select
    
    If scancode > $83 Then KBexit           'exceeds table boundry
    Gosub keycode_tbl                       'translate to keycode
    If keycode = $80 Then KBexit            'value not defined in table
    If keycode < $31 Then KBexit            'not a navigation key
    enav = 1
navkey:
    If keycode < $4A Then Goto navkey2

navkey1:    
    keycode = keycode - $19                 're-index for table read
    Goto KBmain1

navkey2:
    ascii = keycode + $50                   'normal key
    If shift Then
        If enav or keycode < $40 Then
            ascii = keycode + $70           'shift modified key
        Else
            ascii = keycode - $10           're-index for numbers 0-9
        Endif
        enav = 0
    Endif
    If ctrl Then  ascii = keycode + $90     'ctrl modified key
    Goto dec_done

;===============================================================================
; release - A Key has been Released.
;===============================================================================        

release:
    KBrelease = 0
    gosub getbuf    
    Select Case scancode
    Case $12        'Left shift key released
    Lshift = 0
    
    Case $59        'Right shift key released
    Rshift = 0

    Case $14        'Left Ctrl key released
    L_ctrl = 0
    
    Case $11        'Left Alt key released
    L_alt = 0
    
    Case $58        'Caps lock key released
    pcaplck = 0
    
    Case $7E        'Scroll lock key released
    pscrlck = 0
    
    Case $77        'Num lock key released
    pnumlck = 0
    End Select
   
    Goto KBexit

;===============================================================================
; rel_ext - An Extended Key has been Released.
;===============================================================================    

rel_ext:
    KBrelextend = 0
    Gosub getbuf    
    Select Case scancode
    Case $11        'Right Alt key released
    R_alt = 0
    
    Case $14        'Right Ctrl key released
    R_ctrl = 0
    End Select

    Goto KBexit

;===============================================================================
; LEDshow - Copies the 3 LSB of the LED register to the keyboard for the
;           keyboard's Status LEDs (i.e.; Num Lock, Caps Lock, Scroll Lock).
;===============================================================================

LEDshow:
    scancode = $ED
    Gosub putkey
    scancode = (LED & %111)
    Gosub putkey
    If init = 1 Then
    init = 0
    Return
    Endif
    Goto KBexit
    
;===============================================================================
;                                     _putkey
;                             Host to Keyboard Protocol
;             ___    _   _   _   _   _   _   _   _   _   _   _   _   ___
;       CLOCK    |__| |_| |_| |_| |_| |_| |_| |_| |_| |_| |_| |_| |_|
;
;       DATA       |  S | 0 | 1 | 2 | 3 | 4 | 5 | 6 | 7 | P | E |ACK|
;
;          S = start bit = 0    P = odd parity   E = stop bit = 1   ACK =0
;                      data valid on falling edge of clock
;===============================================================================
putkey:
    parity = 1                  'set-up parity register (odd parity)
    
                                'Let's initiate a com request to the keyboard.
                                
    Low KBCLK                   'pull clock line low.
    Pauseus 35                  'pause 35uSec...
    Low KBDAT                   'pull data line low.
    Pauseus 125                 'pause 125uSec longer...
    Input KBCLK                 'then release the clock line.
    
                                'we have now signaled the keyboard
                                'that we wish to send data to it
                                'so let's do it!

    For bitcnt = 1 To 8         'set for 8 data bits
    Gosub sendbit               'send DATA BIT
    If scancode.0 = 0 Then nextbit  'if not a 1 then continue
    parity = parity + 1         'else, add up total # of 1's
nextbit:
    scancode = scancode >> 1    'shift out next bit
    Next bitcnt
    scancode.0 = parity.0
    Gosub sendbit               'send PARITY BIT
    scancode.0 = 1
    Gosub sendbit               'send STOP BIT
                                'all data bits sent so...
    Input KBDAT                 'release the data line
    Pauseus 100                 'and wait for ACK BIT to pass.
    Return                      'DONE --- Scancode sent to keyboard!!!

    
sendbit:
' time-out counter --- requires keyboard response, else bail out!
    Pauseus TOcntDLY            'determines delay for each count
    KB_timeout = KB_timeout + 1
    If KB_timeout = TOvalue Then
    Return
    Endif

' looking for keyboard clock line to go low, then send data bit to it!
    If KBCLK Then sendbit       'loop until clock line goes low
    KBDAT = scancode.0          'send data bit
    KB_timeout = 0
clkhigh:
    If KBCLK = 0 Then clkhigh   'loop until clock line goes high   
    Return


'===========================================================================
' Keyboard Translation Tables
'===========================================================================

keycode_tbl:
asm
    movlw  Low keycode_tbl
    movff  WREG, _ktable
    movlw  High keycode_tbl
    movff  WREG, _ktable + 1
endasm

    Readcode ktable + scancode, keycode
    Return

asm
keycode_tbl
    DB 0x80,0x39,0x80,0x35,0x33,0x31,0x32,0x3C
    DB 0x80,0x3A,0x38,0x36,0x34,0x80,0x1B,0x80
    DB 0x80,0x80,0x80,0x80,0x80,0x11,0x21,0x80
    DB 0x80,0x80,0x1A,0x13,0x01,0x17,0x22,0x3D
    DB 0x80,0x03,0x18,0x04,0x05,0x24,0x23,0x3E
    DB 0x80,0x80,0x16,0x06,0x14,0x12,0x25,0x3F
    DB 0x80,0x0E,0x02,0x08,0x07,0x19,0x26,0x80
    DB 0x80,0x80,0x0D,0x0A,0x15,0x27,0x28,0x80
    DB 0x80,0x2D,0x0B,0x09,0x0F,0x20,0x29,0x80
    DB 0x80,0x2E,0x2F,0x0C,0x2B,0x10,0x1C,0x80
    DB 0x80,0x80,0x2C,0x80,0x1E,0x1D,0x80,0x80
    DB 0x80,0x80,0x80,0x1F,0x80,0x2A,0x80,0x80
    DB 0x80,0x80,0x80,0x80,0x80,0x80,0x80,0x80
    DB 0x80,0x41,0x80,0x44,0x47,0x80,0x80,0x80
    DB 0x40,0x4A,0x42,0x45,0x46,0x48,0x30,0x80
    DB 0x3B,0x4D,0x43,0x4C,0x4B,0x49,0x80,0x80
    DB 0x80,0x80,0x80,0x37
endasm
        

noshift_tbl:
asm
    movlw  Low noshift_tbl
    movff  WREG, _ktable
    movlw  High noshift_tbl
    movff  WREG, _ktable + 1
endasm

    Goto keytrans

asm
noshift_tbl
    DB "`","-","=","[","]","0","1","2"
    DB "3","4","5","6","7","8","9",0x5C
    DB ";","'",",",".","/",0x1B,0x7F,"*"
    DB "-","+"
endasm


shift_tbl:
asm
    movlw  Low shift_tbl
    movff  WREG, _ktable
    movlw  High shift_tbl
    movff  WREG, _ktable + 1
endasm

    Goto keytrans

asm
shift_tbl
    DB "~","_","+","{","}",")","!","@"
    DB "#","$","%","^","&","*","(","|"
    DB ":",0x22,"<",">","?",0xA0,0xBF,"*"
    DB "-","+"
endasm


ctrl_tbl:
asm
    movlw  Low ctrl_tbl
    movff  WREG, _ktable
    movlw  High ctrl_tbl
    movff  WREG, _ktable + 1
endasm

keytrans:
    Readcode ktable + (keycode - $1B), ascii
    Return

asm
ctrl_tbl
    DB 0x00,0x1F,0xEA,0x1B,0x1D,0xE0,0xE1,0xE2
    DB 0xE3,0xE4,0xE5,0xE6,0xE7,0xE8,0xE9,0x1C
    DB 0xEB,0xEC,0xED,0xEE,0x1E,0xC0,0xDF,"*"
    DB "-","+"
endasm
User avatar
pedja089
Administrator sajta
Administrator sajta
Posts: 7871
Joined: 20-02-2007, 14:50
Location: Beočin -Srbija

Re: PS/2 tipkovnica

Post by pedja089 »

Da ne listam ceo kod...
Tamo gde ti je ispis na displeju ako je bilo LCDOUT $FE,1,KeyboardChar 'KeyboardChar-promenljiva sa dugmetom sa tastature sto dolazi, nemam pojma kako se u kodu zove
Ti ubaci
DisplayString=KeyboardChar 'Dodaj karakter u string
i=i+1
DisplayString=0 'zavrsi string sa nulom
If i=DisplayStringLenght-1 THEN
'ceo niz ispunjen, radi sta os sad sa njim
ENDIF
LCDOUT $fe,1,STR DisplayString
Niz DisplayString definisi kao
DisplayStringLenght CON 16' za lcd 16
DisplayString var byte[DisplayStringLenght]
febo26
Pravo uznapredovao :)
Pravo uznapredovao :)
Posts: 207
Joined: 12-08-2008, 19:58

Re: PS/2 tipkovnica

Post by febo26 »

Hvala Pedja radi ovo sto si sad napisao.
Nije mi jasan ovaj dio cemu on sluzi i bez njega mogu napisati cijelu rijec od 16 slova moze malo objasnjenje

DisplayString=0 'zavrsi string sa nulom-----------kako dodje do nule sto ga smanjuje
If i=DisplayStringLenght-1 THEN
'ceo niz ispunjen, radi sta os sad sa njim
ENDIF
User avatar
pedja089
Administrator sajta
Administrator sajta
Posts: 7871
Joined: 20-02-2007, 14:50
Location: Beočin -Srbija

Re: PS/2 tipkovnica

Post by pedja089 »

i=i+1
DisplayString=0
Zadnji bajt u stringu mora biti 0. Jer STR radi tako da ispisuje sve bajtove iz niza dok ne naidje na bajt koji ima vrednost 0. Kada dodje do bajta koji je 0, prestaje sa ispisom i vraca se nazad, bez obzira sta se nalazi iza.
If i=DisplayStringLenght-1 THEN
'ceo niz ispunjen, radi sta os sad sa njim
ENDIF
Ovo ispitivanje sluzi da znas kada je niz pun. Jer ako definises niz da ima 8 clanova, a i dodje do 9og clana, onda ce krenuti bezveze pisati po RAM-u i zajebati ko zna koje promenljive i registre...
febo26
Pravo uznapredovao :)
Pravo uznapredovao :)
Posts: 207
Joined: 12-08-2008, 19:58

Re: PS/2 tipkovnica

Post by febo26 »

Ok,zahvaljujem,sad su neke stvari malo jasnije

idem dalje testirat javim rezultate
User avatar
pedja089
Administrator sajta
Administrator sajta
Posts: 7871
Joined: 20-02-2007, 14:50
Location: Beočin -Srbija

Re: PS/2 tipkovnica

Post by pedja089 »

Nema na cemu.
febo26
Pravo uznapredovao :)
Pravo uznapredovao :)
Posts: 207
Joined: 12-08-2008, 19:58

Re: PS/2 tipkovnica

Post by febo26 »

Malo mi je zapelo u testiranju a rjesenje bi moglo biti meni pred nosom ali ga ne vidim.

Ovaj kod za PS2 tipkovnicu radi savrseno,dekodira sve tipke s tipkovnice i radi savseno brzo i nema krivih ocitanja s tipkovnice.

Na ovaj nacin prikazujem slova na 4x20 LCD displeju.

Code: Select all

 
 'pedja dopuna
z var byte

DisplayStringLenght con 80
DisplayString var byte[DisplayStringLenght]

Code: Select all

modstart_prnt2scrn:

If keydec Then              ' check if decoded key is present
    keydec = 0                  ' If so... reset key decoded flag.
Endif
       
       
If alt Then                 ' If Alt key down,
        If ascii = $DF Then     ' and Ctrl+Delete Key pressed,
        Pause 500
        @   reset               ' do software reset!
        Endif
Endif


     
DisplayString[z]=ascii ' ASCII je dekodirana vrijednost tipke s tipkovnice.
z=z+1
       
 DisplayString[z]=0 'zavrsi string sa nulom
 
  
LCDOUT $fe,1,STR DisplayString  


' dok dodje do  predzadnjeg slova u nizu onda izvrsi skok na zadatu radnju                        
If  z = DisplayStringLenght -1 THEN 
    z=0
    LCDOUT $fe,1 
    
endif
     
Return
znaci na ovaj nacin mogu napisati 78 znakova na svom LCD i kad dodje na 79 znak on brise kompletni sadrzaj LCD-a i krece opet iz pocetka.

Kako da tih 78 znakova koje sam napisao pomocu tipkovnice skopiram u neku varijablu ili string (tu neznam kaj trebam napraviti) da bi to mogao prikazati na plivajucem displeju .
Na ovaj nacin prikazujem text na displeju

Code: Select all

 
  main:                  
     For r=0 to 255
     Char=0
     LOOKUP r,["    Temperatura:"], Char
     if char=0 then exit'Automatski detektuj kraj teksta, tako da ne moras svaki put brojati koliko tekst ima slova
     GOSUB SendChar
     Next r
znaci umjesto rijeci Temperatura bi trebalo ubaciti onih 78 znakova za ispis.
User avatar
pedja089
Administrator sajta
Administrator sajta
Posts: 7871
Joined: 20-02-2007, 14:50
Location: Beočin -Srbija

Re: PS/2 tipkovnica

Post by pedja089 »

Nisam pazljivo citao, ali ako sam dobro skontao ovo hoces

Code: Select all

  main:                 
     For r=0 to 255
     Char=DisplayString[r] 'uzimaj iz niza umesto iz lookup
     if char=0 then exit'Automatski detektuj kraj teksta, tako da ne moras svaki put brojati koliko tekst ima slova
     GOSUB SendChar
     Next r
febo26
Pravo uznapredovao :)
Pravo uznapredovao :)
Posts: 207
Joined: 12-08-2008, 19:58

Re: PS/2 tipkovnica

Post by febo26 »

To je to Pedja,radi bez greske.Imam jos jedan problem zezam se s njime vec par sati ali nema napretka.

Za prikaz teksta s tipkovnice koristim LCD displej 40x2 i to je sveukupno 80 znakova na njemu i to radi savrseno, problem nastaje kada je text duzi od 80 znakova onda se 81 znak ispisuje na prvom mjestu na lcd-u skroz gore lijevo i tako dalje prepisavam postojeci text slovo preko slova.
Htio bih napraviti to da ako je text duzi od 80 znakova da se LCD obrise i da mogu normalno dalje nastaviti pisati po njemu i da taj cjelokupni text prikazem s ovim tvojim rjesenjem.

Code: Select all

 main:                 
     For r=0 to 255
     Char=DisplayString[r] 'uzimaj iz niza umesto iz lookup
     if char=0 then exit'Automatski detektuj kraj teksta, tako da ne moras svaki put brojati koliko tekst ima slova
     GOSUB SendChar
     Next r
User avatar
pedja089
Administrator sajta
Administrator sajta
Posts: 7871
Joined: 20-02-2007, 14:50
Location: Beočin -Srbija

Re: PS/2 tipkovnica

Post by pedja089 »

Nisam siguran sta tacno hoces izvesti, da li da samo obrises displej, ili da obrises niz, ali kako god, ne vidim gde je problem...
Ne znam koji LCD koristis, ali recimo da uradis samo LCDOUT $FE,1, kada ispunis ceo niz.
Za brisanje niza, samo stavi 0 posle tog teksta, i ni jedna od onih rutina sto smo radili nece ici dalje od znaka 0, a nece ni ici STR komanda u pbp.
febo26
Pravo uznapredovao :)
Pravo uznapredovao :)
Posts: 207
Joined: 12-08-2008, 19:58

Re: PS/2 tipkovnica

Post by febo26 »

Ako je niz duzi od 80 znakova zelim da mi se LCD obrise a da niz ostane u komad i da nakon 80 znaka pisem po cistom displeju.

ako imam ovo

Code: Select all

     
DisplayString[z]=ascii ' ASCII je dekodirana vrijednost tipke s tipkovnice.
z=z+1
       
 DisplayString[z]=0 'zavrsi string sa nulom
 
 
LCDOUT $fe,1,STR DisplayString 


' dok dodje do  predzadnjeg slova u nizu onda izvrsi skok na zadatu radnju                       
If  z = DisplayStringLenght -1 THEN
    z=0
    LCDOUT $fe,1
   
endif
     
Return
i ako tu dodam red:

if z=80 then
lcdout $fe,1
lcdout $fe,STR DisplayString

onda on obrise cijeli LCD ali nakon 81 znaka opet prikaze prvih 80 znakova i dalje prepisavam znakove jedne preko drugih.Jedino na napravim vise nizova po 80 znakova i da ih onda svaki posebno prikazem na LCD displeju i da svaki niz od 80 znakova posebno saljem na MAX7219.
User avatar
pedja089
Administrator sajta
Administrator sajta
Posts: 7871
Joined: 20-02-2007, 14:50
Location: Beočin -Srbija

Re: PS/2 tipkovnica

Post by pedja089 »

Niz ne sme da ti bude duzi od DisplayStringLenght, to i jeste cela poenta te konstante i ispitivanja do kojeg karaktera je stiglo... Moras napraviti duzi niz. ako hoces vise karaktera u nizu

A prikaz na LCD mozes resiti na vise nacina.
Recimo, tamo gde ti stize sa tastature promenljiva, stavi

Code: Select all

If z//80=0 then LCDOUT $FE,1 ' Obrisi displej i vrati kursor na pocetak ako si stigao do 80tog znaka, 160 itd...
LCDOUT Ascii 'Turi slovo na displej
Drugi nacin je da na displeju prikazujes samo zadnjih 80 karaktera

Code: Select all

IF z<80 then
    LCDOUT $FE,$80, STR DisplayString
ELSE
    LCDOUT $FE,$80 'vrati kursor na prvo polje bez brisanja lcd-a da izbegnes treperenje
    FOR i = Z-80 TO Z
        LCDOUT DisplayString[i]  
    NEXT i 
ENDIF
Probaj i jedno i drugo pa vidi sta ces dalje...
febo26
Pravo uznapredovao :)
Pravo uznapredovao :)
Posts: 207
Joined: 12-08-2008, 19:58

Re: PS/2 tipkovnica

Post by febo26 »

Code: Select all

   
 If z//80=0 then LCDOUT $FE,1 ' Obrisi displej i vrati kursor na pocetak ako si stigao do 80tog znaka, 160 itd...
    LCDOUT Ascii 'Turi slovo na displej
Ovo radi super kad dodje do 80 znaka displej se lijepo obrise i izpocetka pisem znakove i to je to.

Code: Select all

IF z<80 then
    LCDOUT $FE,$80, STR DisplayString
ELSE
    LCDOUT $FE,$80 'vrati kursor na prvo polje bez brisanja lcd-a da izbegnes treperenje
    FOR i = Z-80 TO Z
        LCDOUT DisplayString[i] 
    NEXT i
ENDIF
ovo radi dobro ali je problem kad dodje do 80 znaka ne obrise displej vec krene prepisavati novi text preko staroga ali od zadnje pozicije prema prvoj.

Nisam uspio niti jedan primjer iskoristi ali su mi pomogli u rjesavanju problema koji sam rjesio a ni sam neznam kako.Uglavnom stvar radi.

Probat cu objasniti koji je bio problem.Uredjaj je zamisljen da ima dva displeja,jedan LCD na kojem se vrsi ispis poruke koja se treba prikazivati na vecem displeju izradjenom s led diodama i MAX7219 chipom.Poruka se ispise pomocu PS2 tipkovnice na LCD displeju i nakon pritiska na tipku ENTER poruka se salje na LED displej.

-----------------------------------------------------------------------------------------------------------------------------
Tipku koju pritisnem na tipkovnici moram prikazati na LCDu i njenu vrijednost spremiti u niz za kasniji prikaz na MATRiX displeju.Ako se text pise u cijelosti bez greske u pisanju onda stvar funkcionira idealno i prikaz je savrsen na LCDu i na matrix displeju.

Ako dodje do greske u pisanju i kada zelim obrisati pogresno slovo u tom momentu su se razisli prikazi na LCD displeju i na MATRIX displeju Pritiskom na tipku BACKSPACE slovo se u nizu obrisalo ali je zato na LCD-u prikaz otisao za jedno slovu unaprijed s prikazom hijeroglifa. Nakon rjesavanja tog problem stvar radi perfektno.


ovo je na pocetku programa:

Code: Select all

  'pedja dopuna
z var byte
DisplayStringLenght con 80
DisplayString var byte[DisplayStringLenght]
DisplayStringLenght2 con 80
DISPLAYSTRING2 VAR BYTE [DisplayStringLenght2]
Z=0
 p var byte
 p=0
 

i ovo je u prikazu za LCD displej:

Code: Select all

'===========================================================================
modstart_prnt2scrn:

If keydec Then              ' check if decoded key is present
    keydec = 0              ' If so... reset key decoded flag.
    Endif
       
'Ako je pritisnut CTRL+ALT+DELETE onda resetiraj procesor.       
If alt Then                 ' If Alt key down,
        If ascii = $DF Then     ' and Ctrl+Delete Key pressed,
        Pause 500
        @   reset               ' do software reset!
        Endif
        endif
        
        
DisplayString[z]=ascii 'Dodaj karakter u string
'ako je pritisnut BACKSPACE brisi pogresno slovo.    
  IF ASCII = $08 THEN    'ako je pritisnut BACKSPACE
  Z=Z-1                  'vrati poziciju u stringu za jedno mjesto u LIJEVO   
  ASCII=$20              'i to mjesto ima vrijednost praznog displeja  RAZMAK
  ELSE
  Z=Z+1                  'ako nije pritisnut BACKSCAPE pomagni poziciju u stringu za jedno mjesto u DESNO
  ENDIF
DisplayString[z]=0 'zavrsi string sa nulom
LCDOUT $fe,1,STR DisplayString  


If z>DisplayStringLenght THEN
IF ASCII = $08 THEN    'ako je pritisnut BACKSPACE
  p=p-1                  'vrati poziciju u stringu za jedno mjesto u LIJEVO   
  ASCII=$20              'i to mjesto ima vrijednost praznog displeja  RAZMAK
  ELSE
  p=p+1                  'ako nije pritisnut BACKSCAPE pomagni poziciju u stringu za jedno mjesto u DESNO
  ENDIF
DisplayString2[p]=0 'zavrsi string sa nulom
LCDOUT $fe,1,STR DisplayString2 
'ceo niz ispunjen, radi sta os sad sa njim
ENDIF


 return 
User avatar
pedja089
Administrator sajta
Administrator sajta
Posts: 7871
Joined: 20-02-2007, 14:50
Location: Beočin -Srbija

Re: PS/2 tipkovnica

Post by pedja089 »

Sto se tice drugog primera, tako je i zamisljen, da se dodaje slovo samo u na zadnjoj poziciji. Kao kod kineskih digitrona kad kucas tekst bezi ulevo...
Trebalo bi da radi, ali ne garantujem.
Al kako god, drago mi je da si uspeo...
febo26
Pravo uznapredovao :)
Pravo uznapredovao :)
Posts: 207
Joined: 12-08-2008, 19:58

Re: PS/2 tipkovnica

Post by febo26 »

Ovaj probni projekat ponovo je postao aktualan i ovako kako je napisan radi odlično.Sada me zanima da li je moguce tekst koji napisem pomocu tipkovnice nekako spremiti u I2c EEprom i koje velicine bi on trebao biti.
Maksimalna duzina teksta je 160 znakova.Problem je u tome sto je tekst u RAM-u procesora i nakon nestanka struje text se izgubi pa bih htio da kada napisem text koji zelim prikazivat spremim u EEprom i kada opet upalim da text krene izpocetka,da ga ne moram ponovo upisivati.Da li je nesto takvo izvedivo?
User avatar
pedja089
Administrator sajta
Administrator sajta
Posts: 7871
Joined: 20-02-2007, 14:50
Location: Beočin -Srbija

Re: PS/2 tipkovnica

Post by pedja089 »

Bez ikakvih problema je izvodljivo. Treba ti 160 ili vise bajtova EEPROM memorije.
Ne znam jos da li je isti PIC u pitanji, ali valja baciti oko na datasheet
Data EEPROM: 256
Sto znaci da sa READ i WRITE mozes citati i upisivati podatke. I ne treba ti nikakva I2C memorija.
febo26
Pravo uznapredovao :)
Pravo uznapredovao :)
Posts: 207
Joined: 12-08-2008, 19:58

Re: PS/2 tipkovnica

Post by febo26 »

Code: Select all

 main:                
     For r=0 to 255
     Char=DisplayString[r] 'uzimaj iz niza umesto iz lookup
     if char=0 then exit'Automatski detektuj kraj tekst
     GOSUB SendChar
     Next r
Ovo gore je dio koda s kojim čitam slova iz stringa i šaljem ih na MAX7219 i to radi super.

Ako sam dobro svatio problem s memoriranjem sadržaja stringa u EPROM ja moram svaki karakter iz stringa posebno pročitati i spremiti na svoju adresu u EPROM.

probao sam nesto poput ovoga ali stvar ne radi:

Code: Select all

upis_eprom:

     for E_adress = 0 to 250
    For r=0 to 250
     Char=DisplayString[r] 'uzimaj iz niza 
     'if char=0 then exit'Automatski detektuj kraj teksta
      write e_adress,char
      next r
     next e_adress
da li se slovo koje je u stringu mora pretvoriti u neku decimalnu vrijednost da se upise u EPROM ili ono vec ima svoju decimalnu vrijednost po ASCII tablici.
User avatar
pedja089
Administrator sajta
Administrator sajta
Posts: 7871
Joined: 20-02-2007, 14:50
Location: Beočin -Srbija

Re: PS/2 tipkovnica

Post by pedja089 »

To bi trebalo da radi. Kako citas te vrednosti?
Post Reply