switch to two-stack async setup!!!

This commit is contained in:
Shoofle 2025-02-26 15:49:02 -05:00
parent 89684a3b83
commit 08d978bd58
13 changed files with 572 additions and 722 deletions

View File

@ -29,42 +29,42 @@ TheFool:
ld [hl+], a ; $c201 = timer for big zero ld [hl+], a ; $c201 = timer for big zero
.fUpdate: .fUpdate:
ldh a, [rDELTAT] ld a, [rDELTAT]
ld b, a ld b, a
ld a, [$c300] ld a, [CARD_VARS_START]
add a, b add a, b
ld [$c200], a ld [CARD_VARS_START], a
ld a, [$c300+1] ld a, [CARD_VARS_START+1]
adc a, 0 adc a, 0
ld [$c300+1], a ; increment time. when the 16bit time register is greater ld [CARD_VARS_START+1], a ; increment time. when the 16bit time register is greater
ld a, [$c300+1] ld a, [CARD_VARS_START+1]
cp a, $08 ; $10 00 = 1 second cp a, $08 ; $10 00 = 1 second
jp c, .doneWithTimer1 ; if the timer is less than $0800, skip to end jp c, .doneWithTimer1 ; if the timer is less than $0800, skip to end
;otherwise reset the timer ;otherwise reset the timer
ld a, 0 ld a, 0
ld [$c300], a ld [CARD_VARS_START], a
ld [$c300+1], a ld [CARD_VARS_START+1], a
.doneWithTimer1 .doneWithTimer1
ld a, [$c302] ld a, [CARD_VARS_START+2]
add a, b add a, b
ld [$c302], a ld [CARD_VARS_START+2], a
ld a, [$c302+1] ld a, [CARD_VARS_START+2+1]
adc a, 0 adc a, 0
ld [$c302+1], a ld [$c302+1], a
ld a, [$c302+1] ld a, [CARD_VARS_START+2+1]
cp a, $10 ; $10 00 = 1 second cp a, $10 ; $10 00 = 1 second
jp c, .doneWithTimer2 ; if the timer is less than $0800, skip to end jp c, .doneWithTimer2 ; if the timer is less than $0800, skip to end
;otherwise reset the timer ;otherwise reset the timer
ld a, 0 ld a, 0
ld [$c302], a ld [CARD_VARS_START+2], a
ld [$c302+1], a ld [CARD_VARS_START+2+1], a
.doneWithTimer2 .doneWithTimer2

446
Async.inc
View File

@ -1,55 +1,120 @@
; async variables from ff80-ff8f! ; async variables somewhere in RAM
def vAsyncAF equ $ff80 def vAsyncAF equ ASYNC_VARS_START
def vAsyncHL EQU $ff82 def vAsyncHL EQU vAsyncAF+2
def vAsyncDE EQU $ff84 def vAsyncDE EQU vAsyncHL+2
def vAsyncBC equ $ff86 def vAsyncBC equ vAsyncDE+2
def vAsyncPC equ $ff88 def vAsyncPC equ vAsyncBC+2
def vAsyncNext equ $ff8a def vAsyncNext equ vAsyncPC+2
def vAsyncAfter equ $ff8c def vAsyncAfter equ vAsyncNext+2
def vAsyncProgress equ $ff8e def vAsyncProgress equ vAsyncAfter+2
def vAsyncMainSP equ vAsyncProgress+2
def vAsyncThreadSP equ vAsyncMainSP+2
def SAFE_ASYNC_START EQU 146 ; canonical ordering to push should be: AF, BC, DE, HL,
def SAFE_ASYNC_END EQU 152
DoInAsyncVBlank: def ASYNC_STACK_TOP equ $ffc0
; stack top is ffc0
; first value on the stack is the early return pointer, at ffbe = ffc0-2
; second value is the destination of the async call, at ffbc = ffbe-2 = ffc0-2-2
def ASYNC_THREAD_CALL equ ASYNC_STACK_TOP - 2 - 2
def SAFE_ASYNC_START EQU 148
def SAFE_ASYNC_END EQU 153
Async_Spawn_HL:
di di
push af ld a, l
ld [ASYNC_THREAD_CALL], a
ld a, l
ldh [vAsyncHL], a
ld a, h ld a, h
ldh [vAsyncHL+1], a ld [ASYNC_THREAD_CALL+1], a
ld a, e Async_Spawn:
ldh [vAsyncDE], a di
ld a, d nop
ldh [vAsyncDE+1], a
ld a, c
ldh [vAsyncBC], a
ld a, b
ldh [vAsyncBC+1], a
; save all the registers
push af
ld a, l
ld [vAsyncHL], a
ld a, h
ld [vAsyncHL+1], a
ld a, e
ld [vAsyncDE], a
ld a, d
ld [vAsyncDE+1], a
ld a, c
ld [vAsyncBC], a
ld a, b
ld [vAsyncBC+1], a
pop hl pop hl
ld a, l ld a, l
ldh [vAsyncAF], a ld [vAsyncAF], a
ld a, h ld a, h
ldh [vAsyncAF+1], a ld [vAsyncAF+1], a
; set pu the next call! ; save main sp
ldh a, [vAsyncNext] ld hl, sp+0
ldh [vAsyncPC], a ld a, l
ldh a, [vAsyncNext+1] ld [vAsyncMainSP], a
ldh [vAsyncPC+1], a ; put next into pc ld a, h
ldh a, [vAsyncAfter] ld [vAsyncMainSP+1], a
ldh [vAsyncNext], a
ldh a, [vAsyncAfter+1]
ldh [vAsyncNext+1], a ; puut after into next
ld a, 0
ldh [vAsyncAfter], a ; unless this gets overwritten later, end execution after that
ldh [vAsyncAfter+1], a
ld a, LOW(DoInAsyncVBlank_EnterThread) ; switch to thread sp
ld a, LOW(ASYNC_STACK_TOP)
ld l, a
ld a, HIGH(ASYNC_STACK_TOP)
ld h, a
ld sp, hl
; push early return onto thread stack
ld l, LOW(Async_EarlyReturn)
ld h, HIGH(Async_EarlyReturn)
push hl
; requestedd pc is expected to be set at ASYNC_THREAD_CALL by the calling func
ld hl, sp-2
ld sp, hl
; push registers
; canonical ordering to push should be: AF, BC, DE, HL,
ld a, [vAsyncAF]
ld l, a
ld a, [vAsyncAF+1]
ld h, a
push hl
ld a, [vAsyncBC]
ld l, a
ld a, [vAsyncBC+1]
ld h, a
push hl
ld a, [vAsyncDE]
ld l, a
ld a, [vAsyncDE+1]
ld h, a
push hl
ld a, [vAsyncHL]
ld l, a
ld a, [vAsyncHL+1]
ld h, a
push hl
; save current sp to vAsyncThreadSP
ld hl, sp+0
ld a, l
ld [vAsyncThreadSP], a
ld a, h
ld [vAsyncThreadSP+1], a
; now the stack looks like: early return, ASYNC_THREAD_CALL, AF, BC, DE, HL
; switch back to main thread.
; register enterthread
ld a, LOW(Async_EnterThread)
ld [INTERRUPT_LCD], a ld [INTERRUPT_LCD], a
ld a, HIGH(DoInAsyncVBlank_EnterThread) ld a, HIGH(Async_EnterThread)
ld [INTERRUPT_LCD + 1], a; set interrupt handler to "ENTER THREAD" ld [INTERRUPT_LCD + 1], a; set interrupt handler to "ENTER THREAD"
ld a, SAFE_ASYNC_START ; CHANGE ME TO ADJUST SAFE TRANSFER TIMING ld a, SAFE_ASYNC_START ; CHANGE ME TO ADJUST SAFE TRANSFER TIMING
ld [rLYC], a ; set LYC ld [rLYC], a ; set LYC
@ -59,204 +124,177 @@ DoInAsyncVBlank:
set 6, [hl] ; set the stat interrupt to LYC mode set 6, [hl] ; set the stat interrupt to LYC mode
ld hl, rIF ld hl, rIF
res 1, [hl] ; clear the interrupt so we don't immediately fire it res 1, [hl] ; clear the interrupt so we don't immediately fire it
ei
; restore main sp
ld a, [vAsyncMainSP]
ld l, a
ld a, [vAsyncMainSP+1]
ld h, a
ld sp, hl
; restore registers from memory
ld a, [vAsyncAF]
ld l, a
ld a, [vAsyncAF+1]
ld h, a
push hl ; this is so we can pop af when we're done
ld a, [vAsyncHL]
ld l, a
ld a, [vAsyncHL+1]
ld h, a
ld a, [vAsyncDE]
ld e, a
ld a, [vAsyncDE+1]
ld d, a
ld a, [vAsyncBC]
ld c, a
ld a, [vAsyncBC+1]
ld b, a
pop af
ei
ret ret
DoInAsyncVBlank_EnterThread: Async_EnterThread:
;stack looks like: ;stack looks like:
;c113 (SMC int @ LYC 90 pc), 004b (hw int @ LYC 90 pc), outer context pc ;c113 (SMC int @ LYC 90 pc), 004b (hw int @ LYC 90 pc), outer context pc
push hl push af
push bc push bc
push de push de
push af push hl
; check if there's anything queued up for executing; if no, just clean up
ld a, LOW(ASYNC_STACK_TOP) ; we're checkng if the current async stack is empty
ld hl, vAsyncThreadSP ; comparing to the current thread sp
cp a, [hl] ; are they equal?
jp z, Async_CleanUpThread
;af, de, bc, hl, c113 (SMC interrupt pc), 004b (hardwired interrput pc), outer context pc ;af, de, bc, hl, c113 (SMC interrupt pc), 004b (hardwired interrput pc), outer context pc
; check if there's anything queued up for next execution ld a, LOW(Async_ExitThread)
ldh a, [vAsyncPC]
ld l, a
ldh a, [vAsyncPC+1]
ld h, a
or a, l
jp z, DoInAsyncVBlank_EndThread ; if nothing is queued up, jump to cleanup
ld a, LOW(DoInAsyncVBlank_ExitThread)
ld [INTERRUPT_LCD], a ld [INTERRUPT_LCD], a
ld a, HIGH(DoInAsyncVBlank_ExitThread) ld a, HIGH(Async_ExitThread)
ld [INTERRUPT_LCD+1], a ld [INTERRUPT_LCD+1], a
ld a, SAFE_ASYNC_END ; CHANGE ME TO ADJUST SAFE TRANSFER TIMING ld a, SAFE_ASYNC_END ; CHANGE ME TO ADJUST SAFE TRANSFER TIMING
ld [rLYC], a ; set lcd interrupt handler to EXIT SAFE MODE on line 153 ld [rLYC], a ; set lcd interrupt handler to EXIT SAFE MODE on line 153
; save main thread stack pointer
ld hl, sp+0
ld a, l
ld [vAsyncMainSP], a
ld a, h
ld [vAsyncMainSP+1], a
; what if our async thread calls return? ; load side thread stack pointer
; we need to have a PC to return to. if that happens, we will want to ld a, [vAsyncThreadSP]
; reti.
ld hl, DoInAsyncVBlank_EarlyReturn
push hl ; address for if the thread retrns
ldh a, [vAsyncPC]
ld l, a ld l, a
ldh a, [vAsyncPC+1] ld a, [vAsyncThreadSP+1]
ld h, a ld h, a
push hl ; put vAsyncPC on the stack! for jumping to it! ld sp, hl
; stack looks like: vasyncpc, early return, af, de, bc, hll, SMC interrput pc, hardwired interrupt pc, outer context pc
ldh a, [vAsyncAF] ; pop registers
ld l, a ; canonical ordering to push should be: AF, BC, DE, HL,
ldh a, [vAsyncAF+1] ; pop is HL, DE, BC, AF
ld h, a pop hl
push hl pop de
pop bc
ldh a, [vAsyncHL] pop af
ld l, a
ldh a, [vAsyncHL+1] reti ; "return" to the vAsyncPC wee put on the stack previously.
ld h, a
ldh a, [vAsyncDE]
ld e, a
ldh a, [vAsyncDE+1]
ld d, a
ldh a, [vAsyncBC]
ld c, a
ldh a, [vAsyncBC+1]
ld b, a
pop af; putting vAsyncAF into af requires this hoop-jumping
ei
ret ; "return" to the vAsyncPC wee put on the stack previously.
; this is more or less a jump, not a return. ; this is more or less a jump, not a return.
; is that the source of our problems? ; is that the source of our problems?
; after this instruction executes, stack looks like: ; after this instruction executes, stack looks like:
; early return, af, de, bc, hl, PC (smc int), PC (hardwired int), PC (outer context) ; early return, af, de, bc, hl, PC (smc int), PC (hardwired int), PC (outer context)
; and we'll be in the async thread, executing ; and we'll be in the async thread, executing
Async_ExitThread:
; save interrupt registers (AF, BC, DE, HL)
push af
push bc
push de
push hl
DoInAsyncVBlank_EarlyReturn: ;af, de, bc, hl, c113 (SMC interrupt pc), 004b (hardwired interrput pc), thread pc, return
; stack:
; af, de, bc, hl, PC (smc int @ LYC90), PC (hw int @ LYC 90), PC (outer context)
;PRINTln "early return handle is ", DoInAsyncVBlank_EarlyReturn
; save state of registers
di
push af
ld a, l ld a, LOW(Async_EnterThread)
ldh [vAsyncHL], a
ld a, h
ldh [vAsyncHL+1], a
ld a, e
ldh [vAsyncDE], a
ld a, d
ldh [vAsyncDE+1], a
ld a, c
ldh [vAsyncBC], a
ld a, b
ldh [vAsyncBC+1], a
pop hl
ld a, l
ldh [vAsyncAF], a
ld a, h
ldh [vAsyncAF+1], a
; set pu the next call!
ldh a, [vAsyncNext]
ldh [vAsyncPC], a
ldh a, [vAsyncNext+1]
ldh [vAsyncPC+1], a ; put next into pc
ldh a, [vAsyncAfter]
ldh [vAsyncNext], a
ldh a, [vAsyncAfter+1]
ldh [vAsyncNext+1], a ; puut after into next
ld a, 0
ldh [vAsyncAfter], a ; unless this gets overwritten later, end execution after that
ldh [vAsyncAfter+1], a
ld a, LOW(DoInAsyncVBlank_EnterThread) ; set up next call
ld [INTERRUPT_LCD], a ld [INTERRUPT_LCD], a
ld a, HIGH(DoInAsyncVBlank_EnterThread) ld a, HIGH(Async_EnterThread)
ld [INTERRUPT_LCD+1], a ld [INTERRUPT_LCD+1], a
ld a, SAFE_ASYNC_START ld a, SAFE_ASYNC_START ; CHANGE ME TO ADJUST SAFE TRANSFER TIMING
ld [rLYC], a ld [rLYC], a ; set lcd interrupt handler to EXIT SAFE MODE on line 153
; save side thread stack pointer
ld hl, sp+0
ld a, l
ld [vAsyncThreadSP], a
ld a, h
ld [vAsyncThreadSP+1], a
; load main thread stack pointer
ld a, [vAsyncMainSP]
ld l, a
ld a, [vAsyncMainSP+1]
ld h, a
ld sp, hl
; pop registers
; canonical ordering to push should be: AF, BC, DE, HL,
; pop is HL, DE, BC, AF
pop hl
pop de
pop bc
pop af
reti
Async_EarlyReturn:
di
; don't care about current registers bc we're done executing.
; store side thread SP, so everyone knows that the side thread stack is empty
ld hl, sp+0
ld a, l
ld [vAsyncThreadSP], a
ld a, h
ld [vAsyncThreadSP+1], a
; unset next call
ld hl, rIE
res 1, [hl] ; disable vblank
ld hl, rIF
res 1, [hl] ; clear the interrupt
; load main thread stack pointer
ld a, [vAsyncMainSP]
ld l, a
ld a, [vAsyncMainSP+1]
ld h, a
ld sp, hl
; restore the pre-interrupt registers, return and enable interrupts ; restore the pre-interrupt registers, return and enable interrupts
pop af pop af
pop de pop de
pop bc pop bc
pop hl pop hl
reti reti
DoInAsyncVBlank_EndThread:
; end execution of the thread by disabling the interrupt
; and restore the state for the outer thread Async_CleanUpThread:
ld hl, rIE ;stack looks like:
res 1, [hl] ; disable STAT/vblank interrupt ;hl, de, bc, af, c113 (SMC int @ LYC 90 pc), 004b (hw int @ LYC 90 pc), outer context pc
pop af pop hl
pop de pop de
pop bc pop bc
pop hl pop af
reti
DoInAsyncVBlank_ExitThread:
; at this point, it's an interrpt being called from inside the interrupt
; our stack probably looks like this:
; PC (smc int), PC (hardwired int), PC (inside thread), early return, af, de, bc, hl, PC (smc int), PC (hardwired int), PC (outer context)
; first, save the interrpt thread registers.
push af
ld a, l reti
ldh [vAsyncHL], a
ld a, h
ldh [vAsyncHL+1], a
ld a, e
ldh [vAsyncDE], a
ld a, d
ldh [vAsyncDE+1], a
ld a, c
ldh [vAsyncBC], a
ld a, b
ldh [vAsyncBC+1], a
pop hl
ld a, l
ldh [vAsyncAF], a
ld a, h
ldh [vAsyncAF+1], a
;god i'm such a genius
; this was called as an interrupt inside the interrupt
;so our stack looks like this:
; PC (smc int), PC (hardwired int), PC (inside thread), early return, af, de, bc, hl, PC (smc int), PC (hardwired int), PC (outer context)
; we've got the two PCs from the inner interrupt call stack.
; get rid of them! we're running without handrails! i know what i'm doing! I hope!
pop hl
pop hl
; now, save the interrupt thread's pc., which is on the stack from this
; interrupt being called.
pop hl
ld a, l
ldh [vAsyncPC], a
ld a, h
ldh [vAsyncPC+1], a
; now we are done with this entire execution of thread. now we need to set up
; the next execution of this thread.
ld a, LOW(DoInAsyncVBlank_EnterThread)
ld [INTERRUPT_LCD], a
ld a, HIGH(DoInAsyncVBlank_EnterThread)
ld [INTERRUPT_LCD+1], a
ld a, SAFE_ASYNC_START ; CHANGE ME TO ADJUST SAFE TRANSFER TIMING
ld [rLYC], a ; set lcd interrupt handler to EXIT SAFE MODE on line 153
;at present the stack looks like:
; early return, af, de, bc, hl, pc (smc int @ LYC 90), pc (hardwired int at LYC 90), PC (outer context)
; pop the early return and discard it.
pop hl
; and finally, we can restore the state of the registers to what they were
; before this whole handler got called.
pop af
pop de
pop bc
pop hl
reti ; this is a proper return

View File

@ -1,9 +1,8 @@
LoadCardDataAsync: ; to be called as async LoadCardData:
LoadCardDataAsync:
ei ei
ld a, 1 ld a, [vSelectedCardIndex]
ldh [vBlocked], a ld [vPreviousCardIndex], a
ldh a, [vSelectedCardIndex]
ldh [vPreviousCardIndex], a
ld b, 0 ld b, 0
ld c, a ; load bc from a, the number of the card in the cards list ld c, a ; load bc from a, the number of the card in the cards list
@ -23,20 +22,7 @@ LoadCardDataAsync: ; to be called as async
ld h, b ld h, b
ld l, c ; hl now contains the address of the card data. ld l, c ; hl now contains the address of the card data.
ld a, LOW(.duringDraw)
ld [vAsyncNext], a
ld a, HIGH(.duringDraw)
ld [vAsyncNext+1], a
ld a, 0
ld [vAsyncAfter], a
ld [vAsyncAfter+1], a
di
nop
nop
ret
.duringDraw .duringDraw
di ; these function calls should be fast so we'll disable interrupts and do them
nop
; synchronously ; synchronously
; hl points to a card struct. ; hl points to a card struct.
@ -55,8 +41,6 @@ LoadCardDataAsync: ; to be called as async
ld de, $9800 + 32*16 + 10 ld de, $9800 + 32*16 + 10
call PrintString call PrintString
ei
; hl now contains the address after all the strings. ; hl now contains the address after all the strings.
; [hl+] and [hl+] read the length first, into bc ; [hl+] and [hl+] read the length first, into bc
ld a, [hl+] ld a, [hl+]
@ -74,22 +58,10 @@ LoadCardDataAsync: ; to be called as async
ld b, 16 ; height ld b, 16 ; height
ld c, 8 ; width ld c, 8 ; width
ld a, LOW(CopyTilesToMapThreadsafe) call CopyTilesToMapUnsafe
ld [vAsyncNext], a
ld a, HIGH(CopyTilesToMapThreadsafe) ld a, [vSelectedCardIndex]
ld [vAsyncNext+1], a ld [vPreviousCardIndex], a
ld a, LOW(.afterCopyTiles)
ld [vAsyncAfter], a
ld a, HIGH(.afterCopyTiles)
ld [vAsyncAfter+1], a
di
nop
nop
ret
.afterCopyTiles
ei
ldh a, [vSelectedCardIndex]
ldh [vPreviousCardIndex], a
ld b, 0 ld b, 0
ld c, a ; load bc from a, the number of the card in the cards list ld c, a ; load bc from a, the number of the card in the cards list
@ -108,13 +80,11 @@ LoadCardDataAsync: ; to be called as async
ld h, b ld h, b
ld l, c ; hl now contains the address of the card data. ld l, c ; hl now contains the address of the card data.
di
call PassList call PassList
call PassList call PassList
call PassList call PassList
call PassList call PassList
call PassList ; skip the strings call PassList ; skip the strings
ei
inc hl inc hl
inc hl ; skip tile map width inc hl ; skip tile map width
inc hl inc hl
@ -132,30 +102,8 @@ LoadCardDataAsync: ; to be called as async
ld l, e ; hl takes the source ld l, e ; hl takes the source
ld de, $9000 + VARIABLE_TILES_START*$10 ; always load tile data into the same spot in vram ld de, $9000 + VARIABLE_TILES_START*$10 ; always load tile data into the same spot in vram
ld a, LOW(CopyRangeUnsafe) call CopyRangeUnsafe
ld [vAsyncNext], a
ld a, HIGH(CopyRangeUnsafe)
ld [vAsyncNext+1], a
ld a, LOW(.afterLoadingTiles)
ld [vAsyncAfter], a
ld a, HIGH(.afterLoadingTiles)
ld [vAsyncAfter+1], a
di di
nop nop
nop
ret
.afterLoadingTiles
ei
ld a, 0
ldh [vBlocked], a
ld a, 0
ld [vAsyncNext], a
ld [vAsyncNext+1], a
ld [vAsyncAfter], a
ld [vAsyncAfter+1], a
di
nop
nop
ret ret

View File

@ -212,9 +212,6 @@ CopyRangeUnsafe: ; this is threadsafe but not vblank safe
ld a, b ld a, b
or a, c ; check if bc is zero or a, c ; check if bc is zero
jp nz, CopyRangeUnsafe jp nz, CopyRangeUnsafe
di
nop
nop
ret ret

View File

@ -1,6 +1,6 @@
ClockLFSR: ; uses af, bc and clocks one bit of the LFSR. ClockLFSR: ; uses af, bc and clocks one bit of the LFSR.
; at return time, a holds the bottom eight of lfsr state. ; at return time, a holds the bottom eight of lfsr state.
ldh a, [rLFSR] ; ld a, [rLFSR] ;
ld b, a ; b has shifted value ; 1 cycle ld b, a ; b has shifted value ; 1 cycle
srl b ; second tap is two shifts ; 2 cycles srl b ; second tap is two shifts ; 2 cycles
@ -21,12 +21,12 @@ ClockLFSR: ; uses af, bc and clocks one bit of the LFSR.
jr nz, .noComplementCarry ; 2 or 3 cycles jr nz, .noComplementCarry ; 2 or 3 cycles
ccf ; 1 cycle if prev was 2 cycles :) ccf ; 1 cycle if prev was 2 cycles :)
.noComplementCarry .noComplementCarry
ldh a, [rLFSR+1] ; 2 cycles ld a, [rLFSR+1] ; 2 cycles
rra ; 1 cycle ; this should populate with the carry flag rra ; 1 cycle ; this should populate with the carry flag
ldh [rLFSR+1], a ; 2 cycles ld [rLFSR+1], a ; 2 cycles
ldh a, [rLFSR] ; 2 cycles ld a, [rLFSR] ; 2 cycles
rra ; 1 cycle rra ; 1 cycle
ldh [rLFSR], a ; 2 cycles ld [rLFSR], a ; 2 cycles
ret ; 37 cycles total. can call roughly three of these per scanline ret ; 37 cycles total. can call roughly three of these per scanline
OneRandomByte: ; clocks LFSR 8 times so a is OneRandomByte: ; clocks LFSR 8 times so a is

View File

@ -1,6 +1,5 @@
; screen variables already ddefined in screencardread ; screen variables shared with screencardread
;DEF vPreviousCardIndex EQU VARIABLES_START ;DEF vPreviousCardIndex EQU VARIABLES_START
;def vBlocked equ vPreviousCardIndex + 1
ScreenCardBrowse: ScreenCardBrowse:
dw CardBrowseSetup dw CardBrowseSetup
@ -10,68 +9,54 @@ ScreenCardBrowse:
CardBrowseSetup: CardBrowseSetup:
ld a, 1 ld a, 1
ldh [vBlocked], a ld [vBlocked], a
ld a, LOW(RunDMA) ; zero out the OAM ld hl, .loadUIMap
ld [vAsyncNext], a call Async_Spawn_HL
ld a, HIGH(RunDMA)
ld [vAsyncNext+1], a
ld a, LOW(.loadUIMap)
ld [vAsyncAfter], a
ld a, HIGH(.loadUIMap)
ld [vAsyncAfter+1], a
ld a, HIGH(ZEROES)
ld de, $ffc0 ; arguments to the first async call.
call DoInAsyncVBlank
ret ret
.loadUIMap .loadUIMap
ld a, HIGH(ZEROES)
ld de, SAFE_DMA_LOCATION ; arguments to the first async call.
call RunDMA
ld hl, CardBrowse.UITilemap ; origin ld hl, CardBrowse.UITilemap ; origin
ld de, $9800 ; destination ld de, $9800 ; destination
ld b, 18 ; height ld b, 18 ; height
ld c, 20 ; width ld c, 20 ; width
ld a, LOW(CopyTilesToMapThreadsafe) call CopyTilesToMapUnsafe
ld [vAsyncNext], a
ld a, HIGH(CopyTilesToMapThreadsafe)
ld [vAsyncNext+1], a
ld a, LOW(LoadCardDataAsync) call LoadCardData
ld [vAsyncAfter], a
ld a, HIGH(LoadCardDataAsync)
ld [vAsyncAfter+1], a
ret ret
CardBrowseUpdate: CardBrowseUpdate:
ld hl, vTime ld hl, vTime
ldh a, [rDELTAT] ld a, [rDELTAT]
ld b, a ld b, a
ldh a, [vTime] ld a, [vTime]
add a, b add a, b
ldh [vTime], a ld [vTime], a
ldh a, [vTime+1] ld a, [vTime+1]
adc a, 0 adc a, 0
ldh [vTime+1], a ; increment time. when the 16bit time register is greater ld [vTime+1], a ; increment time. when the 16bit time register is greater
; than 4096 ($10_00) then one second has passed. so that's satisfied when ; than 4096 ($10_00) then one second has passed. so that's satisfied when
; vTime+1 is equal to or greater than $10 ; vTime+1 is equal to or greater than $10
ldh a, [vTime+1] ld a, [vTime+1]
cp a, $01 cp a, $01
jp c, .doneTimer ; if the timer is less than $0100, skip to end jp c, .doneTimer ; if the timer is less than $0100, skip to end
;otherwise reset the timer ;otherwise reset the timer
ld a, 0 ld a, 0
ldh [vTime], a ld [vTime], a
ldh [vTime+1], a ld [vTime+1], a
ld hl, SquaresTiles ld hl, SquaresTiles
ldh a, [vFrameCountSquares] ld a, [vFrameCountSquares]
inc a inc a
call ArrayClampLooping call ArrayClampLooping
ldh [vFrameCountSquares], a ld [vFrameCountSquares], a
.doneTimer .doneTimer
ld hl, rMYBTNP ld hl, rMYBTNP
@ -82,7 +67,7 @@ CardBrowseUpdate:
ret ret
.doneWithB .doneWithB
ldh a, [vSelectedCardIndex] ld a, [vSelectedCardIndex]
ld hl, rMYBTNP ld hl, rMYBTNP
bit 3, [hl] bit 3, [hl]
jp z, :+ ; skip the following code if down is not pressed jp z, :+ ; skip the following code if down is not pressed
@ -92,36 +77,40 @@ CardBrowseUpdate:
jp z, :+ ; skip the following code if up is not pressed jp z, :+ ; skip the following code if up is not pressed
dec a dec a
: :
ldh [vSelectedCardIndex], a ld [vSelectedCardIndex], a
ld hl, Cards ld hl, Cards
call ArrayClampLooping call ArrayClampLooping
ldh [vSelectedCardIndex], a ld [vSelectedCardIndex], a
ldh a, [vSelectedCardIndex] ld a, [vSelectedCardIndex]
ld hl, vPreviousCardIndex ld hl, vPreviousCardIndex
cp a, [hl] cp a, [hl]
ret z ; if the selected card diddn't change, nothing to do ret z ; if the selected card diddn't change, nothing to do
ldh a, [vBlocked] ld a, [vBlocked]
cp a, 0 cp a, 0
ret nz ret nz
ld a, LOW(LoadCardDataAsync) ld hl, LoadCardTask
ld [vAsyncAfter], a call Async_Spawn
ld a, HIGH(LoadCardDataAsync)
ld [vAsyncAfter+1], a
call DoInAsyncVBlank
ret ret
LoadCardTask:
ld a, 1
ld [vBlocked], a
call LoadCardData
ld a, 0
ld [vBlocked], a
ret
CardBrowseDraw: CardBrowseDraw:
; the card data is loaded asynchronously, initiated in CardReadUpdate ; the card data is loaded asynchronously, initiated in CardReadUpdate
ld hl, SquaresTiles ld hl, SquaresTiles
inc hl inc hl
ld b, 0 ld b, 0
ldh a, [vFrameCountSquares] ld a, [vFrameCountSquares]
ld c, a ld c, a
add hl, bc add hl, bc
add hl, bc add hl, bc

View File

@ -1,6 +1,5 @@
; screen variables ; screen variables
DEF vPreviousCardIndex EQU VARIABLES_START DEF vPreviousCardIndex EQU SCREEN_VARS_START+16
def vBlocked equ vPreviousCardIndex + 1
ScreenCardRead: ScreenCardRead:
dw CardReadSetup dw CardReadSetup
@ -10,53 +9,48 @@ ScreenCardRead:
CardReadSetup: CardReadSetup:
ld a, 1 ld a, 1
ldh [vBlocked], a ld [vBlocked], a
ld [vAsyncAfter+1], a ld hl, CardReadSetupAsyncTask
call Async_Spawn_HL
ret
CardReadSetupAsyncTask:
ld hl, UITilemap ; origin ld hl, UITilemap ; origin
ld de, $9800 ; destination ld de, $9800 ; destination
ld b, 18 ; height ld b, 18 ; height
ld c, 20 ; width ld c, 20 ; width
call CopyTilesToMapUnsafe
ld a, LOW(CopyTilesToMapThreadsafe) call ChangedCardTask
ld [vAsyncNext], a
ld a, HIGH(CopyTilesToMapThreadsafe)
ld [vAsyncNext+1], a
ld a, LOW(LoadCardDataAsync)
ld [vAsyncAfter], a
ld a, HIGH(LoadCardDataAsync)
ld [vAsyncAfter+1], a
call DoInAsyncVBlank
ret ret
CardReadUpdate: CardReadUpdate:
ld hl, vTime ld hl, vTime
ldh a, [rDELTAT] ld a, [rDELTAT]
ld b, a ld b, a
ldh a, [vTime] ld a, [vTime]
add a, b add a, b
ldh [vTime], a ld [vTime], a
ldh a, [vTime+1] ld a, [vTime+1]
adc a, 0 adc a, 0
ldh [vTime+1], a ; increment time. when the 16bit time register is greater ld [vTime+1], a ; increment time. when the 16bit time register is greater
; than 4096 ($10_00) then one second has passed. so that's satisfied when ; than 4096 ($10_00) then one second has passed. so that's satisfied when
; vTime+1 is equal to or greater than $10 ; vTime+1 is equal to or greater than $10
ldh a, [vTime+1] ld a, [vTime+1]
cp a, $01 cp a, $01
jp c, .doneTimer ; if the timer is less than $0100, skip to end jp c, .doneTimer ; if the timer is less than $0100, skip to end
;otherwise reset the timer ;otherwise reset the timer
ld a, 0 ld a, 0
ldh [vTime], a ld [vTime], a
ldh [vTime+1], a ld [vTime+1], a
ld hl, SquaresTiles ld hl, SquaresTiles
ldh a, [vFrameCountSquares] ld a, [vFrameCountSquares]
inc a inc a
call ArrayClampLooping call ArrayClampLooping
ldh [vFrameCountSquares], a ld [vFrameCountSquares], a
.doneTimer .doneTimer
ld hl, rMYBTNP ld hl, rMYBTNP
@ -67,7 +61,7 @@ CardReadUpdate:
ret ret
.doneWithB .doneWithB
ldh a, [vSelectedSpreadCard] ld a, [vSelectedSpreadCard]
ld hl, rMYBTNP ld hl, rMYBTNP
bit 1, [hl] bit 1, [hl]
jp z, :+ ; skip the following code if left is not pressed jp z, :+ ; skip the following code if left is not pressed
@ -77,39 +71,34 @@ CardReadUpdate:
jp z, :+ ; skip the following code if right is not pressed jp z, :+ ; skip the following code if right is not pressed
inc a inc a
: :
ldh [vSelectedSpreadCard], a ld [vSelectedSpreadCard], a
ldh a, [vCurrentSpread] ld a, [vCurrentSpread]
ld l, a ld l, a
ldh a, [vCurrentSpread+1] ld a, [vCurrentSpread+1]
ld h, a ld h, a
ldh a, [vSelectedSpreadCard] ld a, [vSelectedSpreadCard]
call ArrayClampLooping call ArrayClampLooping
ldh [vSelectedSpreadCard], a
ldh [vSelectedCardIndex], a
ldh a, [vSelectedCardIndex] ld [vSelectedSpreadCard], a
ld hl, vPreviousCardIndex ld hl, vPreviousSpreadCard
cp a, [hl] cp a, [hl]
ret z ; if the selected card diddn't change, nothing to do ret z ; if the selected card diddn't change, nothing to do
ldh a, [vBlocked] ld a, [vBlocked]
cp a, 0 cp a, 0
ret nz ret nz
ld a, LOW(LoadCardDataAsync) ld a, 1
ld [vAsyncAfter], a ld [vBlocked], a
ld a, HIGH(LoadCardDataAsync) ld hl, ChangedCardTask
ld [vAsyncAfter+1], a call Async_Spawn_HL
call DoInAsyncVBlank
ret ret
CardReadDraw: CardReadDraw:
ld hl, SquaresTiles ld hl, SquaresTiles
inc hl inc hl
ld b, 0 ld b, 0
ldh a, [vFrameCountSquares] ld a, [vFrameCountSquares]
ld c, a ld c, a
add hl, bc add hl, bc
add hl, bc add hl, bc
@ -121,23 +110,31 @@ CardReadDraw:
ld de, $8000+$100*16 + 1*16 ld de, $8000+$100*16 + 1*16
ld bc, (SquaresTileset8 - SquaresTileset7) / 8 ld bc, (SquaresTileset8 - SquaresTileset7) / 8
call CopyRangeUnsafeBy8s call CopyRangeUnsafeBy8s
; then draw the spread minimap
ldh a, [vCurrentSpread] ; the card data is loaded asynchronously, initiated in CardReadUpdate
ld c, a ret
ldh a, [vCurrentSpread+1]
ld b, a CardReadTeardown:
ld hl, $9800 + (32*1)+11 ret
ldh a, [vSelectedSpreadCard]
call DrawSpreadMinimap
ldh a, [vCurrentSpread] ChangedCardTask:
ld a, [vSelectedSpreadCard]
ld [vPreviousSpreadCard], a
ld a, [vCurrentSpread]
ld c, a
ld a, [vCurrentSpread+1]
ld b, a ; gett bc as cuurrent spread address
ld hl, $9800 + (32*1)+11
ld a, [vSelectedSpreadCard]
call DrawSpreadMinimap
ld a, [vCurrentSpread]
ld l, a ld l, a
ldh a, [vCurrentSpread+1] ld a, [vCurrentSpread+1]
ld h, a ld h, a
call PassList ; skip spread layout call PassList ; skip spread layout
ldh a, [vSelectedSpreadCard] ld a, [vSelectedSpreadCard]
or a, a or a, a
.loopThroughSpreadPositions .loopThroughSpreadPositions
jp z, .foundSpreadPositionDescription jp z, .foundSpreadPositionDescription
@ -151,11 +148,21 @@ CardReadDraw:
ld de, $9800 + 32*6 + 11 ld de, $9800 + 32*6 + 11
call PrintString call PrintString
; the card data is loaded asynchronously, initiated in CardReadUpdate ld hl, SHUFFLED_DECK+1
ret ld a, [vSelectedSpreadCard]
ld c, a
CardReadTeardown: ld b, 0
add hl, bc
ld a, [hl]
ld [vSelectedCardIndex], a
ld [vPreviousCardIndex], a
call LoadCardData
ld a, 0
ld [vBlocked], a
ret ret
UITilemap: UITilemap:
db $0e, $0a, $0a, $0a, $0a, $0a, $0a, $0a, $0a, $0f, $09, $02, $02, $02, $02, $02, $02, $02, $08, $01 db $0e, $0a, $0a, $0a, $0a, $0a, $0a, $0a, $0a, $0f, $09, $02, $02, $02, $02, $02, $02, $02, $08, $01

View File

@ -5,11 +5,12 @@ def vSelectedSpreadCard equ vSelectedSpreadIndex + 1 ; ff93
def vSelectedCardIndex equ vSelectedSpreadCard+1 ; ff94 def vSelectedCardIndex equ vSelectedSpreadCard+1 ; ff94
DEF vFrameCountSquares EQU vSelectedCardIndex+1 ; ff95 DEF vFrameCountSquares EQU vSelectedCardIndex+1 ; ff95
DEF vTime EQU vFrameCountSquares+1 ; 16bit ; ff96 DEF vTime EQU vFrameCountSquares+1 ; 16bit ; ff96
println "after vTime is ", vTime+2 ; ff98 def vBlocked EQU vTime+2
println "vBlocked is ", vBlocked ;
; screen-specific variables ; screen-specific variables
DEF vFrameCount1 EQU VARIABLES_START DEF vFrameCount1 EQU SCREEN_VARS_START
DEF vFrameCount2 equ vFrameCount1+1 DEF vFrameCount2 equ vFrameCount1+1
DEF vFrameCount3 EQU vFrameCount2+1 DEF vFrameCount3 EQU vFrameCount2+1
DEF vMenuIndex equ vFrameCount3+1 DEF vMenuIndex equ vFrameCount3+1
@ -118,24 +119,26 @@ MainMenuSetup_ScreenOff:
cp a, l cp a, l
jp nz, :- jp nz, :-
ld de, vTime+2 ld de, SAFE_DMA_LOCATION
ld a, $c0 ld a, $c0
call RunDMA call RunDMA
; set LCD and display registers ; set LCD and display registers
ld a, %11100100 ld a, %11100100
ld [rBGP], a ldh [rBGP], a
ld [rOBP0], a ldh [rOBP0], a
ld a, LCDCF_BLK21 | LCDCF_ON | LCDCF_BGON | LCDCF_OBJON | LCDCF_OBJ16 ld a, LCDCF_BLK21 | LCDCF_ON | LCDCF_BGON | LCDCF_OBJON | LCDCF_OBJ16
ldh [rLCDC], a ldh [rLCDC], a
ld a, 0 ld a, 0
ldh [vFrameCount1], a ; first starts at 0 ld [vFrameCount1], a ; first starts at 0
ldh [vTime], a ld [vTime], a
ldh [vTime+1], a ld [vTime+1], a
ldh [vMenuIndex], a ld [vMenuIndex], a
ldh [vMenuIndexPrevious], a ld [vMenuIndexPrevious], a
ld [vSelectedSpreadCard], a
; second starts at 1/3 length which is approximately L/2 - L/4 - L/8 + L/16 ? ; second starts at 1/3 length which is approximately L/2 - L/4 - L/8 + L/16 ?
@ -157,7 +160,7 @@ MainMenuSetup_ScreenOff:
srl b srl b
add a, b ; L - L/2 - L/4 + L/8 - L/16 + L/32 - L/64 + L/128 add a, b ; L - L/2 - L/4 + L/8 - L/16 + L/32 - L/64 + L/128
; that should be approx 1/3 of L ! ; that should be approx 1/3 of L !
ldh [vFrameCount2], a ld [vFrameCount2], a
; third starts at 2/3 length which is approximately L/2 - L/4 + L/8 - L/16 ? ; third starts at 2/3 length which is approximately L/2 - L/4 + L/8 - L/16 ?
ld hl, Coords ld hl, Coords
@ -178,7 +181,7 @@ MainMenuSetup_ScreenOff:
srl b srl b
sub a, b ; L - L/2 + L/4 - L/8 + L/16 - L/32 + L/64 - L/128 sub a, b ; L - L/2 + L/4 - L/8 + L/16 - L/32 + L/64 - L/128
; that should be just about 2/3 of L ! ; that should be just about 2/3 of L !
ldh [vFrameCount3], a ld [vFrameCount3], a
;ld hl, Coords ;ld hl, Coords
;ld a, [hl] ;ld a, [hl]
@ -186,7 +189,7 @@ MainMenuSetup_ScreenOff:
;ldh [vFrameCount4], a ;ldh [vFrameCount4], a
ld a, 0 ld a, 0
ldh [vFrameCountSquares], a ld [vFrameCountSquares], a
; load graphics into vram for deck face ; load graphics into vram for deck face
@ -202,7 +205,7 @@ MainMenuUpdate:
; if timer is max, turn off animation state and unblock? ; if timer is max, turn off animation state and unblock?
ld hl, rMYBTNP ld hl, rMYBTNP
ldh a, [vMenuIndex] ld a, [vMenuIndex]
bit 3, [hl] ; select the down key bit 3, [hl] ; select the down key
jp z, .doneWithDownInput ; skip the following code if down is not pressed jp z, .doneWithDownInput ; skip the following code if down is not pressed
inc a inc a
@ -213,7 +216,7 @@ MainMenuUpdate:
.doneWithUpInput .doneWithUpInput
ld hl, MenuCount ld hl, MenuCount
call ArrayClampLooping call ArrayClampLooping
ldh [vMenuIndex], a ld [vMenuIndex], a
ld hl, rMYBTNP ld hl, rMYBTNP
@ -230,7 +233,7 @@ MainMenuUpdate:
jp .doneWithMenuSelect jp .doneWithMenuSelect
.option1 .option1
ld a, 0 ld a, 0
ldh [vSelectedSpreadIndex], a ld [vSelectedSpreadIndex], a
ld hl, ScreenSpreadSelect ld hl, ScreenSpreadSelect
call ChangeScene call ChangeScene
ret ret
@ -240,56 +243,56 @@ MainMenuUpdate:
ret ret
.option3 .option3
ld a, 0 ld a, 0
ldh [vSelectedCardIndex], a ld [vSelectedCardIndex], a
ld hl, ScreenCardBrowse ld hl, ScreenCardBrowse
call ChangeScene call ChangeScene
ret ret
.doneWithMenuSelect .doneWithMenuSelect
ldh a, [rDELTAT] ld a, [rDELTAT]
ld b, a ld b, a
ldh a, [vTime] ld a, [vTime]
add a, b add a, b
ldh [vTime], a ld [vTime], a
ldh a, [vTime+1] ld a, [vTime+1]
adc a, 0 adc a, 0
ldh [vTime+1], a ; increment time. when the 16bit time register is greater ld [vTime+1], a ; increment time. when the 16bit time register is greater
; than 4096 ($10_00) then one second has passed. so that's satisfied when ; than 4096 ($10_00) then one second has passed. so that's satisfied when
; vTime+1 is equal to or greater than $10 ; vTime+1 is equal to or greater than $10
ldh a, [vTime+1] ld a, [vTime+1]
cp a, $01 cp a, $01
jp c, MainMenuUpdate_Done ; if the timer is less than $0100, skip to end jp c, MainMenuUpdate_Done ; if the timer is less than $0100, skip to end
;otherwise reset the timer ;otherwise reset the timer
ld a, 0 ld a, 0
ldh [vTime], a ld [vTime], a
ldh [vTime+1], a ld [vTime+1], a
ld hl, Coords ld hl, Coords
; and advance the frame counts ; and advance the frame counts
ldh a, [vFrameCount1] ld a, [vFrameCount1]
inc a inc a
call ArrayClampLooping call ArrayClampLooping
ldh [vFrameCount1], a ld [vFrameCount1], a
ldh a, [vFrameCount2] ld a, [vFrameCount2]
inc a inc a
call ArrayClampLooping call ArrayClampLooping
ldh [vFrameCount2], a ld [vFrameCount2], a
ldh a, [vFrameCount3] ld a, [vFrameCount3]
inc a inc a
call ArrayClampLooping call ArrayClampLooping
ldh [vFrameCount3], a ld [vFrameCount3], a
ld hl, SquaresTiles ld hl, SquaresTiles
ldh a, [vFrameCountSquares] ld a, [vFrameCountSquares]
inc a inc a
call ArrayClampLooping call ArrayClampLooping
ldh [vFrameCountSquares], a ld [vFrameCountSquares], a
@ -381,7 +384,7 @@ MainMenuDraw:
ld hl, SquaresTiles ld hl, SquaresTiles
inc hl inc hl
ld b, 0 ld b, 0
ldh a, [vFrameCountSquares] ld a, [vFrameCountSquares]
ld c, a ld c, a
add hl, bc add hl, bc
add hl, bc add hl, bc

View File

@ -1,7 +1,7 @@
; screen variables already ddefined in screencardread ; screen variables already ddefined in screencardread
;DEF vPreviousCardIndex EQU VARIABLES_START ;DEF vPreviousCardIndex EQU VARIABLES_START
;def vBlocked equ vPreviousCardIndex + 1 ;def vBlocked equ vPreviousCardIndex + 1
def vAnimationFrame EQU VARIABLES_START def vAnimationFrame EQU SCREEN_VARS_START
def vAnimationState EQU vAnimationFrame+1 def vAnimationState EQU vAnimationFrame+1
def vCurrentAnimation EQU vAnimationState+1 ; 2 bytes def vCurrentAnimation EQU vAnimationState+1 ; 2 bytes
def vShuffleIndex equ vCurrentAnimation+2 def vShuffleIndex equ vCurrentAnimation+2
@ -17,71 +17,44 @@ ShuffleSetup:
ld hl, SHUFFLED_DECK ld hl, SHUFFLED_DECK
ld a, [hl] ld a, [hl]
dec a dec a
ldh [vShuffleIndex], a ld [vShuffleIndex], a
ld a, 0 ld a, 0
ldh [vAnimationFrame], a ld [vAnimationFrame], a
ldh [vAnimationState], a ld [vAnimationState], a
ld hl, .asyncTask
call Async_Spawn_HL
ret
.asyncTask
ld a, LOW(ShuffleAnimationRight) ld a, LOW(ShuffleAnimationRight)
ldh [vCurrentAnimation], a ld [vCurrentAnimation], a
ld a, HIGH(ShuffleAnimationRight) ld a, HIGH(ShuffleAnimationRight)
ldh [vCurrentAnimation+1], a ld [vCurrentAnimation+1], a
ld a, LOW(RunDMA) ; zero out the OAM ld hl, ZEROES
ld [vAsyncNext], a ld de, MY_OAM
ld a, HIGH(RunDMA) ld bc, $100
ld [vAsyncNext+1], a
ld a, LOW(.loadUIMap)
ld [vAsyncAfter], a
ld a, HIGH(.loadUIMap)
ld [vAsyncAfter+1], a
ld a, HIGH(ZEROES)
ld de, vMenuIndexPrevious+2 ; arguments to the first async call.
call DoInAsyncVBlank
ld hl, ZEROES ; hl is source
ld de, $c000 ; de is destination
ld bc, $100 ; length to copy
call CopyRangeUnsafe call CopyRangeUnsafe
ret ld de, SAFE_DMA_LOCATION
ld a, HIGH(ZEROES)
.loadUIMap call RunDMA
ld hl, Shuffle.UITilemap ; origin ld hl, Shuffle.UITilemap ; origin
ld de, $9800 ; destination ld de, $9800 ; destination
ld b, 18 ; height ld b, 18 ; height
ld c, 20 ; width ld c, 20 ; width
call CopyTilesToMapUnsafe
ld a, LOW(CopyTilesToMapThreadsafe)
ld [vAsyncNext], a
ld a, HIGH(CopyTilesToMapThreadsafe)
ld [vAsyncNext+1], a
ld a, LOW(.loadTiles)
ld [vAsyncAfter], a
ld a, HIGH(.loadTiles)
ld [vAsyncAfter+1], a
ret
.loadTiles
ld hl, Shuffle.UITileData ld hl, Shuffle.UITileData
ld de, $9000 + VARIABLE_TILES_START*16 ld de, $9000 + VARIABLE_TILES_START*16
ld bc, Shuffle.UITileDataEnd - Shuffle.UITileData ld bc, Shuffle.UITileDataEnd - Shuffle.UITileData
call CopyRangeUnsafe
ld a, LOW(CopyRangeUnsafe)
ldh [vAsyncNext], a
ld a, HIGH(CopyRangeUnsafe)
ldh [vAsyncNext+1], a
ld a, LOW(.drawBigCard) ; manually drawing the Big Card
ld [vAsyncAfter], a ld hl, $9800 + $20*5 + 7
ld a, HIGH(.drawBigCard)
ld [vAsyncAfter+1], a
ret
.drawBigCard
ld hl, $9800 + $20*5 + 8
ld a, VARIABLE_TILES_START ld a, VARIABLE_TILES_START
ld [hl+], a ld [hl+], a
inc a inc a
@ -93,7 +66,6 @@ ShuffleSetup:
ld c, 32 - 4 ld c, 32 - 4
add hl, bc add hl, bc
inc a inc a
ld [hl+], a ld [hl+], a
inc a inc a
@ -159,7 +131,7 @@ ShuffleSetup:
ShuffleUpdate: ShuffleUpdate:
ld hl, vShuffleTime ld hl, vShuffleTime
ldh a, [rDELTAT] ld a, [rDELTAT]
ld b, a ld b, a
ld a, [hl] ld a, [hl]
add a, b add a, b
@ -171,7 +143,7 @@ ShuffleUpdate:
ld hl, vTime ld hl, vTime
ldh a, [rDELTAT] ld a, [rDELTAT]
ld b, a ld b, a
ld a, [hl] ld a, [hl]
add a, b add a, b
@ -192,10 +164,10 @@ ShuffleUpdate:
ld [hl], a ld [hl], a
ld hl, SquaresTiles ld hl, SquaresTiles
ldh a, [vFrameCountSquares] ld a, [vFrameCountSquares]
inc a inc a
call ArrayClampLooping call ArrayClampLooping
ldh [vFrameCountSquares], a ld [vFrameCountSquares], a
.doneTimer .doneTimer
@ -204,10 +176,10 @@ ShuffleUpdate:
ld a, 0 ld a, 0
cp a, [hl] cp a, [hl]
jr z, .noButtons jr z, .noButtons
ldh a, [rLFSR] ld a, [rLFSR]
ldh [rLFSR+1], a ; lfsr = (lfsr << 8) + (vShuffleTime & $ff) ld [rLFSR+1], a ; lfsr = (lfsr << 8) + (vShuffleTime & $ff)
ldh a, [vShuffleTime] ld a, [vShuffleTime]
ldh [rLFSR], a ld [rLFSR], a
.noButtons .noButtons
@ -221,14 +193,14 @@ ShuffleUpdate:
jp z, .doneWithRight jp z, .doneWithRight
ld a, 1 ld a, 1
ldh [vAnimationState], a ld [vAnimationState], a
ld a, 0 ld a, 0
ldh [vAnimationFrame], a ld [vAnimationFrame], a
ld a, LOW(ShuffleAnimationRight) ld a, LOW(ShuffleAnimationRight)
ldh [vCurrentAnimation], a ld [vCurrentAnimation], a
ld a, HIGH(ShuffleAnimationRight) ld a, HIGH(ShuffleAnimationRight)
ldh [vCurrentAnimation+1], a ld [vCurrentAnimation+1], a
call DoSomeShuffling call DoSomeShuffling
.doneWithRight .doneWithRight
@ -236,43 +208,43 @@ ShuffleUpdate:
jp z, .doneWithLeft jp z, .doneWithLeft
ld a, 1 ld a, 1
ldh [vAnimationState], a ld [vAnimationState], a
ld a, 0 ld a, 0
ldh [vAnimationFrame], a ld [vAnimationFrame], a
ld a, LOW(ShuffleAnimationRightReturn) ld a, LOW(ShuffleAnimationRightReturn)
ldh [vCurrentAnimation], a ld [vCurrentAnimation], a
ld a, HIGH(ShuffleAnimationRightReturn) ld a, HIGH(ShuffleAnimationRightReturn)
ldh [vCurrentAnimation+1], a ld [vCurrentAnimation+1], a
.doneWithLeft .doneWithLeft
;animation logic! ;animation logic!
ldh a, [vCurrentAnimation] ld a, [vCurrentAnimation]
ld l, a ld l, a
ldh a, [vCurrentAnimation+1] ld a, [vCurrentAnimation+1]
ld h, a ; fetch current animation ld h, a ; fetch current animation
ldh a, [vAnimationState] ld a, [vAnimationState]
or a, a or a, a
jp z, .doneWithAnimation jp z, .doneWithAnimation
ldh a, [vAnimationFrame] ld a, [vAnimationFrame]
inc a inc a
cp a, [hl] cp a, [hl]
jp nz, .animNotDone jp nz, .animNotDone
dec a dec a
ldh [vAnimationFrame], a ld [vAnimationFrame], a
ld a, 0 ld a, 0
ld [vAnimationState], a ld [vAnimationState], a
ldh a, [vAnimationFrame] ld a, [vAnimationFrame]
.animNotDone .animNotDone
call ArrayClampLooping call ArrayClampLooping
ldh [vAnimationFrame], a ld [vAnimationFrame], a
.doneWithAnimation .doneWithAnimation
inc hl inc hl
ld b, 0 ld b, 0
ldh a, [vAnimationFrame] ld a, [vAnimationFrame]
ld c, a ld c, a
add hl, bc add hl, bc
add hl, bc ; two bytes per entry add hl, bc ; two bytes per entry
@ -288,17 +260,21 @@ ShuffleUpdate:
ld a, 32 ld a, 32
ld e, a ld e, a
ld hl, $c000 ld hl, $c000
call DrawWholeCard call DrawWholeCard ; hl memory location, b y, c x, e width, d wiggle
ret ret
ShuffleDraw: ShuffleDraw:
ld de, SAFE_DMA_LOCATION ; safe bytes in hram for dma code to live at
ld a, HIGH(MY_OAM)
call RunDMA
; the card data is loaded asynchronously, initiated in CardReadUpdate ; the card data is loaded asynchronously, initiated in CardReadUpdate
ld hl, SquaresTiles ld hl, SquaresTiles
inc hl inc hl
ld b, 0 ld b, 0
ldh a, [vFrameCountSquares] ld a, [vFrameCountSquares]
ld c, a ld c, a
add hl, bc add hl, bc
add hl, bc add hl, bc
@ -310,10 +286,7 @@ ShuffleDraw:
ld de, $8000+$100*16 + 1*16 ; tile number $101 is the sliding background ld de, $8000+$100*16 + 1*16 ; tile number $101 is the sliding background
ld bc, (SquaresTileset8 - SquaresTileset7) / 8 ld bc, (SquaresTileset8 - SquaresTileset7) / 8
call CopyRangeUnsafeBy8s call CopyRangeUnsafeBy8s
ld de, vMenuIndexPrevious+2 ; safe bytes in hram for dma code to live at
ld a, $c0
call RunDMA
ret ret
@ -331,7 +304,7 @@ DoSomeShuffling:
OneSwap: ; shuffles once and decrements vshuffleindex OneSwap: ; shuffles once and decrements vshuffleindex
; vShuffleIndex holds the index of the next card to swap with something ; vShuffleIndex holds the index of the next card to swap with something
ldh a, [vShuffleIndex] ld a, [vShuffleIndex]
cp a, 1 cp a, 1
jp z, .zeroIndex ; if we're swapping index 1 with index 0 skip it jp z, .zeroIndex ; if we're swapping index 1 with index 0 skip it
@ -344,15 +317,15 @@ OneSwap: ; shuffles once and decrements vshuffleindex
ld hl, SHUFFLED_DECK ld hl, SHUFFLED_DECK
call SwapCards ; arguments c and e as indices to swap, hl as array in memory call SwapCards ; arguments c and e as indices to swap, hl as array in memory
ldh a, [vShuffleIndex] ld a, [vShuffleIndex]
dec a dec a
ldh [vShuffleIndex], a ; decrement vshuffleindex so the next time around ld [vShuffleIndex], a ; decrement vshuffleindex so the next time around
; we do the next step of the shuffle ; we do the next step of the shuffle
ret ret
.zeroIndex .zeroIndex
ld a, [SHUFFLED_DECK] ld a, [SHUFFLED_DECK]
dec a dec a
ldh [vShuffleIndex], a ld [vShuffleIndex], a
ret ret

View File

@ -1,4 +1,4 @@
DEF vPreviousSpreadIndex EQU VARIABLES_START DEF vPreviousSpreadIndex EQU SCREEN_VARS_START
def vPreviousSpreadCard equ vPreviousSpreadIndex + 1 def vPreviousSpreadCard equ vPreviousSpreadIndex + 1
ScreenSpreadSelect: ScreenSpreadSelect:
@ -8,60 +8,40 @@ ScreenSpreadSelect:
dw SpreadSelectTeardown dw SpreadSelectTeardown
SpreadSelectSetup: SpreadSelectSetup:
ld a, 0 ld a, [vSelectedSpreadIndex]
ldh [vPreviousSpreadIndex], a ld [vPreviousSpreadIndex], a
ldh [vSelectedSpreadCard], a ld a, [vSelectedSpreadCard]
ldh [vPreviousSpreadCard], a ld [vPreviousSpreadCard], a
ld a, 1
ld [vBlocked], a
call UpdateCurrentSpread call UpdateCurrentSpread
ld a, LOW(RunDMA) ; zero out the OAM ld hl, .asyncTask
ld [vAsyncNext], a call Async_Spawn_HL
ld a, HIGH(RunDMA)
ld [vAsyncNext+1], a
ld a, LOW(.loadUIMap)
ld [vAsyncAfter], a
ld a, HIGH(.loadUIMap)
ld [vAsyncAfter+1], a
ld a, HIGH(ZEROES)
ld de, $ffc0 ; arguments to the first async call.
call DoInAsyncVBlank
ret ret
.loadUIMap .asyncTask ; setup task to be executed async
ld a, HIGH(ZEROES)
ld de, SAFE_DMA_LOCATION
call RunDMA
ld hl, SpreadSelectTilemap ld hl, SpreadSelectTilemap
ld de, $9800 ld de, $9800
ld b, 18 ld b, 18
ld c, 20 ld c, 20
call CopyTilesToMapUnsafe
ld a, LOW(CopyTilesToMapThreadsafe)
ld [vAsyncNext], a
ld a, HIGH(CopyTilesToMapThreadsafe)
ld [vAsyncNext+1], a
ld a, LOW(.loadFaceCardTiles)
ld [vAsyncAfter], a
ld a, HIGH(.loadFaceCardTiles)
ld [vAsyncAfter+1], a
ret
.loadFaceCardTiles
ld hl, CardPartTiles ld hl, CardPartTiles
ld de, $9000 - ($10)*16 ld de, $9000 - ($10)*16
ld bc, CardPartTilesEnd - CardPartTiles ld bc, CardPartTilesEnd - CardPartTiles
ld a, LOW(CopyRangeUnsafe) call CopyRangeUnsafe
ld [vAsyncNext], a
ld a, HIGH(CopyRangeUnsafe) call DrawSpreadTask
ld [vAsyncNext+1], a ld a, 0
ld a, LOW(DrawSpreadAsync) ld [vBlocked], a
ld [vAsyncAfter], a
ld a, HIGH(DrawSpreadAsync)
ld [vAsyncAfter+1], a
ret ret
SpreadSelectUpdate: SpreadSelectUpdate:
@ -92,10 +72,10 @@ SpreadSelectUpdate:
.doneUp .doneUp
ld hl, Spreads ld hl, Spreads
call ArrayClampLooping call ArrayClampLooping
ldh [vSelectedSpreadIndex], a ; save clamped index ld [vSelectedSpreadIndex], a ; save clamped index
; left and righgt ; left and righgt
ldh a, [vSelectedSpreadCard] ld a, [vSelectedSpreadCard]
ld hl, rMYBTNP ld hl, rMYBTNP
bit 1, [hl] bit 1, [hl]
jp z, .doneLeft ; skip the following code if left is not pressed jp z, .doneLeft ; skip the following code if left is not pressed
@ -113,43 +93,43 @@ SpreadSelectUpdate:
ld l, c ld l, c
; hl has current spread, a has index ; hl has current spread, a has index
call ArrayClampLooping call ArrayClampLooping
ldh [vSelectedSpreadCard], a ld [vSelectedSpreadCard], a
ld hl, vTime ld hl, vTime
ldh a, [rDELTAT] ld a, [rDELTAT]
ld b, a ld b, a
ldh a, [vTime] ld a, [vTime]
add a, b add a, b
ldh [vTime], a ld [vTime], a
ldh a, [vTime+1] ld a, [vTime+1]
adc a, 0 adc a, 0
ldh [vTime+1], a ; increment time. when the 16bit time register is greater ld [vTime+1], a ; increment time. when the 16bit time register is greater
; than 4096 ($10_00) then one second has passed. so that's satisfied when ; than 4096 ($10_00) then one second has passed. so that's satisfied when
; vTime+1 is equal to or greater than $10 ; vTime+1 is equal to or greater than $10
ldh a, [vTime+1] ld a, [vTime+1]
cp a, $01 cp a, $01
jp c, .doneTimer ; if the timer is less than $0100, skip to end jp c, .doneTimer ; if the timer is less than $0100, skip to end
;otherwise reset the timer ;otherwise reset the timer
ld a, 0 ld a, 0
ldh [vTime], a ld [vTime], a
ldh [vTime+1], a ld [vTime+1], a
ld hl, SquaresTiles ld hl, SquaresTiles
ldh a, [vFrameCountSquares] ld a, [vFrameCountSquares]
inc a inc a
call ArrayClampLooping call ArrayClampLooping
ldh [vFrameCountSquares], a ld [vFrameCountSquares], a
.doneTimer .doneTimer
ldh a, [vSelectedSpreadIndex] ld a, [vSelectedSpreadIndex]
ld hl, vPreviousSpreadIndex ld hl, vPreviousSpreadIndex
cp a, [hl] cp a, [hl]
jp nz, .spreadChanged ; update the spread if the spread changed jp nz, .spreadChanged ; update the spread if the spread changed
ldh a, [vSelectedSpreadCard] ld a, [vSelectedSpreadCard]
ld hl, vPreviousSpreadCard ld hl, vPreviousSpreadCard
cp a, [hl] cp a, [hl]
jp nz, .cardChanged ; update the spread if the card changed jp nz, .cardChanged ; update the spread if the card changed
@ -157,50 +137,41 @@ SpreadSelectUpdate:
ret ret
.spreadChanged .spreadChanged
ld a, [vAsyncPC] ld a, [vBlocked]
ld b, a cp a, 0
ld a, [vAsyncPC+1] ret nz ; early return if we're blocked
or a, b ld a, 1
ret nz ; early return if the async threadd is in use ld [vBlocked], a ; block!
ld a, [vSelectedSpreadIndex] ld a, [vSelectedSpreadIndex]
ld [vPreviousSpreadIndex], a ld [vPreviousSpreadIndex], a
ld a, 0 ld a, 0
ld [vSelectedSpreadCard], a ld [vSelectedSpreadCard], a
ld [vPreviousSpreadCard], a ld [vPreviousSpreadCard], a
call UpdateCurrentSpread call UpdateCurrentSpread
; execute an async call to DrawSpreadAsync. ; execute an async call to DrawSpreadAsync.
ld a, LOW(DrawSpreadAsync) ld hl, DrawSpreadTask
ld [vAsyncNext], a call Async_Spawn_HL
ld a, HIGH(DrawSpreadAsync)
ld [vAsyncNext+1], a
call DoInAsyncVBlank
ret ret
.cardChanged .cardChanged
ld a, [vAsyncPC] ld a, [vBlocked]
ld b, a cp a, 0
ld a, [vAsyncPC+1]
or a, b
ret nz ; early return if the async threadd is in use ret nz ; early return if the async threadd is in use
ld a, 1
ld [vBlocked], a ; block!
ld a, [vSelectedSpreadIndex] ld a, [vSelectedSpreadIndex]
ld [vPreviousSpreadIndex], a ld [vPreviousSpreadIndex], a
ld a, [vSelectedSpreadCard] ld a, [vSelectedSpreadCard]
ld [vPreviousSpreadCard], a ld [vPreviousSpreadCard], a
call UpdateCurrentSpread call UpdateCurrentSpread
; execute an async call to DrawSpreadAsync. ; execute an async call to DrawSpread.
ld a, LOW(DrawSpreadALittleAsync) ld hl, DrawSpreadTaskWithoutRefreshingBackgroundFirst
ld [vAsyncNext], a call Async_Spawn_HL
ld a, HIGH(DrawSpreadALittleAsync)
ld [vAsyncNext+1], a
call DoInAsyncVBlank
ret ret
@ -220,12 +191,10 @@ UpdateCurrentSpread:
add hl, de add hl, de
.skipCardDescription ; e has number of cards in spread .skipCardDescription ; e has number of cards in spread
di
call PassList call PassList
call PassList ; one card description has two strings call PassList ; one card description has two strings
dec e ; this will not work if the spreadd had zero cardss. i will overflow. dec e ; this will not work if the spreadd had zero cardss. i will overflow.
jp nz, .skipCardDescription jp nz, .skipCardDescription
ei
ld e, [hl] ; skip title of spread ld e, [hl] ; skip title of spread
inc hl inc hl
@ -243,101 +212,54 @@ UpdateCurrentSpread:
ld [vCurrentSpread+1], a ; save the current spread (hl) into vcurrentspread. ld [vCurrentSpread+1], a ; save the current spread (hl) into vcurrentspread.
ret ret
DrawSpreadAsync: DrawSpreadTask: ; draw the spread large in the middle of the screen, and descs
ldh a, [vSelectedSpreadIndex] ; clear the space to scrolling background tiles
ldh [vPreviousSpreadIndex], a
ld de, $9800 + 32*5 + 3 ld de, $9800 + 32*5 + 3
ld hl, ONES ld hl, ONES
ld b, 8 ld b, 8
ld c, 14 ld c, 14
call CopyTilesToMapUnsafe
ld a, LOW(CopyTilesToMapThreadsafe) DrawSpreadTaskWithoutRefreshingBackgroundFirst:
ld [vAsyncNext], a ; step past the spread layout to get to the spread description
ld a, HIGH(CopyTilesToMapThreadsafe)
ld [vAsyncNext+1], a
ld a, LOW(.afterClear)
ld [vAsyncAfter], a
ld a, HIGH(.afterClear)
ld [vAsyncAfter+1], a
di
nop
ret ; return from async execution now that we've registered desire
; to call copytilestomapthreadsafe
; and then drawspread
.afterClear
ld a, [vCurrentSpread] ld a, [vCurrentSpread]
ld l, a ld l, a
ld a, [vCurrentSpread+1] ld a, [vCurrentSpread+1]
ld h, a ld h, a
ld e, [hl] ; e holds length of spread ld e, [hl] ; e holds length of spread
di
call PassList ; step past spread layout call PassList ; step past spread layout
ei
nop
nop
.PassCardPositionDescriptions .PassCardPositionDescriptions
di
call PassList ; step past one pdesc call PassList ; step past one pdesc
call PassList ; step past two pdesc call PassList ; step past two pdesc
ei
dec e ; we've looked at one dec e ; we've looked at one
jp nz, .PassCardPositionDescriptions jp nz, .PassCardPositionDescriptions
.foundSpreadTitle
; now hl is pointing at the title string
ld de, $9800 + 32 + 1 ld de, $9800 + 32 + 1
ld a, LOW(PrintString) call PrintString
ld [vAsyncNext], a
ld a, HIGH(PrintString) ; now hl is pointing at the description
ld [vAsyncNext+1], a ld de, $9800 + (32*2) + 1
ld a, LOW(.afterTitle) call PrintString
ld [vAsyncAfter], a
ld a, HIGH(.afterTitle) call DrawSpreadCards
ld [vAsyncAfter+1], a
di ld a, 0
nop ld [vBlocked], a
ret ret
.afterTitle DrawSpreadCards:
ld de, $9800 + (32*2) + 1
ld a, LOW(PrintString)
ld [vAsyncNext], a
ld a, HIGH(PrintString)
ld [vAsyncNext+1], a
ld a, LOW(DrawSpreadALittleAsync)
ld [vAsyncAfter], a
ld a, HIGH(DrawSpreadALittleAsync)
ld [vAsyncAfter+1], a
di
nop
ret
DrawSpreadALittleAsync:
ld hl, $9800 + 32*5 + 3 ld hl, $9800 + 32*5 + 3
ldh a, [vSelectedSpreadCard] ld a, [vSelectedSpreadCard]
ld d, 0 ld d, 0
ld e, a ; e contains the selected index ld e, a ; e contains the selected index
call DrawSpreadBig ; draw the large cards for the spread
ld a, LOW(DrawSpreadBigAndThreadsafe)
ld [vAsyncNext], a
ld a, HIGH(DrawSpreadBigAndThreadsafe)
ld [vAsyncNext+1], a
ld a, LOW(.drawSpreadPositionDescription)
ld [vAsyncAfter], a
ld a, HIGH(.drawSpreadPositionDescription)
ld [vAsyncAfter+1], a
di
nop
ret
.drawSpreadPositionDescription .drawSpreadPositionDescription
di
ld a, [vCurrentSpread] ld a, [vCurrentSpread]
ld l, a ld l, a
ld a, [vCurrentSpread+1] ld a, [vCurrentSpread+1]
ld h, a ; hl points at beginning of card list ld h, a ; hl points at beginning of card postion list
call PassList ; hl points at first card description call PassList ; hl points at first card description
ld a, [vSelectedSpreadCard] ld a, [vSelectedSpreadCard]
ld e, a ld e, a
@ -349,41 +271,18 @@ DrawSpreadALittleAsync:
dec e dec e
jp nz, .stepForwardCardDescription jp nz, .stepForwardCardDescription
.printIt .printIt
ei
nop
nop
.drawFirstDescription
ld de, $9800+32*15 + 6 ld de, $9800+32*15 + 6
ld a, LOW(PrintString) call PrintString
ld [vAsyncNext], a
ld a, HIGH(PrintString)
ld [vAsyncNext+1], a
ld a, LOW(.drawSecondDescription)
ld [vAsyncAfter], a
ld a, HIGH(.drawSecondDescription)
ld [vAsyncAfter+1], a
di
nop
ret
.drawSecondDescription
ld de, $9800+32*16 + 6 ld de, $9800+32*16 + 6
ld a, LOW(PrintString) call PrintString
ld [vAsyncNext], a
ld a, HIGH(PrintString)
ld [vAsyncNext+1], a
ld a, 0
ld [vAsyncAfter], a
ld [vAsyncAfter+1], a
di
nop
ret ret
SpreadSelectDraw: SpreadSelectDraw:
ld hl, SquaresTiles ld hl, SquaresTiles
inc hl inc hl
ld b, 0 ld b, 0
ldh a, [vFrameCountSquares] ld a, [vFrameCountSquares]
ld c, a ld c, a
add hl, bc add hl, bc
add hl, bc add hl, bc
@ -400,11 +299,10 @@ SpreadSelectDraw:
SpreadSelectTeardown: SpreadSelectTeardown:
ret ret
DrawSpreadBigAndThreadsafe: DrawSpreadBig:
; hl for location on screen ; hl for location on screen
; current spread address in vCurrentSpread ; current spread address in vCurrentSpread
; e for index of selected card ; e for index of selected card
di
ld a, [vCurrentSpread] ld a, [vCurrentSpread]
ld c, a ld c, a
ld a, [vCurrentSpread+1] ld a, [vCurrentSpread+1]
@ -415,10 +313,7 @@ DrawSpreadBigAndThreadsafe:
ld d, a ; length of spread in d ld d, a ; length of spread in d
inc d inc d
.drawCards .drawCards
ei
nop
nop
di
dec d dec d
jp z, .doneWithSpread ; if we're drawing zero remaining cards, stop drawing jp z, .doneWithSpread ; if we're drawing zero remaining cards, stop drawing
inc bc ; step forward inc bc ; step forward
@ -451,22 +346,13 @@ DrawSpreadBigAndThreadsafe:
ld h, b ld h, b
ld l, c; retrieve vram address ld l, c; retrieve vram address
ei
nop
di
nop
nop
call DrawBigCardSelected call DrawBigCardSelected
.doneDrawingSpread .doneDrawingSpread
di
nop
nop
ret ret
DrawBigCard: ; starting from screen location hl, draw a card at DrawBigCard: ; starting from screen location hl, draw a card at
;the location described in a ;the location described in a
; saves de and is therefore not threadsafe
push de push de
ld d, a ld d, a
swap a swap a
@ -573,7 +459,7 @@ DrawSpreadMinimap:
pop hl pop hl
jp .drawCards jp .drawCards
.doneWithSpread ; stack has hl, bc, af at the time of jumping here .doneWithSpread
pop bc ; stack: af pop bc ; stack: af
pop af pop af
ld d, 0 ld d, 0

View File

@ -4,45 +4,54 @@
; moss for keeping me from working sixteen hours a day and burning out ; moss for keeping me from working sixteen hours a day and burning out
; yuri for letting me bounce ideas off you at all times ; yuri for letting me bounce ideas off you at all times
; 0xc100 CALL ; 0xc100 CALL
; 0xc101 LOW - SCENE_SETUP points to this ; 0xc101 LOW - SCENE_SETUP points to this
; 0xc102 HIGH ; 0xc102 HIGH
; 0xc103 RET ; 0xc103 RET
; 0xc104 CALL ... ; 0xc104 CALL ...
def MY_OAM equ $c000 def MY_OAM equ $c000
; $c100 - c120 call handles, scene stack and interrupt
DEF SCENE_SETUP EQU $c101 DEF SCENE_SETUP EQU $c101
DEF SCENE_UPDATE EQU SCENE_SETUP + 4 ; call then ret is 3+1 bytes DEF SCENE_UPDATE EQU SCENE_SETUP + 4 ; call then ret is 3+1 bytes
DEF SCENE_DRAW EQU SCENE_UPDATE + 4 DEF SCENE_DRAW EQU SCENE_UPDATE + 4
DEF SCENE_TEARDOWN EQU SCENE_DRAW + 4 DEF SCENE_TEARDOWN EQU SCENE_DRAW + 4
DEF INTERRUPT_LCD EQU SCENE_TEARDOWN + 4
DEF INTERRUPT_LCD EQU $c111 ; each of these sections is way bgger than it needs to be
def SHUFFLED_DECK equ $c200 ; location for the shuffled deck ; i doubt any of them will hold more than $20 bytes at all
def CARD_VARIABLES equ $c300 ; but might as well put them at round numbers for now
def ASYNC_VARS_START equ $c200 ; this space's layout defined manually in async.inc
def SYSTEM_VARS_START equ $c300 ; system variables like buttons pressed, rng, time
def GLOBAL_VARS_START equ $c400 ; defined mostly in mainmenu, program-wide state
def SCREEN_VARS_START equ $c500 ; per-screen variables like animation stuff
def CARD_VARS_START equ $c600 ; variables for animation of individual cards
def SHUFFLED_DECK equ $c700 ; location for the shuffled deck
def ZEROES equ $D000 def ZEROES equ $D000
def ONES equ $D200 def ONES equ $D200
DEF ASYNC_VARS_START equ $ff80 ; these are defined manually in async.inc ; allocating $8 spaces for system variables, currently only using $4 bytes
DEF SYSTEM_VARS_START equ ASYNC_VARS_START + $10
; allocating $8 spaces for system variables, currently only using $3 bytes
DEF rMYBTN EQU SYSTEM_VARS_START DEF rMYBTN EQU SYSTEM_VARS_START
DEF rMYBTNP EQU rMYBTN + 1 DEF rMYBTNP EQU rMYBTN + 1
DEF rDELTAT EQU rMYBTNP + 1 ; delta_t where $1000 = 1 second DEF rDELTAT EQU rMYBTNP + 1 ; delta_t where $1000 = 1 second
def rLFSR equ rDELTAT + 1 ; 16 bit def rLFSR equ rDELTAT + 1 ; 16 bit
DEF GLOBAL_VARS_START EQU SYSTEM_VARS_START + $8
; global app-wide variables go after GLOBAL_VARS_START. allocated $10 for them
def VARIABLES_START equ GLOBAL_VARS_START + $10
; screen-specific variables live after VARIABLES_START
; WRAM Layout looks like this: ; WRAM Layout looks like this:
; $c000 - $c100 OAM DMA source ; $c000 - $c100 OAM DMA source
; $c100 - $c114 self-modifying code interrupts ; $c100 - $c114 self-modifying code interrupts
; $c200 - $c21a shuffled deck ; $c200 - $c21a shuffled deck
; $c300 - $c400 card display variables ; $c300 - $c400 card display variables
; $c300-$c30f timers ; $c300 - $c30f timers
; $c300 - $c400 card display variables ; $c300 - $c400 card display variables
; $d000 - $d400 zeroes and ones, just because they're handy! ; $d000 - $d400 zeroes and ones, just because they're handy!
def SAFE_DMA_LOCATION equ $ffc1
def VARIABLE_TILES_START equ 26 def VARIABLE_TILES_START equ 26
@ -103,8 +112,8 @@ EntryPoint:
; initialize global variables ; initialize global variables
ld a, 0 ld a, 0
ldh [vSelectedSpreadIndex], a ld [vSelectedSpreadIndex], a
ldh [vSelectedCardIndex], a ld [vSelectedCardIndex], a
ld hl, Cards ld hl, Cards
ld b, [hl] ld b, [hl]
ld hl, SHUFFLED_DECK ld hl, SHUFFLED_DECK
@ -117,7 +126,7 @@ EntryPoint:
jr nz, .writeCard jr nz, .writeCard
ld a, %1010_1010 ld a, %1010_1010
ldh [rLFSR], a ld [rLFSR], a
; move on to framework stuff ; move on to framework stuff
@ -205,7 +214,7 @@ Loop:
sra a sra a
sra a sra a
add a, 64 add a, 64
ldh [rDELTAT], a ld [rDELTAT], a
xor a, a ; zero a out in one cycle xor a, a ; zero a out in one cycle
; store dpad and btn state in the rMYBTN register ; store dpad and btn state in the rMYBTN register
@ -228,12 +237,12 @@ Loop:
swap a swap a
or a, b or a, b
ld b, a ; put new input state in b ld b, a ; put new input state in b
ldh a, [rMYBTN] ; previous input state in a ld a, [rMYBTN] ; previous input state in a
cpl ; a holds buttons which weren't pressed last frame cpl ; a holds buttons which weren't pressed last frame
and a, b ; select buttons which were pressed this frame, but not last frame and a, b ; select buttons which were pressed this frame, but not last frame
ldh [rMYBTNP], a ; save that as btnp state ld [rMYBTNP], a ; save that as btnp state
ld a, b ; select buttons which were pressed this frame ld a, b ; select buttons which were pressed this frame
ldh [rMYBTN], a ; save that as btn state ld [rMYBTN], a ; save that as btn state
call SCENE_UPDATE - 1 ; hope this takes not too many scanlines! call SCENE_UPDATE - 1 ; hope this takes not too many scanlines!

Binary file not shown.

Binary file not shown.