;***** Final Project: BlakJak **********
;Create a simple blackjack game for 8535 board.
;
;Keyboard uses D,LCD uses C

.include     "c:\users\bnj\8535def.inc"
.include     "c:\users\bnj\addldef.inc"                    ;this file is attached at the bottom of this page
.device     AT90S8535

.def     score  =r0                                                ;player $ left
.def     savSREG  =r1                                         ;save the status register
.def     key  =r2                                                  ;holds raw button press value
.def     comp  =r3                                               ;for binary to ascii conversion
.def     RNG  =r4                                               ;RNG register
.def     finalP  =r24                                             ;final point value (w/ aces) of player
.def     acenumP  =r10                                       ;number of aces of player
.def     acevalue =r11                                         ;point value of aces (selected between aceA and aceB)
.def     acenumD  =r12                                       ;number of aces of dealer
.def     finalD  =r26                                            ;final point value (w/ aces) of dealer
.def     cardval  =r14                                          ;value of currently selected card
.def     temp  =r16                                              ;temporary register
.def     state  =r17                                              ;state register
.def     aceA  =r18                                             ;acevalue A
.def     butnum  =r19                                          ;final press value
.def     count  =r20                                             ;counter for writing unshuffled deck
.def     count2  =r21                                           ;second register for unshuffled deck
.def     temp2  =r22                                           ;second temp reg
.def     aceB  =r23                                             ;acevalue B
.def     totalP  =r9                                             ;current accumulated point value (no aces) of player
.def     totalD  =r13                                           ;current accumulated point value (no aces) of dealer
.def     statusbj =r27                                         ;side0---who1---blackjack2---playerbusted3---dlrbusted4
                                                                        ;---playerwins5---even6----who0: 0 = dealer, 1 = player
.def     dlrfrstc =r28                                          ;dealer's first card
.def     cardsP  =r8                                           ;
.def     cardsD  =r15                                        ;
.def     tempmo  =r29                                       ;

;LCD REGISTERS
.def    wreg    =R25                                        ;temp register for interrupts
.def    timeout =R5                                         ;Timeout value passed to subroutine
.def    lcdstat =R6                                          ;LCD busy/wait status
.def    longtime=R7                                        ;Long timer for powerup

;*************
.dseg

;pre-shuffled deck
deck:            .byte 52                                     ;52 cards
decktemp:    .byte 52                                     ;temporary storage of preshuffled

;Shuffled deck
shuffle:         .byte 52                                     ;52 cards
ashuffle:       .byte 52                                     ;ascii version of shuffled deck

;score
scoremem:   .byte 3                                      ;3 digit score (each point representing $10)

;******************
.cseg

.org $0000
             rjmp         RESET                                ;reset entry vector
             rjmp         EXT_INT0                         ;keybd hit
             rjmp         EXT_INT1                         ;keybd stay
             reti
             reti
             reti
             reti
             reti
             reti
             rjmp         T0INT                                  ;timer 0 ovfl intrpt (LCD)
             reti
             reti
             reti
             reti
             reti
             reti
             reti

;define fixed strings to be tranmitted from flash- zero terminated
keytbl:         .db     0b11101110, 0b11101101, 0b11101011, 0b11100111
                   .db     0b11011110, 0b11011101, 0b11011011, 0b11010111
                   .db     0b10111110, 0b10111101, 0b10111011, 0b10110111
                  .db     0b01111110, 0b01111101, 0b01111011, 0b01110111
 

RESET:     ldi         temp, LOW(RAMEND)      ;init stack pointer
                 out        SPL, temp
                 ldi         temp, HIGH(RAMEND)
                 out        SPH, temp

                 ldi         temp,0xc0
                 out       GIFR, temp
                 ldi         wreg, 0b11000000             ;enable external interrupt 1&0
                 out       GIMSK, wreg                      ; (button detection)

                 ldi         state,shuffling                      ;Start state is shuffling

                 clr         butnum                               ;Default=no button pressed
                 ldi         temp,10                             ;
                 mov      score,temp                         ;player gets $100 to start

                 ldi         Temp, TCK1024               ;scale tim1 by 1024 for 1 sec delay
                 out        TCCR1B, Temp                  ;
                 ldi         temp, TCK1                         ;
                 out       TCCR2, temp                     ;Timer 2 at TCK1 speed

;********LCD STARTUP CODE
                ldi         temp,TSTOP                      ;
                out        TCCR0,temp                     ;Timer 0 off (just in case)
                ldi         temp,0b00000001             ;Enable Timer 0 interrupt
                out        TIMSK,temp

                sei                                                    ;global interrupt enabled

                rcall       lcdinit                                  ;Initialize LCD module
                rcall       lcdclr                                   ;Clear LCD screen
                ldi temp, 0xd4                                   ;print score 0 on line 4
                rcall lcdcmd                                      ;
                ldi temp, 0x24                                  ;Initial score=$100
                rcall lcdput                                       ;
                ldi temp, 0x31                                  ;
                rcall lcdput                                       ;
                ldi temp, 0x30                                  ;
                rcall lcdput                                       ;
                ldi temp, 0x30                                  ;
                rcall lcdput                                       ;

;*****statetable select
states:     cpi         state,shuffling                          ;jump to appropriate state
              breq      _shuffling                                  ;see our state diagram
              cpi         state,dealing                              ;
              breq      _dealingPT                              ;
              cpi         state,hitstay                              ;
              breq      _hitstayPT                                  ;
              cpi         state,hit                                      ;
              breq      _hitPT                                       ;
              cpi         state,stay                                  ;
              breq      _stayPT                                   ;
              cpi         state,winner                              ;
              breq      _winnerPT                                  ;
_error:    rjmp      _error                                       ;No match for state; error
 

;*******************************
;Store the preshuffled deck at location "deck"
_shuffling:  ldi         ZL, LOW(deck)                  ;ptr to RAM
                 ldi         ZH, HIGH(deck)
                 ldi         temp, 1
                 ldi         count, 52
                 ldi         count2, 4

                clr         butnum                               ;Default=no button pressed
                clr         cardsP                               ;set # cards for each side to be 0
                 clr         cardsD                               ;

_pilecards: st          Z, temp
                 adiw     ZL, 1
                 dec       count2
                 breq     _incvalue
                 dec      count
                 brne     _pilecards
                 rjmp     _shuffle

_incvalue:  ldi         count2, 4                             ;need to adjust count every 4 cards
                 inc        temp                                   ;increase card value by 1
                 dec       count
                 brne     _pilecards
                 rjmp     _shuffle

;***jump points**
_dealingPT:
                 rjmp     _dealing                                  ;
_hitstayPT:
                 rjmp     _hitstay                                      ;
_hitPT:      rjmp     _hit                                           ;
_stayPT:   rjmp     _stay                                       ;
_winnerPT:
                rjmp     _winner                                   ;
 

;*******************************
;This routine will shuffle the default deck to location "shuffle"
_shuffle:
             ldi             XL, LOW(shuffle)                ;ptr to RAM (shuffled deck)
             ldi             XH, HIGH(shuffle)
             in             rng, TCNT1L                         ;rng will be 7-bit RNG from timer 1
             ldi             count2, 52                             ;need to go through 52 cards
_takecard:                                                         ;Now get new random number, based on previous value
             mov         temp, rng                                ;use temp and temp2 to do RNG
             andi         temp, 0x01
             mov         temp2, rng
             andi         temp, 0x02
             eor          temp, temp2                             ;XOR these last two bits
             ror           temp                                          ;and place into C
             ror           rng                                          ;place C into RNG with a shift

;The # cards remaining affects what our random # should be
;[will want max(random #) = ((# cards) - 1) ]
             mov         temp, rng                                 ;place random number into temp reg
             cpi           count2, 33                             ;if need number > 32,
             brsh         _6rng                                      ; use 6 bits
             cpi c        ount2, 17                                 ;if need number > 16,
             brsh         _5rng                                      ; use 5 bits
             cpi          count2, 9                                 ;if need number > 8,
             brsh         _4rng                                      ; use 4 bits
             cpi          count2, 5                                 ;if need number > 4,
             brsh         _3rng                                      ; use 3 bits
             cpi          count2, 3                                 ;if need number > 2,
             brsh         _2rng                                      ; use 2 bits
             cpi          count2, 2                                 ;if need number > 1,
             brsh         _1rng                                      ; use 1 bit
             cpi          count2, 1                                 ;if need number = 1,
             breq         _0rng                                      ; use final card

             clr             statusbj                                 ;clear black jack status register

             ldi             temp,0b00000001                 ;
             bst            temp,1                                  ;
             bld           statusbj, 1                             ;who bit =0 (dealer)
             bst           temp,0                                  ;
             bld           statusbj, 0                               ;side bit =1 (down)

             clr         count                                      ;count (aka card #) = 0
             clr         acenumP                                  ;clear ace number count for both
             clr         acenumD                                  ;
             clr         totalP                                      ;clear total point value for both
             clr         totalD                                      ;

             ldi         ZL, low(shuffle)                        ;record the dealer first card
             ldi         ZH, high(shuffle)                         ;
             ld         dlrfrstc, Z                                 ;

             ldi         temp,0b00000001                  ;
             bst          temp,0                                   ;
             bld         statusbj, 0                                  ;side bit =1 (down)

             ldi         state, dealing                         ;ELSE LOAD DEALING STATE
             rjmp      states                                         ;

_6rng:    andi         temp, 0x3f                             ;take low 6 bits from RNG
             cp            temp, count2                         ;if RN too big, take less bits
             brsh         _5rng                                      ;
             rjmp        _movecard                             ;else put appropriate card into place

_5rng:    andi         temp, 0x1f                             ;take low 5 bits from RNG
             cp            temp, count2                         ;if RN too big, take less bits
             brsh         _4rng                                      ;
             rjmp        _movecard                             ;else put appropriate card into place

_4rng:    andi         temp, 0x0f                             ;take low 4 bits from RNG
             cp           temp, count2                         ;if RN too big, take less bits
             brsh         _3rng                                      ;
             rjmp        _movecard                             ;else put appropriate card into place

_3rng:   andi         temp, 0x07                             ;take low 3 bits from RNG
             cp           temp, count2                         ;if RN too big, take less bits
             brsh         _2rng                                      ;
             rjmp        _movecard                             ;else put appropriate card into place

_2rng:    andi         temp, 0x03                             ;take low 2 bits from RNG
             cp            temp, count2                         ;if RN too big, take less bits
             brsh         _1rng                                      ;
             rjmp         _movecard                             ;else put appropriate card into place

_1rng:    andi         temp, 0x01                             ;take low 1 bit from RNG
             rjmp         _movecard                             ;else put appropriate card into place

_0rng:    ldi           temp, 0                                    ;
             rjmp        _movecard                                 ;else put last card into place

;Now that card is chosen for shuffled deck, put it in
_movecard:
             clr         count                                          ;gone through 0 cards
             ldi         ZL, LOW(deck)                         ;ptr to RAM (preshuffled)
             ldi         ZH, HIGH(deck)
             ldi         YL, LOW(decktemp)                ;ptr to RAM (decktemp)
             ldi         YH, HIGH(decktemp)

;This loop is made for each card in preshuffled deck
_nextcard:
             ld          temp2, Z                                     ;get next card value
             cp         count, temp                                 ;have we reached card to remove?
             breq     _removecard                                 ;move card to shuffled deck at this point

             st         Y, temp2                                     ;otherwise place card into decktemp
             adiw     ZL, 1                                          ;choose next card to go into temp deck
             adiw     YL, 1                                          ;choose next temp deck spot

             inc         count                                           ;
             cp         count, count2                               ;reached end of deck?
             brne      _nextcard                                     ;
             dec       count2                                          ;one less card in deck
             rjmp     _takecard                                     ;going on to choose next card

;We have reached the card we wish to use in the shuffled deck
_removecard:
             st X,     temp2                                         ;put card taken from preshuffled into shuffled deck
             adiw     ZL, 1                                          ;choose next card to go into temp deck
             adiw     XL, 1                                          ;move shuffled pointer to next spot

             inc         count                                          ;
             cp         count, count2                              ;reached end of deck?
             brne     _nextcard                                     ;
             dec     count2                                              ;one less card in deck
             rjmp     _takecard                                     ;going on to choose next card

;****************
;Dealing state: give two cards to each player
_dealing:
             cpi       count, 4                                      ;check if this is the 5th card
             breq    _nodealing                                  ;if so, go to next state's selection

             rcall     _deal                                           ;give dealer a card

             sbrs     statusbj,1                                      ;check to see which side to display for
             rjmp    _dealeraddr                                  ;if bit cleared, display for dealer

            ldi        temp,0x7f                                    ;change addressing for player
            add     temp,cardsP                                  ;add # cards played
            rcall    lcdcmd                                         ; (1st line)
            rjmp   _writechar                                      ;now write character

_dealeraddr:
             ldi         temp,0xbf                                ;change addressing for dealer
             add       temp,cardsD                              ;add # cards played
            rcall       lcdcmd                                         ; (2nd line)
             mov      temp, statusbj                              ;
             andi     temp, 0x01                                      ;side bit
             brne     _downcard                                  ;side=1 (down)

_writechar:
             mov     temp, cardval                                  ;
             rcall     _cardconv                                      ;convert into ascii
_w2:     rcall     lcdput                                               ;place cardval onto LCD
             cpi      count, 3                                          ;if count <=3 and count=3 or 1
             breq     _dealingP                                      ;then the current card is dealt
             cpi       count, 1                                          ;to the player
             breq     _dealingP  ;

             cpi       count, 2                                              ;if count =2 then the current card
             breq     _dealingD                                          ;is dealt to the dealer

_moredealing:                                                        ;and it remains in dealing state
             rjmp     states                                               ;

_downcard:        ldi temp, 0xff                                  ;dark block (down card)
             rjmp     _w2                                                   ;

_dealingP:
             ldi          temp,0b00000001                              ;
             bst         temp,0                                               ;
             bld         statusbj, 1                                          ;who bit =1 (player)
             bst         temp,1                                               ;
             bld         statusbj, 0                                          ;side bit =0 (up)
             rjmp      _moredealing                                      ;

_dealingD:
             ldi          temp,0b00000001                              ;
             bst         temp,1                                                   ;
             bld         statusbj, 1                                          ;who bit =0 (dealer)
             bst          temp,1                                               ;
             bld         statusbj, 0                                          ;side bit =0 (up)
             rjmp      _moredealing                                      ;

_nodealing:
             rcall      _blackJ                                                ;
             sbrc     statusBJ, 2                                          ;if blackjack bit is set
             rjmp     _towinner                                          ;then go straight to winner state
             ldi        state, hitstay                                      ;otherwise go to hit/stay state
             rjmp     states                                                   ;
_towinner:
             ldi         state, winner                                      ;
             rjmp     states                                                   ;
 ;check blackjack bit in statusbj register
 ;if set then goto state winner
 ;otherwise goto state hitstay

;****************
_hitstay:

             cpi        finalP,21                                             ;auto end if player has 21
             breq     _stay1                                                  ;

           ldi          temp,0xc0
             out         GIFR, temp

             cpi         butnum, 4                                          ;if hit (button 1)
             breq      _tohit                                                   ;then go to state hit
             cpi         butnum, 8                                          ;if stay (button 2)
             brne      _hitstay                                              ;continue

_stay1:  clr         butnum                                               ;RESET BUTNUM AFTER KEYPRESS

             ldi         temp,0b00000001                              ;otherwise goto state stay
             bst         temp,1                                               ;
             bld         statusbj, 1                                          ;who bit =0 (dealer)
             bst         temp,1                                                   ;
             bld         statusbj, 0                                          ;side bit =0 (up)

             ldi         temp,0xC0                                                ;change addressing for dealer
             rcall       lcdcmd                                                     ; (2nd line)
             mov       temp, dlrfrstc                                              ;get label of dealer's first card
             rcall       _cardconv                                                  ;convert into ascii
             rcall       lcdput                                                       ;place dlrfrstc onto LCD

             ldi         state, stay                                                          ;
             rjmp     states                                                               ;
_tohit:    ldi        temp,30                                                 ;delay for button press
             mov     longtime, temp
             clr         temp
             mov     timeout,temp                                            ;Delay 15 mS
puwait3:
            rcall        delay
            ldi           temp,1
            sub         longtime, temp
            brne        puwait3

             clr         butnum                                                   ;RESET BUTNUM AFTER KEYPRESS

             ldi         temp,0b00000001                                  ;otherwise goto state stay
             bst         temp,0                                                   ;
             bld         statusbj, 1                                              ;who bit =1 (player)
             bst          temp,1                                                   ;
             bld         statusbj, 0                                              ;side bit =0 (up)
             ldi         state, hit                                                      ;
             rjmp     states                                                       ;

;*****************
_hit:       rcall      _deal                                                       ;deal player a card

             ldi         temp,0x7f                                                    ;change addressing for player
             add       temp,cardsP                                              ;add # cards played
             rcall       lcdcmd                                                     ; (1st line)
             mov       temp, cardval                                              ;
             rcall       _cardconv                                                  ;convert into ascii
             rcall       lcdput                                                       ;place cardval onto LCD

             rcall      playerfinal                                                      ;

             cpi         finalP, 22                                                      ;
             brsh       _towinner                                                      ;if finalP>21 then to winner state
             ldi          state, hitstay                                                  ;otherwise back to hit/stay state
             rjmp      states                                                               ;

;*****************
_stay:     rcall     dealerfinal                                                          ;
             cpi         finalD, 17                                                      ;
             brsh      _towinner2                                                  ;if finalD >=17 then to state winner
             rcall      _deal                                                           ;otherwise stay in this state
                                                                                             ;and keep dealing cards to dealer

             ldi         temp,0xbf                                                    ;change addressing for dealer
             add       temp,cardsD                                                  ;add # cards played
            rcall        lcdcmd                                                             ; (2nd line)
             mov      temp, cardval                                                      ;
             rcall      _cardconv                                                  ;convert into ascii
             rcall      lcdput                                                           ;place cardval onto LCD
             rjmp     states                                                           ;
_towinner2:
             cpi         finalD, 22                                                      ;
             brlo       _nobustD                                                      ;if finalD <=21 , then no bustD
             ldi         tempmo, 0b00000010                                 ;otherwise
             bst         tempmo, 1                                                  ;
             bld         statusbj,4                                                      ;bustedD bit =1
_nobustD:
             ldi         state, winner                                                  ;
             rjmp      states                                                           ;

;*****************
_winner:
             rcall      playerfinal                                                      ;

            ldi         temp, 0x94                                                          ;print on 3rd line
            rcall       lcdcmd                                                             ;

             sbrc         statusbj,2                                                          ;
             rjmp         _bj                                                               ;if blackjack, then player wins
             sbrc         statusbj,3                                                         ;
             rjmp         _loss                                                               ;if player busted, then player loses
             sbrc         statusbj,4                                                          ;
             rjmp         _win                                                                   ;if dealer busted, then player wins
             mov         temp,finalD                                                          ;
             mov         temp2,finalP                                                      ;
             cp          temp, temp2                                                          ;
             brlo       _win                                                                   ;finalD < finalP, player wins
             breq      _lossoreven                                                          ;if finalD = finalP, player loses or even
             rjmp      _loss                                                                   ;otherwise finalD > finalP, player loses

_bj:       ldi           tempmo, 0b00000010                                         ;
             bst         tempmo, 1                                                             ;
             bld         statusbj, 5                                                             ;player wins bit =1
             inc         score                                                                    ;Give 2x normal win for BJ
             inc         score                                                                    ;
             ldi         temp, 0x42                                                              ;'B'
             rcall         lcdput                                                                   ;
             ldi         temp, 0x4a                                                               ;'J'
             rcall        lcdput                                                                   ;
             rjmp _mopupLCD                                                              ;goto final lcd update
_win:     ldi          tempmo, 0b00000010                                         ;
             bst         tempmo, 1                                                              ;
             bld         statusbj, 5                                                          ;player wins bit =1
             ldi          temp, 0x57                                                          ;'W'
             rcall       lcdput                                                                     ;
             rjmp     _mopupLCD                                                          ;goto final lcd update
_even:   ldi         tempmo, 0b00000010                                                     ;
             bst         tempmo, 1                                                                      ;
             bld         statusbj, 6                                                                   ;even bit =1
             ldi         temp, 0x54                                                                  ;'T'
             rcall      lcdput                                                                           ;
             rjmp     _mopupLCD                                                                  ;goto final lcd update
_loss:    ldi         tempmo, 0b00000010                                                     ;
             bst       tempmo, 0                                                                      ;
             bld       statusbj, 5                                                                      ;player wins bit =0
             ldi         temp, 0x4C                                                                  ;'L'
             rcall      lcdput                                                                           ;
             rjmp     _mopupLCD                                                              ;goto final lcd update
_lossoreven:
             cpi       finalD, 17                                                                      ;
             breq     _loss                                                                           ;
             cpi      finalD, 18                                                                      ;
             breq    _loss                                                                               ;
             cpi      finalD, 19                                                                       ;
             breq     _loss                                                                               ;
             cpi      finalD, 20                                                                      ;
             breq     _even                                                                           ;
             cpi      finalD, 21                                                                      ;
             breq     _even                                                                               ;

_mopupLCD:
             rcall     _score                                                                               ;puts ascii value of score into mem

_buttonwait:
             in         temp2, PIND                                                                  ;wait for button 1 to be pressed to restart
             cpi       temp2, 0xfe                                                                      ;
             brne     _buttonwait                                                                       ;

             rcall     lcdclr                                                                                  ;

             ldi        temp, 10                                                                          ;
             tst         score                                                                               ;run out of $?
             brne     _gotmon
             mov     score,temp                                                                          ;if so, give more $

_gotmon:rcall _score                                                                               ;after clearing screen, show score again

            ldi         state, shuffling                                                                 ;
            rjmp     states                                                                               ;

;;;;;;;end of all states;;;;;;;;;

;=======================
;       Clear entire LCD and delay for a bit
lcdclr:   ldi         temp,1                                                                          ;Clear LCD command
            rcall       lcdcmd
            ldi         temp,256
            mov     timeout,temp                                                                 ;Delay 15 mS for clear command
            rcall     delay
            ret

;=======================
;       Initialize LCD module
lcdinit:  out         PORTC,temp                                                              ;Pull all pins low
            ldi         temp,0xff                                                                       ;All pins are outputs
            out        DDRC,temp
            ldi         temp,256
            mov     timeout,temp                                                                 ;Wait at least 15 mS at power up
            rcall       delay

;       LCD specs call for 3 repetitions as follows
            ldi         temp,3                                                                          ;Function set
            out         PORTC,temp                                                              ;to 8-bit mode
            nop                                                                                             ;nop is data setup time
            sbi         PORTC,lcde                                                                  ;Toggle enable line
            cbi         PORTC,lcde

             ldi         temp,256
            mov     timeout,temp                                                                     ;Wait at least 15 mS
            rcall       delay

            ldi         temp,3                                                                              ;Function set
            out         PORTC,temp
            nop
            sbi         PORTC,lcde                                                                      ;Toggle enable line
            cbi         PORTC,lcde

             ldi         temp,256
             mov     timeout,temp                                                                     ;Wait at least 15 ms
            rcall       delay

            ldi         temp,3                                                                              ;Function set
            out         PORTC,temp
            nop
            sbi         PORTC,lcde                                                                  ;Toggle enable line
            cbi         PORTC,lcde

            ldi         temp,256
            mov     timeout,temp                                                                     ;Wait at least 15 ms
            rcall       delay

            ldi         temp,2                                                                              ;Function set, 4 line interface
            out         PORTC,temp
            nop
            sbi         PORTC,lcde                                                                      ;Toggle enable line
            cbi         PORTC,lcde

            ldi         temp,0b11110000                                                             ;Make 4 data lines inputs
            out         DDRC,temp

;       Finally, at this pt, the normal 4 wire command routine can be used

            ldi         temp,0b00101000                                                         ;Function set, 4 wire, 2 lines, 5x7 font
            rcall       lcdcmd

            ldi         temp,0b00001100                                                         ;Display on, no cursor, no blink
            rcall       lcdcmd

            ldi         temp,0b00000110                                                         ;Address increment, no scrolling
            rcall       lcdcmd
            ret

;=======================
;       Wait for LCD to go unbusy
lcdwait:
            ldi         temp,0xF0                                                               ;Make 4 data lines inputs
            out         DDRC,temp
            sbi         PORTC,lcdrw                                                         ;Set r/w pin to read
            cbi         PORTC,lcdrs                                                         ;Set register select to command
waitloop:
            sbi         PORTC,lcde                                                          ;Toggle enable line
            cbi         PORTC,lcde
            in          lcdstat,PINC                                                            ;Read busy flag
        ;Read, and ignore lower nibble
            sbi         PORTC,lcde                                                          ;Toggle enable line
            cbi         PORTC,lcde

            sbrc        lcdstat,3                                                                   ;Loop until done
            rjmp        waitloop
            ret

;=======================
;       Send command in temp to LCD
lcdcmd:
            push        temp                                                                    ;Save character
            rcall       lcdwait                                                                 ;Wait for LCD to be ready
            ldi         temp,0xFF                                                           ;Make all port D pins outputs
            out         DDRC,temp
            pop         temp                                                                        ;Get character back
            push        temp                                                                        ;Save another copy
            swap        temp                                                                        ;Get upper nibble
            andi        temp,0x0F                                                               ;Strip off upper bits
            out         PORTC,temp                                                              ;Put on port
            nop                                                                                 ;wait for data setup time
            sbi         PORTC,lcde                                                      ;Toggle enable line
            cbi         PORTC,lcde

            pop         temp                                                                    ;Recall character
            andi        temp,0x0F                                                           ;Strip off upper bits
            out         PORTC,temp                                                      ;Put on port
            nop
            sbi         PORTC,lcde                                                           ;Toggle enable line
            cbi         PORTC,lcde

            ldi         temp,0xF0                                                           ;Make 4 data lines inputs
            out         DDRC,temp
            ret

;=======================
;       Send character data in temp to LCD
lcdput:
            push        temp                                                                ;Save character
            rcall       lcdwait                                                                 ;Wait for LCD to be ready
            ldi         temp,0xFF                                                           ;Make all port C pins outputs
            out         DDRC,temp

            pop         temp                                                                ;Get character back
            push        temp                                                            ;Save another copy
            swap        temp                                                            ;Get upper nibble
            andi        temp,0x0F                                                   ;Strip off upper bits
            out         PORTC,temp                                              ;Put on port
            sbi         PORTC,lcdrs                                             ;Register select set for data
            nop
            sbi         PORTC,lcde                                              ;Toggle enable line
            cbi         PORTC,lcde

            pop         temp                                                            ;Recall character
            andi        temp,0x0F                                                   ;Strip off upper bits
            out         PORTC,temp                                              ;Put on port
            sbi         PORTC,lcdrs                                             ;Register select set for data
            nop
            sbi         PORTC,lcde                                              ;Toggle enable line
            cbi         PORTC,lcde

            ldi         temp,0xF0                                                   ;Make 4 data lines inputs
            out         DDRC,temp
            ret

;=======================
;***** Timer 0 overflow interrupt handler
T0INT:
            set                                                                         ;Set T flag
            ldi         wreg,TSTOP                                             ;Timer 0 off
            out         TCCR0,wreg                                          ;Stop timer
            reti                                                                        ;Done, return

;** Delay n*64 microseconds using timer 0, delay time passed in timeout
; weird construction, interrupt is called like a subroutine

delay:    in          wreg,SREG                                               ;Save status register
             push     wreg
             out      TCNT0,timeout
            clt                                                                         ;Clear T
            ldi         wreg,TCK256                                         ;Timer 0 prescaler, CK / 256
            out       TCCR0,wreg                                              ;Run timer
dwait:  brtc        dwait                                                       ;Wait for timer 0 interrupt to set T
            pop       wreg                                                        ;Restore status register
            out        SREG,wreg
            ret

;=======================

EXT_INT0:
            in         savSREG, SREG                                                ;save the status reg
            ldi         butnum, 4
            out         SREG, savSREG                                                ;restore status reg
            reti                                                                                                ;

EXT_INT1:
            in         savSREG, SREG                                                ;save the status reg
            ldi         butnum, 8
           out         SREG, savSREG                                                ;restore status reg
           reti    ;

;-----------------------
;DEAL subroutine
;ENTRY REQUIREMENTS: shuffle is completed, cardnum has # of current card (starting at 0)
_deal:     ldi         ZL, LOW(shuffle)                                       ;ptr to RAM for shuffled deck in binary
              ldi         ZH, HIGH(shuffle)                                         ;
              add         ZL, count                                                  ;add difference in card #
              in             tempmo, sreg                                              ;
              sbrc       tempmo, 0                                                      ;if carry, manually do
              inc         ZH                                                                   ;
              inc         count                                                                   ;
              ld         cardval, Z                                                         ;put card value into cardval
              ldi         temp,1
              sbrc     statusbj,1                                                          ;if who=player
              add     cardsP, temp                                                      ; inc count of player cards
              sbrs     statusbj,1                                                          ;if who=dealer
              add     cardsD, temp                                                      ; inc count of dealer cards
              rcall     _total                                                               ;using card value, decide new total value
              ret                                                                                ;
;-----------------------
;TOTAL subroutine
;ENTRY: cardval has number of card, total and acenum are ready to be added to
_total:     ldi         temp, 1                                                                   ;
              cp         cardval, temp                                                      ;is current card an ace?
              breq     _acecard                                                              ;if so, adjust acenum
              ldi         temp, 10                                                              ;
              cp         cardval, temp                                                      ;if a face card, use appropriate value
              brsh     _facecard                                                              ;
              sbrc     statusbj, 1                                                              ;if who=player,
              add     totalP, cardval                                                          ;add the pointvalue to player total
              sbrs     statusbj, 1                                                              ;if who=dealer,
              add     totalD, cardval                                                      ;add the pointvalue to player total
              ret                                                                                    ;
_acecard:
              ldi         temp, 1                                                               ;not strictly necessary, as temp is already 1
              sbrc      statusbj, 1                                                              ;if who=player,
              add         acenumP, temp                                                  ;increment number of player aces
              sbrs      statusbj, 1                                                              ;if who=dealer,
              add      acenumD, temp                                                          ;increment number of dealer aces
              ret
_facecard:
              ldi         temp, 10                                                                  ;not strictly necessary, as temp is already 10
              sbrc     statusbj, 1                                                              ;if who=player,
              add      totalP, temp                                                          ;increment number of player aces
              sbrs      statusbj, 1                                                              ;if who=dealer,
              add      totalD, temp                                                          ;increment number of dealer aces
              ret
;-----------------------
_blackJ: mov      temp, acenumP                                                   ;
             cpi         temp, 1                                                                ;
             brne      _endBJ                                                                ;
             ldi         temp, 10                                                               ;
             cpse     totalP, temp                                                           ;
             rjmp     _endBJ                                                                ;
             ldi         temp,0b00000001                                               ;
             bst         temp,0                                                                    ;
             bld         statusbj, 2                                                           ;blackjack bit =1 (blackjack condition met!)
_endBJ: ret                                                                                 ;

;-----------------------
playerfinal:
             clr         tempmo                                                               ;
             cp          acenumP, tempmo                                                  ;
             brne         _acesP                                                                ;ace(s) sited!
             mov         finalP, totalP                                                       ;if no ace, then finalP=totalP
             ret     ;
_acesP: mov          temp2, acenumP                                                   ;load acenumP for acevalue lookup
             rcall         acemap                                                                    ;

             mov         temp, totalP                                                               ;
             add         temp, aceA                                                               ;
             cpi         temp, 22                                                                   ;temp= totalP + aceA
             brsh         _playerbusted                                                           ;if totalP +aceA >21 then player busted
             mov         temp2, totalP                                                               ;else
             add         temp2, aceB                                                               ;
             cpi         temp2, 22                                                                   ;temp= totalP + aceB
             brlo         _largeAce                                                                   ;if totalP + aceB <=21, then use aceB
             mov         finalP, temp                                                           ;otherwise finalP = totalP + aceA
             ret     ;
_playerbusted:
             mov         finalP, temp                                                                   ;
             ldi             tempmo, 0b00000010                                                  ;
             bst             tempmo, 1                                                               ;set T bit
             bld             statusbj,3                                                               ;set player busted bit =1
             ret     ;
_largeAce:
             mov         finalP, temp2                                                           ;finalP=totalP + aceB
             ret     ;
;-----------------------
dealerfinal:
             clr             tempmo                                                                    ;
             cp             acenumD, tempmo                                                   ;
             brne         _acesD                                                                    ;ace(s) sighted!
             mov         finalD, totalD                                                           ;if no ace, then finalD=totalD
             ret     ;
_acesD: mov         temp2, acenumD                                                       ;load acenumD for acevalue lookup
             rcall         acemap                                                                        ;

             mov         temp, totalD                                                                   ;
             add         temp, aceB                                                               ;temp= totalD + aceB
             cpi         temp, 22                                                                   ;if totalD + aceB >= 22 then
             brsh       _smallAce                                                                   ;use aceA value
             mov       finalD, temp                                                                   ;finalD=totalD + aceB
             ret     ;
_smallAce:
             mov         temp2, totalD                                                               ;
             add         temp2, aceA                                                                 ;
             mov         finalD, temp2                                                               ;finalD=totalD + aceA
             ret     ;
;-----------------------
acemap: cpi         temp2, 1                                                                   ;
             brne     _2aces                                                                        ;
             ldi         aceA, 1                                                                   ;if P/D acenum =1 then A is either
             ldi         aceB, 11                                                                  ;1 or 11
             ret     ;
_2aces: cpi         temp2, 2                                                                   ;
             brne     _3aces                                                                        ;
             ldi         aceA, 2                                                                    ;if P/D acenum =2 then A is either
             ldi         aceB, 12                                                                   ;2 or 12
             ret     ;
_3aces: cpi         temp2, 3                                                                   ;
             brne     _4aces                                                                        ;
             ldi         aceA, 3                                                                    ;if P/D acenum =3 then A is either
             ldi         aceB, 13                                                                   ;3 or 13
             ret     ;
_4aces: ldi         aceA, 4                                                                    ;if P/D acenum =4 then A is either
             ldi         aceB, 14                                                                   ;4 or 14
             ret     ;
;-----------------------
;ascii card conversion subroutine

_cardconv:
             cpi         temp, 1                                                                    ;card is ace?
             breq      _aceconv                                                                   ;
             cpi         temp, 13                                                                   ;card is king?
             breq      _kingconv                                                                  ;
             cpi         temp, 12                                                                   ;card is queen?
             breq     _queenconv                                                                   ;
             cpi         temp, 11                                                                   ;card is jack?
             breq     _jackconv                                                                       ;
             cpi         temp, 10                                                                   ;card is 10?
             breq     _10conv                                                                       ;
             subi      temp, negzero                                                            ;sub negative 0x30
             ret         ;

_aceconv:
             ldi         temp, 0x41                                                                   ;'A'
             ret     ;

_kingconv:
             ldi         temp, 0x4b                                                                   ;'K'
             ret     ;

_queenconv:
             ldi         temp, 0x51                                                                   ;'Q'
             ret     ;

_jackconv:
             ldi         temp, 0x4a                                                                     ;'J'
             ret     ;

_10conv:
             ldi         temp, 0x30                                                                      ;'0'
             ret     ;

;-----------------------
;keyboard subroutine

keybd:
             ldi         wreg, 0x0f                                                                     ;set lower four lines to output
             out          DDRD, wreg
             ldi         wreg, 0xf0                                                                     ;and turn on the pullups on the inputs
             out       PORTD, wreg
             nop                                                                                            ;Need some time for the pullups to
             nop                                                                                           ;charge the port pins
             nop
             nop
             nop
             nop
             nop
             in         wreg, PIND                                                                     ;read the high nibble
             mov       key, wreg                                                                     ;and store it (with zeros in the low nibble)
 

              ldi         wreg, 0xf0                                                                     ;set upper four lines to outputs
             out        DDRD, wreg
             ldi         wreg, 0x0f                                                                     ;and turn on pullups on the inputs
             out       PORTD, wreg

             nop                                                                                               ;As before wait for the pin to charge
             nop
             nop
             nop
             nop
             nop
             nop
             in         wreg, PIND                                                                         ;read the low nibble
             or         key, wreg                                                                         ;combine to make key code

 ;At the point the raw key code should have exactly one zero each
 ;in the lower and upper nibbles. Any other number of zeros indicates
 ;either no-button pressed or multiple-button pressed.

 ;Now search the table for a match to the raw key code
 ;and exit with a button number
             ldi         ZL, low(keytbl*2)                                                             ;  table pointer in FLASH
             ldi         ZH, high(keytbl*2)                                                             ;so convert from word to byte addr
             ldi         butnum, 0

tbllp:     lpm                                                                                                   ;get the table entry
             cp         key, r0                                                                              ;match?
             breq     foundit
             inc         butnum                                                                              ;if not, have we exhausted the
             cpi         butnum, 0x10                                                                     ;table
             breq         illegal
             adiw         ZL, 1                                                                                  ;if not, get the next table entry
             rjmp         tbllp

foundit: subi         butnum, -1                                                                     ;add one for display

            ldi         temp, 0x4b
            rcall         lcdput
            mov         temp, butnum
            subi         temp, negzero

             ret   ;RETURN FROM SUBROUTINE CALL

illegal:
             clr         butnum

            ldi         temp, 0x4b
            rcall      lcdput
            mov     temp, butnum
            subi      temp, negzero

             ret                                                                                               ;RETURN FROM SUBROUTINE CALL0
 

;----
;Take temp as binary to translate to ASCII
_score:  ldi ZL, LOW(scoremem)                                                             ;
            ldi ZH, HIGH(scoremem)                                                             ;
            clr temp2                                                                                      ;decimal digit value
            mov temp,score

_cap100loop: cpi temp,100                                                                        ;low byte >= 100?
            brlo _no100                                                                                    ; if not, goto 10's
            inc temp2                                                                                     ;else, 3rd digit ++
            subi temp,100                                                                                     ;capvalue - 100
            rjmp _cap100loop                                                                                                                                                                        ;

_no100:  subi temp2,negzero                                                                       ;decimal digit value = 0x30 + offset
            st Z, temp2                                                                                     ;
            adiw  ZL,1                                                                                      ;
            clr temp2                                                                                     ;
_cap10loop: cpi temp,10                                                                              ;
            brsh _cap10                                                                                     ;cap value >=10
            subi temp2,negzero                                                                                    ;decimal digit value = 0x30 + offset
            st Z, temp2                                                                                     ;
            adiw  ZL,1                                                                                      ;
            clr temp2                                                                                     ;
_cap1loop: cpi temp,1                                                                                     ;
            brsh _cap1                                                                                      ;cap value >=1
            subi temp2,negzero                                                                                    ;decimal digit value = 0x30 + offset
            st Z, temp2                                                                                     ;
            adiw  ZL,1                                                                                      ;
            rjmp _print                                                                                      ;display ascii

_cap10:  inc temp2                                                                                     ;2nd digit ++
            subi temp,10                                                                                     ;capvalue - 10
            rjmp _cap10loop                                                                                     ;return to test again

_cap1:  inc temp2                                                                                     ;1st digit ++
            dec temp                                                                                      ;capvalue --
            rjmp _cap1loop                                                                                     ;return to test again

 
_print:  ldi ZL, LOW(scoremem)                                                                                    ;
            ldi ZH, HIGH(scoremem)                                                                                    ;
            ldi temp, 0xd4                                                                                    ;print on 4th line
            rcall lcdcmd                                                                                     ;
            clr temp2                                                                                     ;using temp2 to track nonzero
            ldi temp, 0x24                                                                                     ;'$'
            rcall lcdput                                                                                      ;
 

            ld temp, Z                                                                                     ;
            adiw ZL, 1                                                                                     ;inc pointer
            cpi temp,0x30                                                                                    ;stored ascii = 0?
            breq _10dig                                                                                     ;if so, go on to next digit
            rcall lcdput                                                                                     ;if not, print #
            ser temp2                                                                                     ; and set temp2
 
_10dig:  ld temp, Z                                                                                     ;
            adiw ZL, 1                                                                                     ;inc pointer
            cpi temp,0x30                                                                                    ;stored ascii = 0?
            brne _print10                                                                                    ;if not, print
            tst temp2                                                                                     ;encountered nonzero?
            brne _print10                                                                                    ;if so, print
            rjmp _1dig                                                                                     ;if not, next digit
_print10: rcall lcdput                                                                                     ;print digit
            ser temp2                                                                                     ;
 
_1dig:  ld temp, Z                                                                                     ;
            adiw ZL, 1                                                                                     ;inc pointer
            cpi temp,0x30                                                                                    ;stored ascii = 0?
            brne _print1                                                                                     ;if not, print
            tst temp2                                                                                     ;encountered nonzero yet?
            brne _print1                                                                                     ;if so, print
            rjmp _0dig                                                                                     ;if not, final 0
_print1: rcall lcdput                                                                                     ;print digit

_0dig:  ldi temp, 0x30                                                                                    ;print a '0'
            rcall lcdput                                                                                     ;
            ldi temp, 0x20                                                                                    ;print a space
            rcall lcdput                                                                                     ;
            ret
 

Additional definition file:

;***** Other equates
.equ    lcdrs   =Pc6                                                                                   ;LCD rs pin connected to Pc6
.equ    lcdrw   =Pc5                                                                                    ;LCD r/w pin connected to Pc5
.equ    lcde    =Pc4                                                                                    ;LCD enable pin connected to Pc4

;       Timer/Counter prescaler values
.equ    TSTOP   =0                                                                                  ;Stop Timer/Counter
.equ    TCK1    =1                                                                                  ;Timer/Counter runs from CK / 1
.equ    TCK256  =4                                                                                  ;Timer/Counter runs from CK / 256
.equ    TCK1024  =5                                                                                  ;Timer/Counter runs from CK / 1024
.equ     PreScal1=0x41                                                                                  ;Timer 1 w/prescale=1 w/rising edge (from anacomp)

.equ     negzero  =0xd0                                                                                 ;2's complement of 0x30 (ascii 0) for subi
.equ     azero  ='0'                                                                                     ;0x30 ascii '0'
.equ     aone  ='1'                                                                                         ;0x31 ascii '1'
.equ     aspace  =' '                                                                                     ;0x20 ascii ' '
.equ     aA  ='A'                                                                                         ;0x41 ascii 'A'
.equ     aJ  ='J'                                                                                             ;0x4a ascii 'J'
.equ     aK  ='K'                                                                                         ;0x4b ascii 'K'
.equ     aQ  ='Q'                                                                                             ;0x51 ascii 'Q'
.equ     shuffling =1                                                                                          ;State labels
.equ     dealing  =2 ;
.equ     hitstay  =3 ;
.equ     hit  =4 ;
.equ     stay  =5 ;
.equ     winner  =6 ;
.equ     mopup  =7 ;