[stella] Euchre back with odd behavior

Subject: [stella] Euchre back with odd behavior
From: "Erik J. Eid" <eeid@xxxxxxxxx>
Date: Fri, 15 Jun 2001 23:28:09 -0400
Greetings again!

I've continued work on my Euchre game. Rather than simply displaying a few cards in your hand and on the table, the game now actually "deals" cards. All you see is your hand plus the card turned up for the proposed trump suit. Also, to ensure a random first deal, I force the player to push Reset. (I hope to have room for a title screen, but for now, there's just a game over message.)

I reworked the program to operate in "stages", which indicate what is going on during that frame - shuffling (only once per frame eliminates the flicker), dealing (revealing cards), bidding, etc. I also added the ability to display a message in the red section at the bottom of the screen and a "cursor" to select a card from your hand (though you won't see it in this version).

I'm now coming up against another problem that I can't get past. Some code is behaving in a peculiar way.

Once the deal is complete, players are to start bidding. While I don't have bidding set up yet, it starts with the player to the left of the dealer, and that player's name (north, east, etc.) should be displayed in the message section. However, the name of the player across from the dealer is shown instead.

Here's the critical code:

StartBid1
    lda #StageBidding1
    sta Stage
    lda Dealer
    adc #$01
    and #$03
    sta Turn
    adc #MsgNumSouth
    sta MessageNum
    lda #StageHold
    sta Stage
    rts

What this does is set the current stage to the first phase of bidding, set the current turn to the player one "above" (meaning, to the left) of the dealer, show the message appropriate to that player (since south is the zeroth player, adding the turn to south's message number should bring up the first bidder's name), and put the program in a hold state.

I used the debugger in PCAE and found something astonishing! Whatever is in the accumulator after the "lda Dealer" statement is increased by two, not one, by "adc #$01". To see this yourself, open up the debugger, find address 12D5, click the Here button, go back to the program window (it helps not to be in full-screen mode), hit F2 to reset, then click Trace repeatedly. Watch the accumulator. It will be increased by two.

Am I just misunderstanding how an immediate-mode adc is supposed to work, or is there something very wrong here? (It is interesting to note that the value of memory location 01 - VBLANK - is 2 when this code is executed.)

This oddness occurs under PCAE, Stella, and Z26, so I'm inclined to think my code is bad, but I can't see where at the moment.

(The newbie strikes again...)
;
; Euchre game program for the Atari 2600 video computer system
;
; Copyright 2001 by Erik Eid (eeid@xxxxxxxxx)
;
; Last update: June 15, 2001
;
; Compiled with the dasm assembler using the -f3 option
;

    processor 6502
    include vcs.h

; Constants

    seg.u defines

CardsInDeck = $18  ; 24 cards in a Euchre deck

Team1Color = $88
Team2Color = $38
TableRegionColor = $d4
CardTableColor = $0f
RedSuitColor = $36
BlackSuitColor = $00
MessageRegionColor = $22
MessageTextColor = $1c
CursorColor = $82

RankMask = %00000111      ; Bit mask for rank of a card
DispSuitMask = %00011000  ; Bit mask for suit displayed on a card
RealSuitMask = %01100000  ; Bit mask for suit used when following (the left
                          ; bower becomes the suit of the right bower)
ShowCardMask = %10000000  ; Bit mask for determining if a card is shown

BlackSuitMask = %00010000

SWACNT = $281  ; Strangely not part of the original vcs.h
VS_Disable = 0  ; Ditto

CenterRankPos = $75  ; Player positions
CenterSuitPos = $66
LeftRankPos = $a2
RightRankPos = $57

MessageP0Pos = $44
MessageP1Pos = $c4

NoCursorPos = $05

MsgNumBlank = $00
MsgNumSelect = $01
MsgNumSwap = $02
MsgNumPass = $03
MsgNumOrder = $04
MsgNumCall = $05
MsgNumAlone = $06
MsgNumTrumpHearts = $07
MsgNumTrumpDiamonds = $08
MsgNumTrumpClubs = $09
MsgNumTrumpSpades = $0a
MsgNumDeal = $0b
MsgNumGameOver = $0c
MsgNumSouth = $0d
MsgNumWest = $0e
MsgNumNorth = $0f
MsgNumEast = $10

StageHold = $00
StageNewGame = $01
StageNewHand = $02
StageGameOver = $03
StageShuffle = $04
StageDeal = $05
StageBidding1 = $06
StageBidding2 = $07

; Variables

    seg.u vars
    org $80

Team1Score  ds 1
Team2Score  ds 1
Team1Tricks ds 1
Team2Tricks ds 1
SouthHand   ds 5  ; Cards in a player's hand
WestHand    ds 5
NorthHand   ds 5
EastHand    ds 5
SouthCard   ds 1  ; Cards down on the table
WestCard    ds 1
NorthCard   ds 1
EastCard    ds 1
ImgPtr1     ds 2  ; Pointers to playfield and player images
ImgPtr2     ds 2
ImgPtr3     ds 2
ImgPtr4     ds 2
ImgPtr5     ds 2
ImgPtr6     ds 2
HandCard    ds 1  ; Pointer to a card in a hand
T1          ds 1  ; Temporary variables used in subroutines
T2          ds 1
T3          ds 1
T4          ds 1
rand1       ds 1  ; Locations to hold bits of random number
rand2       ds 1
rand3       ds 1
rand4       ds 1
NeedShuffle ds 1  ; Flag indicating if a shuffle is needed
MessageNum  ds 1  ; Number of message to display
MessagePtr  ds 2
CursorPos   ds 1  ; Card selection cursor position
Stage       ds 1
Turn        ds 1
Dealer      ds 1
FrameCount  ds 1

DeckStart = SouthHand
Upcards = SouthCard

; Program

    seg code
    org $f000  ; 4K cartridge

;
; Initialization
;
CartStart
    sei  ; Disable all interrupts
    cld  ; Clear decimal mode (so carry is at 256, not 100)

    ldx #$ff
    txs  ; Reset the stack pointer to the highest point possible

; Clear out registers and variables
    lda #$00
ClearRAM
    sta $00,x
    dex
    bne ClearRAM  ; Loop does not zero WSYNC, but it's not needed

    sta SWACNT  ; Tell port A to accept input

    lda #$6d  ; seed random number generator
    sta rand1
    sta rand2
    sta rand3
    sta rand4

    lda #NoCursorPos
    sta CursorPos

    lda #$80
    ldx #CardsInDeck
HideLoop
    dex
    sta DeckStart,x
    bne HideLoop

    jsr StartGameOver
    jmp Main

ProgStart

;
; Main loop
;
Main
; Start of display kernel
; Provide three lines of vertical sync
    lda #VS_Enable
    sta WSYNC
    sta WSYNC
    sta WSYNC
    sta VSYNC
    sta WSYNC
    sta WSYNC
    sta WSYNC
    lda #VS_Disable
    sta VSYNC

; Provide 37 scanlines of vertical blank
    lda #43  ; 37 lines * 76 cycles/line = 2812 cycles / 64 cycles/interval = 43.96 intervals
    sta TIM64T

; When it comes time, check console switches here
    lda NeedShuffle
    beq PostShuffle
    jsr ShuffleDeck
    lda #$00
    sta NeedShuffle

PostShuffle
    jsr RandomBit  ; keep the randomness flowing

WaitVBlank
    lda INTIM
    nop
    bne WaitVBlank
    sta WSYNC   ; Finish up last line
    sta VBLANK  ; Stop vertical blank (accumulator holds zero)

; Now we start on the visible portion of the screen

; First eight lines are blank...
    lda #9  ; 8 lines * 76 cycles/line = 608 cycles / 64 cycles/interval = 9.5 intervals
    sta TIM64T

; Since we have some time, prepare the playfield for displaying the scores
; and get pointers to playfield images for them.
    lda #Team1Color
    sta COLUP0
    lda #Team2Color
    sta COLUP1
    lda #PF_Score
    sta CTRLPF

    ldx Team1Score
    ldy #ImgPtr1
    jsr GetScoreImage
    ldx Team2Score
    ldy #ImgPtr2
    jsr GetScoreImage

WaitEndScore
    lda INTIM
    nop
    bne WaitEndScore

; Now we spend ten lines drawing the scores on the playfield

    ldx #$09
ScoresLoop
    sta WSYNC
    txa
    lsr
    tay
    lda (ImgPtr1),y
    sta PF1
    ror T1
    ror T1
    nop
    nop
    nop
    lda (ImgPtr2),y
    sta PF1
    dex
    bpl ScoresLoop

; Pause for four lines and prepare to show tricks

    sta WSYNC
    lda #$00
    sta PF1

    lda #4
    sta TIM64T

WaitBeginTricks
    lda INTIM
    nop
    bne WaitBeginTricks

; Trick graphics are four lines with the same value, so the offset into
; the TrickImages table is for the number of tricks rather than the xth
; byte of an image.
    ldy #$04
TricksLoop
    sta WSYNC
    ldx Team1Tricks
    lda TrickImages,x
    sta PF1
    ror T1
    ror T1
    nop
    nop
    nop
    ldx Team2Tricks
    lda TrickImages,x
    sta PF1
    dey
    bne TricksLoop

; Pause for eight more lines.

    sta WSYNC
    lda #$00
    sta PF1

    lda #7
    sta TIM64T

; Position the players for display of a card.  This is well in advance but
; we have time now.
    lda #CenterRankPos
    ldx #0
    jsr PositionPlayer
    lda #CenterSuitPos
    ldx #1
    jsr PositionPlayer
    sta WSYNC
    sta HMOVE

WaitBeginTable
    lda INTIM
    nop
    bne WaitBeginTable

; Now switch to the "card table" display

    sta WSYNC

    lda #TableRegionColor
    sta COLUBK
    lda #CardTableColor
    sta COLUPF
    lda #PF_Reflect
    sta CTRLPF
    lda #$0f
    sta PF1
    lda #$ff
    sta PF2

    lda NorthCard
    ldx #ImgPtr1
    ldy #ImgPtr2
    jsr GetCardGraphics
    sta COLUP0
    sta COLUP1

    jsr DrawSingleCard

    lda #$00
    sta GRP0
    sta GRP1

; Now we come to the hard one... both West and East

    lda #P_TwoClose    ; Two copies close
    sta NUSIZ0
    sta NUSIZ1

    lda WestCard
    ldx #ImgPtr1
    ldy #ImgPtr3
    jsr GetCardGraphics
    sta COLUP0

    lda EastCard
    ldx #ImgPtr2
    ldy #ImgPtr4
    jsr GetCardGraphics
    sta COLUP1

    lda #LeftRankPos
    ldx #0
    jsr PositionPlayer
    lda #RightRankPos
    ldx #1
    jsr PositionPlayer
;    sta WSYNC
;    sta HMOVE

    jsr DrawTwoCards

    lda #$00
    sta GRP0
    sta GRP1
    sta NUSIZ0
    sta NUSIZ1

    lda #CenterRankPos
    ldx #0
    jsr PositionPlayer
    lda #CenterSuitPos
    ldx #1
    jsr PositionPlayer
    sta WSYNC
    sta HMOVE

    lda SouthCard
    ldx #ImgPtr1
    ldy #ImgPtr2
    jsr GetCardGraphics
    sta COLUP0
    sta COLUP1

    jsr DrawSingleCard

    lda #4
    sta TIM64T

WaitEndSouth
    lda INTIM
    nop
    bne WaitEndSouth

    lda #9  ; burn 8 lines
    sta TIM64T

    lda #$00
    sta COLUBK
    sta PF1
    sta PF2

WaitBeforeHand
    lda INTIM
    nop
    bne WaitBeforeHand

; Draw the five cards in the player's hand.  For each of the cards, draw four
; black lines then twelve card lines.  The middle eight lines of the card have
; the images.  During the four black lines, get the image pointers and player
; colors.

    lda #$00
    sta HandCard
ShowHandLoop
    lda #4
    sta TIM64T
    lda #$00
    sta COLUBK
    sta PF2
    ldx HandCard
    lda SouthHand,x
    ldx #ImgPtr1
    ldy #ImgPtr2
    jsr GetCardGraphics
    sta COLUP0
    sta COLUP1
WaitToDrawHandCard
    lda INTIM
    nop
    bne WaitToDrawHandCard

    lda #$f0
    sta PF2
    sta WSYNC
    sta WSYNC
    lda HandCard
    cmp CursorPos
    beq ShowCursor
    lda #$00
    jmp xx
ShowCursor
    lda #CursorColor
xx
    sta COLUBK
    jsr DrawSingleCard
    lda #$00
    sta GRP0
    sta GRP1
    sta WSYNC
    sta COLUBK
    sta WSYNC
    sta WSYNC
    inc HandCard
    lda HandCard
    cmp #$05
    bne ShowHandLoop

; Now the gap between the last card and the message region

    lda #13
    sta TIM64T

    lda #$00
    sta COLUBK
    sta PF2
    sta COLUP0
    sta COLUP1

; Prepare for the message section
    lda #MessageP0Pos
    ldx #0
    jsr PositionPlayer
    lda #MessageP1Pos
    ldx #1
    jsr PositionPlayer
    sta WSYNC
    sta HMOVE

    ldx MessageNum
    ldy #MessagePtr
    jsr GetMessagePointer
    jsr GetMessageImages

WaitForGap
    lda INTIM
    nop
    bne WaitForGap

    sta WSYNC

    lda #MessageRegionColor
    sta COLUBK

    lda #19  ; 16 lines of message
    sta TIM64T

    lda P_ThreeClose
    sta NUSIZ0
    sta NUSIZ1
    lda #MessageTextColor
    sta COLUP0
    sta COLUP1
    lda #$01
    sta VDELP0
    sta VDELP1
    sta WSYNC
    sta WSYNC

    jsr DrawMessageText

    lda #$00
    sta VDELP0
    sta VDELP1
    lda #$00
    sta GRP0
    sta GRP1

    sta WSYNC

WaitForMessage
    lda INTIM
    nop
    bne WaitForMessage

    lda #$00
    sta COLUPF

    lda #9  ; 8 lines
    sta INTIM

    lda #$00
    sta WSYNC
    sta PF1
    sta PF2
    sta COLUBK
    sta COLUP0
    sta COLUP1
    sta COLUPF
    sta CTRLPF
    sta GRP0
    sta GRP1
    sta NUSIZ0
    sta NUSIZ1

WaitForEnd
    lda INTIM
    nop
    bne WaitForEnd

    sta WSYNC

    lda #35  ; 30 lines of overscan
    sta TIM64T

    lda #$02
    sta VBLANK

CheckReset
    lda SWCHB
    and #$01
    cmp #$01
    beq CheckStages
    jsr StartNewGame
    jmp ProgStart

CheckStages
    lda Stage
    cmp #StageHold
    bne CheckNewGame
    ;
    jmp EndCase
CheckNewGame
    cmp #StageNewGame
    bne CheckNewHand
    jsr PerformNewGame
    jmp EndCase
CheckNewHand
    cmp #StageNewHand
    bne CheckGameOver
    jsr PerformNewHand
    jmp EndCase
CheckGameOver
    cmp #StageGameOver
    bne CheckShuffle
    ;
    jmp EndCase
CheckShuffle
    cmp #StageShuffle
    bne CheckDealing
    jsr PerformShuffle
    jmp EndCase
CheckDealing
    cmp #StageDeal
    bne CheckBidding1
    jsr PerformDeal
    jmp EndCase
CheckBidding1
    cmp #StageBidding1
    bne EndCase
;    jsr PerformBidding1

EndCase

WaitOverscan
    lda INTIM
    nop
    bne WaitOverscan
    sta WSYNC

    jmp Main

StartBid1
    lda #StageBidding1
    sta Stage
    lda Dealer
    adc #$01
    and #$03
    sta Turn
    adc #MsgNumSouth
    sta MessageNum
    lda #StageHold
    sta Stage
    rts

StartShuffle
    lda #StageShuffle
    sta Stage
    lda #$08
    sta Turn
    lda #MsgNumDeal
    sta MessageNum
    rts

StartDeal
    lda #StageDeal
    sta Stage
    lda #MsgNumDeal
    sta MessageNum
    rts

PerformDeal
    ldx #$04
DealLoop
    lda SouthHand,x
    and #%01111111
    sta SouthHand,x
    dex
    bpl DealLoop
    ldx Dealer
    lda Upcards,x
    and #%01111111
    sta Upcards,x
    jsr StartBid1
    rts

PerformShuffle
    lda Turn
    cmp #$07
    bne SkipRefresh
    jsr RefreshDeck
SkipRefresh
    jsr ShuffleDeck
    dec Turn
    bpl GoAway
    jsr StartDeal
GoAway
    rts

StartNewGame
    lda #StageNewGame
    sta Stage
    lda #MsgNumBlank
    sta MessageNum
    rts

PerformNewGame
    lda #$00
    sta Team1Score
    sta Team2Score
    lda rand1
    and #$03
    sta Dealer
    jsr StartNewHand
    rts

StartNewHand
    lda #StageNewHand
    sta Stage
    lda #MsgNumBlank
    sta MessageNum
    rts

PerformNewHand
    lda #$00
    sta Team1Tricks
    sta Team2Tricks
    lda Dealer
    adc #$01
    and #$03
    sta Dealer
    jsr StartShuffle
    rts

StartGameOver
    lda #StageGameOver
    sta Stage
    lda #MsgNumGameOver
    sta MessageNum
    rts

GetScoreImage
    txa
    asl
    tax
    lda ScoreImageTable,x
    sta $00,y
    lda ScoreImageTable+1,x
    sta $01,y
    rts

GetRankImage
    txa
    asl
    tax
    lda RankImageTable,x
    sta $00,y
    lda RankImageTable+1,x
    sta $01,y
    rts

GetSuitImage
    txa
    asl
    tax
    lda SuitImageTable,x
    sta $00,y
    lda SuitImageTable+1,x
    sta $01,y
    rts

GetLetterImage
    txa
    asl
    tax
    lda LetterImageTable,x
    sta $00,y
    lda LetterImageTable+1,x
    sta $01,y
    rts

GetMessagePointer
    txa
    asl
    tax
    lda MessageTable,x
    sta $00,y
    lda MessageTable+1,x
    sta $01,y
    rts

GetMessageImages
    ldy #$06
MessageImageLoop
    dey
    sty T4
    lda (MessagePtr),y
    tax
    tya
    asl
    adc #ImgPtr1
    tay
    jsr GetLetterImage
    ldy T4
    bne MessageImageLoop
    rts

; All images are reversed since they are read by decrementing loops.

; routine to draw a single card
; assumes ImgPtr1 and ImgPtr2 point to proper images, sprites are
; positioned, and so on

    org $fb00

DrawSingleCard
    ldy #$07
DrawCardLoop
    sta WSYNC
    lda (ImgPtr1),y
    sta GRP0
    lda (ImgPtr2),y
    sta GRP1
    dey
    bpl DrawCardLoop
    rts

; routine to draw two cards
; assumes ImgPtr1-4 point to proper images, sprites are positioned,
; and so on

DrawTwoCards
    sta WSYNC
    sta HMOVE
    ldy #$07
DrawCardLoop2
    nop
    nop
    ror T1
    ror T1
    lda (ImgPtr3),y
    tax
    lda (ImgPtr1),y
    sta GRP0
    stx GRP0
    pha
    lda (ImgPtr4),y
    tax
    lda (ImgPtr2),y
    sta GRP1
    nop
    stx GRP1
    pla
    sta WSYNC
    dey
    bpl DrawCardLoop2

    rts

; Six-digit score display
; original version by Robert Colbert in the Stella mailing list message
; "Re: [stella] Displaying scores - how?" from March 11, 1997
; (http://www.biglist.com/lists/stella/archives/199703/msg00219.html)

DrawMessageText
    sta WSYNC
    ldy #7
    sty T2
loop2
    ldy T2
    lda (ImgPtr1),y
    sta GRP0
    sta WSYNC
    lda (ImgPtr2),y
    sta GRP1
    lda (ImgPtr3),y
    sta GRP0
    lda (ImgPtr4),y
    sta T1
    lda (ImgPtr5),y
    tax
    lda (ImgPtr6),y
    tay
    lda T1
    sta GRP1
    stx GRP0
    sty GRP1
    sta GRP0
    dec T2
    bne loop2

    rts

; routine to shuffle the deck

RefreshDeck
    ldx #CardsInDeck
RD1
    dex
    lda NewDeck,x
    sta DeckStart,x
    bne RD1
    rts

ShuffleDeck
    ldx #CardsInDeck
OneShuffle
    dex
    stx T1
    jsr RandomByte
ModLoop
    cmp #CardsInDeck
    bcc LTCards
    sec
    sbc #CardsInDeck
    jmp ModLoop
LTCards
    ldx T1
    tay
    lda DeckStart,x
    sta T2
    lda DeckStart,y
    sta DeckStart,x
    lda T2
    sta DeckStart,y
    ldx T1
    bne OneShuffle
    rts

    org $fc00

MessageBlank
    .byte $00,$00,$00,$00,$00,$00
MessageSelect
    .byte $13,$05,$0c,$05,$03,$14
MessageSwap
    .byte $00,$13,$17,$01,$10,$00
MessagePass
    .byte $00,$10,$01,$13,$13,$00
MessageOrder
    .byte $0f,$12,$04,$05,$12,$00
MessageCall
    .byte $00,$03,$01,$0c,$0c,$00
MessageAlone
    .byte $01,$0c,$0f,$0e,$05,$00
MessageTrumpHearts
    .byte $14,$12,$15,$0d,$10,$1b
MessageTrumpDiamonds
    .byte $14,$12,$15,$0d,$10,$1c
MessageTrumpClubs
    .byte $14,$12,$15,$0d,$10,$1d
MessageTrumpSpades
    .byte $14,$12,$15,$0d,$10,$1e
MessageDeal
    .byte $00,$04,$05,$01,$0c,$00
MessageGameOver
    .byte $00,$0f,$16,$05,$12,$00
MessageSouth
    .byte $13,$0f,$15,$14,$08,$00
MessageWest
    .byte $00,$17,$05,$13,$14,$00
MessageNorth
    .byte $0e,$0f,$12,$14,$08,$00
MessageEast
    .byte $00,$05,$01,$13,$14,$00

MessageTable
    .word MessageBlank
    .word MessageSelect
    .word MessageSwap
    .word MessagePass
    .word MessageOrder
    .word MessageCall
    .word MessageAlone
    .word MessageTrumpHearts
    .word MessageTrumpDiamonds
    .word MessageTrumpClubs
    .word MessageTrumpSpades
    .word MessageDeal
    .word MessageGameOver
    .word MessageSouth
    .word MessageWest
    .word MessageNorth
    .word MessageEast

    org $fd00

; routine to position a player
; original version by Erik Mooney in the Stella mailing list message
; "Re: [stella] sexp8.bin Multi-Japanese Sprites" from April 18, 1998
; (http://www.biglist.com/lists/stella/archives/199804/msg00170.html)
; modified to work on both player 0 and 1 and to take a hard-coded
; position value rather than look at a table (there is no motion in
; this game, so the table is not necessary)
;
; a = position value - high nybble = fine position, low nybble =
; course position
; x = player number

PositionPlayer
    sta WSYNC
    ror T1  ; waste 5 cycles
    sta HMP0,x
    and #$0f
    tay
P0
    dey
    bpl P0
    sta RESP0,x
; Rather than WSYNC and HMOVE now, let the calling routine do it.  If both
; players are positioned in succession, this saves a scanline.
    rts

; routine to generate a random number
; original version by Erik Mooney in the Stella mailing list message
; "Re: [stella] demo update: PCMSD20.BIN" from April 14, 1997
; (http://www.biglist.com/lists/stella/archives/199704/msg00136.html)
; requires four memory locations to be reserved for generation
;
; returns: a = random number

RandomBit
    lda rand4
    asl
    asl
    asl
    eor rand4 ;new bit is now in bit 6 of A
    asl
    asl        ;new bit is now in carry
    rol rand1 ;shift new bit into bit 0 of register; bit 7 goes into carry
    rol rand2 ;shift old bit 7 into bit 8, etc.
    rol rand3
    rol rand4
    rts

RandomByte
    ldx #8
RandomByte1
    jsr RandomBit
    dex
    bne RandomByte1
    lda rand1
    rts

; routine for getting images and colors of a card
; a = card
; x = image pointer for rank
; y = image pointer for suit
; returns: a = color of card

GetCardGraphics
    sta T1
    stx T2
    sty T3
    and #RankMask
    tax
    ldy T2
    jsr GetRankImage
    lda T1
    and #DispSuitMask
    lsr
    lsr
    lsr
    tax
    ldy T3
    jsr GetSuitImage

    lda T1
    and #ShowCardMask
    bne HideCard
    lda T1
    and #BlackSuitMask
    bne CardIsBlack
    lda #RedSuitColor
    jmp LeaveGetCardGraphics
CardIsBlack
    lda #BlackSuitColor
    jmp LeaveGetCardGraphics
HideCard
    lda #CardTableColor
LeaveGetCardGraphics
    rts

    org $fe00

; All images are reversed since they are read by decrementing loops.

LetterImageSpace
    .byte $00,$00,$00,$00,$00,$00,$00,$00  ;
LetterImageA
    .byte $00,$c6,$c6,$fe,$fe,$c6,$7c,$38  ; A
LetterImageB
    .byte $00,$7c,$66,$66,$7c,$66,$66,$7c  ; B
LetterImageC
    .byte $00,$3c,$66,$60,$60,$60,$66,$3c  ; C
LetterImageD
    .byte $00,$7c,$66,$66,$66,$66,$66,$7c  ; D
LetterImageE
    .byte $00,$7e,$60,$60,$78,$60,$60,$7e  ; E
LetterImageF
    .byte $00,$60,$60,$60,$78,$60,$60,$7e  ; F
LetterImageG
    .byte $00,$3c,$66,$66,$6e,$60,$66,$3c  ; G
LetterImageH
    .byte $00,$66,$66,$66,$7e,$66,$66,$66  ; H
LetterImageI
    .byte $00,$7e,$18,$18,$18,$18,$18,$7e  ; I
LetterImageJ
    .byte $00,$3c,$66,$06,$06,$06,$06,$0e  ; J
LetterImageK
    .byte $00,$66,$6c,$78,$70,$78,$6c,$66  ; K
LetterImageL
    .byte $00,$7e,$60,$60,$60,$60,$60,$60  ; L
LetterImageM
    .byte $00,$c6,$c6,$c6,$d6,$fe,$ee,$c6  ; M
LetterImageN
    .byte $00,$c6,$c6,$ce,$de,$f6,$e6,$c6  ; N
LetterImageO
    .byte $00,$3c,$66,$66,$66,$66,$66,$3c  ; O
LetterImageP
    .byte $00,$60,$60,$60,$7c,$66,$66,$7c  ; P
LetterImageQ
    .byte $00,$3a,$64,$6a,$66,$66,$66,$3c  ; Q
LetterImageR
    .byte $00,$66,$66,$66,$7c,$66,$66,$7c  ; R
LetterImageS
    .byte $00,$3c,$66,$06,$3c,$60,$66,$3c  ; S
LetterImageT
    .byte $00,$18,$18,$18,$18,$18,$18,$7e  ; T
LetterImageU
    .byte $00,$3c,$66,$66,$66,$66,$66,$66  ; U
LetterImageV
    .byte $00,$10,$38,$6c,$c6,$c6,$c6,$c6  ; V
LetterImageW
    .byte $00,$c6,$ee,$fe,$d6,$c6,$c6,$c6  ; W
LetterImageX
    .byte $00,$c6,$c6,$6c,$38,$6c,$c6,$c6  ; X
LetterImageY
    .byte $00,$18,$18,$18,$3c,$66,$66,$66  ; Y
LetterImageZ
    .byte $00,$7e,$60,$30,$18,$0c,$06,$7e  ; Z
SuitImageHeart
    .byte $00,$10,$38,$7c,$fe,$fe,$ee,$44
SuitImageDiamond
    .byte $00,$10,$38,$7c,$fe,$7c,$38,$10
SuitImageClub
    .byte $00,$18,$7e,$ff,$7e,$18,$3c,$18
SuitImageSpade
    .byte $00,$38,$ba,$fe,$fe,$7c,$38,$10
RankImage9
    .byte $00,$3c,$46,$06,$3e,$66,$66,$3c
RankImage10
    .byte $00,$ee,$5b,$5b,$5b,$5b,$db,$4e
RankImageLeft
    .byte $00,$ec,$8a,$8a,$8c,$8a,$8a,$8c  ; debug "LB"
RankImageRight
    .byte $00,$ac,$aa,$aa,$cc,$aa,$aa,$cc  ; debug "RB"

RankImageTable
    .word RankImage9
    .word RankImage10
    .word LetterImageJ
    .word LetterImageQ
    .word LetterImageK
    .word LetterImageA
    .word RankImageLeft
    .word RankImageRight

SuitImageTable
    .word SuitImageHeart
    .word SuitImageDiamond
    .word SuitImageClub
    .word SuitImageSpade

ScoreImage0
    .byte $07,$05,$05,$05,$07
ScoreImage1
    .byte $07,$02,$02,$06,$02
ScoreImage2
    .byte $07,$04,$07,$01,$07
ScoreImage3
    .byte $07,$01,$03,$01,$07
ScoreImage4
    .byte $01,$05,$07,$01,$01
ScoreImage5
    .byte $07,$01,$07,$04,$07
ScoreImage6
    .byte $07,$04,$07,$05,$07
ScoreImage7
    .byte $04,$04,$02,$01,$07
ScoreImage8
    .byte $07,$05,$02,$05,$07
ScoreImage9
    .byte $07,$01,$07,$05,$07
ScoreImage10
    .byte $77,$25,$25,$65,$27
ScoreImage11
    .byte $72,$22,$22,$62,$22
ScoreImage12
    .byte $77,$24,$27,$61,$27
ScoreImage13
    .byte $77,$21,$23,$61,$27

ScoreImageTable
    .word ScoreImage0
    .word ScoreImage1
    .word ScoreImage2
    .word ScoreImage3
    .word ScoreImage4
    .word ScoreImage5
    .word ScoreImage6
    .word ScoreImage7
    .word ScoreImage8
    .word ScoreImage9
    .word ScoreImage10
    .word ScoreImage11
    .word ScoreImage12
    .word ScoreImage13

TrickImages
    .byte $00,$01,$05,$15,$55,$FF

LetterImageTable
    .word LetterImageSpace
    .word LetterImageA
    .word LetterImageB
    .word LetterImageC
    .word LetterImageD
    .word LetterImageE
    .word LetterImageF
    .word LetterImageG
    .word LetterImageH
    .word LetterImageI
    .word LetterImageJ
    .word LetterImageK
    .word LetterImageL
    .word LetterImageM
    .word LetterImageN
    .word LetterImageO
    .word LetterImageP
    .word LetterImageQ
    .word LetterImageR
    .word LetterImageS
    .word LetterImageT
    .word LetterImageU
    .word LetterImageV
    .word LetterImageW
    .word LetterImageX
    .word LetterImageY
    .word LetterImageZ
    .word SuitImageHeart
    .word SuitImageDiamond
    .word SuitImageClub
    .word SuitImageSpade

NewDeck
    .byte $80,$81,$82,$83,$84,$85
    .byte $a8,$a9,$aa,$ab,$ac,$ad
    .byte $d0,$d1,$d2,$d3,$d4,$d5
    .byte $f8,$f9,$fa,$fb,$fc,$fd

    org $fffc
    .word CartStart
    .word CartStart

Attachment: Euchre.bin
Description: Binary data


. . \_ +\_ + o_-/ . O
. \-_o -=/- . .
. . \=// .
---------\_______ ||O ___.______
/* Erik Eid */ \____||L/\_____/
/* eeid@xxxxxxxxx */_______________________
Current Thread