magic moustaches fixed

This commit is contained in:
giomba 2021-04-14 09:50:46 +02:00
parent a41ae70993
commit 493d69f669
5 changed files with 94 additions and 100 deletions

View File

@ -2,8 +2,42 @@
LASTINIT SET . LASTINIT SET .
#endif #endif
; Currently statusIntro0 is the same as statusIntro1 introreset SUBROUTINE
; statusIntro1 has just been reserved for future use jsr multicolorOff
jsr clearScreen
; Set screen colors
lda #0
sta $d020 ; overscan
sta $d021 ; center
lda #14
sta introYscroll
; for "GLGPROGRAMS" at the beginning
ldx #$78
stx dstPointer
ldy #$04
sty dstPointer + 1
; GLGPROGRAMS color
ldy #$00
lda #$02
.colorLoop:
sta $d800,y
sta $d900,y
sta $da00,y
sta $db00,y
dey
bne .colorLoop
; first raster interrupt line, for moustaches
lda #68+19
sta rasterLineInt
rts
statusIntro0 SUBROUTINE statusIntro0 SUBROUTINE
lda introYscroll lda introYscroll
@ -15,7 +49,7 @@ statusIntro0 SUBROUTINE
cmp #$07 cmp #$07
beq .nextline beq .nextline
inc $d011 inc $d011
jsr setupMagicInterrupt jsr setupMoustacheInterrupt
rts rts
.nextline: .nextline:
lda $d011 lda $d011
@ -49,7 +83,7 @@ statusIntro0 SUBROUTINE
dec introYscroll dec introYscroll
beq .next beq .next
jsr setupMagicInterrupt jsr setupMoustacheInterrupt
rts rts
@ -58,10 +92,10 @@ statusIntro0 SUBROUTINE
sta status sta status
rts rts
setupMagicInterrupt SUBROUTINE setupMoustacheInterrupt SUBROUTINE
; Store in $314 address of our custom interrupt handler ; Store in $314 address of our custom interrupt handler
ldx #<.magicInterruptH ldx #<.moustacheInterruptH
ldy #>.magicInterruptH ldy #>.moustacheInterruptH
stx $314 stx $314
sty $315 sty $315
@ -71,15 +105,17 @@ setupMagicInterrupt SUBROUTINE
rts rts
.magicInterruptH: .moustacheInterruptH:
; +36 ; +36
dec $d019 ; +42, EOI dec $d019 ; +42, EOI
inc $d020 ; +48, white lda #$02 ; +44, color
bit $02 ; +51, timing sta $d020 ; +48, color
nop ; +53, timing nop ; +50, timing
nop ; +55, timing nop ; +52, timing
nop ; +57, timing nop ; +54, timing
dec $d020 ; +63, black bit $02 ; +57, timing
lda #$00 ; +59, color
sta $d020 ; +63, color
; second line, +0 ; second line, +0
inc $0800 ; + 6, timing inc $0800 ; + 6, timing
@ -89,14 +125,16 @@ setupMagicInterrupt SUBROUTINE
inc $0800 ; +30, timing inc $0800 ; +30, timing
inc $0800 ; +36, timing inc $0800 ; +36, timing
inc $0800 ; +42, timing inc $0800 ; +42, timing
inc $d020 ; +54, white lda #$02 ; +44, color
inc $0800 ; +60, timing sta $d020 ; +48, color
bit $02 ; +60, timing inc $0800 ; +54, timing
dec $d020 ; +63, black bit $02 ; +57, timing
lda #$00 ; +59, color
sta $d020 ; +63, color
; set raster beam low ; set raster beam low
ldx #<.magicInterruptL ldx #<.moustacheInterruptL
ldy #>.magicInterruptL ldy #>.moustacheInterruptL
stx $314 stx $314
sty $315 sty $315
clc clc
@ -106,20 +144,24 @@ setupMagicInterrupt SUBROUTINE
jmp $ea31 jmp $ea31
.magicInterruptL: .moustacheInterruptL:
; +36 ; +36
dec $d019 ; +42, EOI dec $d019 ; +42, EOI
inc $0800 ; +48, timing inc $0800 ; +48, timing
inc $0800 ; +54, timing inc $0800 ; +54, timing
inc $0800 ; +60, timing lda #$02 ; +56, color
bit $0800 ; +60, timing
bit $02 ; +63, timing bit $02 ; +63, timing
; newline ; newline
inc $d020 ; + 6, white sta $d020 ; + 4, color
lda #$00 ; + 6, timing
inc $0800 ; +12, timing inc $0800 ; +12, timing
inc $0800 ; +18, timing inc $0800 ; +18, timing
dec $d020 ; +24, black nop ; +20, timing
inc $0800 ; +30, timing sta $d020 ; +24, color
lda #$02 ; +26, color
bit $0800 ; +30, timing
inc $0800 ; +36, timing inc $0800 ; +36, timing
inc $0800 ; +42, timing inc $0800 ; +42, timing
inc $0800 ; +48, timing inc $0800 ; +48, timing
@ -128,10 +170,11 @@ setupMagicInterrupt SUBROUTINE
bit $02 ; +63, timing bit $02 ; +63, timing
; newline ; newline
inc $d020 ; +6, white sta $d020 ; + 4, color
lda #$00 ; + 6, color
inc $0800 ; +12, timing inc $0800 ; +12, timing
inc $0800 ; +18, timing inc $0800 ; +18, timing
dec $d020 ; +24, black sta $d020 ; +22, color
ldx #<irq ldx #<irq
ldy #>irq ldy #>irq
@ -157,12 +200,12 @@ statusIntro1 SUBROUTINE
inc $d011 inc $d011
inc rasterLineInt inc rasterLineInt
jsr setupMagicInterrupt jsr setupMoustacheInterrupt
rts rts
.next: .next:
jsr setupMagicInterrupt jsr setupMoustacheInterrupt
lda counter lda counter
cmp #$80 cmp #$80
@ -171,7 +214,14 @@ statusIntro1 SUBROUTINE
cmp #$00 cmp #$00
bne .end bne .end
; lda #ST_MENURESET ldy #$0
lda #$07
.colorLoop:
sta $d940,y
iny
cpy #200
bne .colorLoop
lda #ST_INTRO2 lda #ST_INTRO2
sta status sta status
@ -179,14 +229,14 @@ statusIntro1 SUBROUTINE
rts rts
statusIntro2 SUBROUTINE statusIntro2 SUBROUTINE
jsr setupMagicInterrupt jsr setupMoustacheInterrupt
; "RETROFFICINA" ; "RETROFFICINA"
lda #<introStringA1 lda #<introStringA1
sta srcStringPointer sta srcStringPointer
lda #>introStringA1 lda #>introStringA1
sta srcStringPointer + 1 sta srcStringPointer + 1
lda #$4e lda #$48
sta dstScreenPointer sta dstScreenPointer
lda #$05 lda #$05
sta dstScreenPointer + 1 sta dstScreenPointer + 1
@ -205,14 +255,14 @@ statusIntro2 SUBROUTINE
rts rts
statusIntro3 SUBROUTINE statusIntro3 SUBROUTINE
jsr setupMagicInterrupt jsr setupMoustacheInterrupt
; "AND" ; "AND"
lda #<introStringA2 lda #<introStringA2
sta srcStringPointer sta srcStringPointer
lda #>introStringA2 lda #>introStringA2
sta srcStringPointer + 1 sta srcStringPointer + 1
lda #$a3 lda #$a5
sta dstScreenPointer sta dstScreenPointer
lda #$05 lda #$05
sta dstScreenPointer + 1 sta dstScreenPointer + 1
@ -231,14 +281,14 @@ statusIntro3 SUBROUTINE
rts rts
statusIntro4 SUBROUTINE statusIntro4 SUBROUTINE
jsr setupMagicInterrupt jsr setupMoustacheInterrupt
; "GIOMBA" ; "GIOMBA"
lda #<introStringA3 lda #<introStringA3
sta srcStringPointer sta srcStringPointer
lda #>introStringA3 lda #>introStringA3
sta srcStringPointer + 1 sta srcStringPointer + 1
lda #$f1 lda #$f9
sta dstScreenPointer sta dstScreenPointer
lda #$05 lda #$05
sta dstScreenPointer + 1 sta dstScreenPointer + 1
@ -266,7 +316,7 @@ statusIntro4 SUBROUTINE
rts rts
statusIntro5 SUBROUTINE statusIntro5 SUBROUTINE
jsr setupMagicInterrupt jsr setupMoustacheInterrupt
; "PRESENT" ; "PRESENT"
lda #<introStringA4 lda #<introStringA4
@ -293,7 +343,7 @@ statusIntro5 SUBROUTINE
rts rts
statusIntro6 SUBROUTINE statusIntro6 SUBROUTINE
jsr setupMagicInterrupt jsr setupMoustacheInterrupt
; "A COMMODORE 64" ; "A COMMODORE 64"
lda #<introStringA5 lda #<introStringA5
@ -320,7 +370,7 @@ statusIntro6 SUBROUTINE
rts rts
statusIntro7 SUBROUTINE statusIntro7 SUBROUTINE
jsr setupMagicInterrupt jsr setupMoustacheInterrupt
; "VIDEOGAME" ; "VIDEOGAME"
lda #<introStringA6 lda #<introStringA6
@ -347,7 +397,7 @@ statusIntro7 SUBROUTINE
rts rts
statusIntro8 SUBROUTINE statusIntro8 SUBROUTINE
jsr setupMagicInterrupt jsr setupMoustacheInterrupt
; blank wait ; blank wait
lda counter lda counter
@ -406,14 +456,14 @@ statusMenuReset SUBROUTINE
sta dstScreenPointer + 1 sta dstScreenPointer + 1
jsr printString jsr printString
jsr setupMagicInterrupt ; never forget the magic jsr setupMoustacheInterrupt ; never forget the magic moustaches
lda #ST_MENU lda #ST_MENU
sta status sta status
rts rts
statusMenu SUBROUTINE statusMenu SUBROUTINE
jsr setupMagicInterrupt ; never forget to draw the lines jsr setupMoustacheInterrupt ; never forget to draw the moustaches
; Decrement interrupt divider for the intro ; Decrement interrupt divider for the intro
ldx introCounter ldx introCounter
dex dex

View File

@ -1,51 +0,0 @@
#if VERBOSE = 1
LASTINIT SET .
#endif
; Intro reset
; ----------------------------------------------------------------------
introreset SUBROUTINE
jsr multicolorOff
jsr clearScreen
; Set screen colors
lda #0
sta $d020 ; overscan
sta $d021 ; center
lda #14
sta introYscroll
; for "GLGPROGRAMS" at the beginning
ldx #$78
stx dstPointer
ldy #$04
sty dstPointer + 1
lda #68+19
sta rasterLineInt
lda #$01
ldy #$0
.colorLoop:
sta $d800,y
sta $d900,y
sta $da00,y
sta $db00,y
dey
bne .colorLoop
#if DEBUG = 1
ldy #$00
.charsetLoop:
tya
sta $4c8,y
iny
bne .charsetLoop
#endif
rts
#if VERBOSE = 1
ECHO "introreset.asm @ ",LASTINIT,"len:",(. - LASTINIT)
#endif

View File

@ -46,7 +46,6 @@ sidtune:
INCLUDE "initdata.asm" INCLUDE "initdata.asm"
INCLUDE "game.asm" INCLUDE "game.asm"
INCLUDE "gameover.asm" INCLUDE "gameover.asm"
INCLUDE "introreset.asm"
INCLUDE "subroutines.asm" INCLUDE "subroutines.asm"
INCLUDE "levels.asm" INCLUDE "levels.asm"
INCLUDE "intro1.asm" INCLUDE "intro1.asm"

View File

@ -141,12 +141,8 @@ irq SUBROUTINE
sta $d020 sta $d020
#endif #endif
; if interrupt raster line is not 0, then someone is doing some magic elsewhere ; Play music first -> no audio skew if computations are slow
lda $d012
;bne .noPlay
; Play music first -> no skew if computations are slow
jsr sidtune + 3 jsr sidtune + 3
.noPlay:
#if DEBUG = 1 #if DEBUG = 1
; Change background to visually see the ISR timing ; Change background to visually see the ISR timing

View File

@ -14,7 +14,7 @@ clearScreen SUBROUTINE
sta $500,x sta $500,x
sta $600,x sta $600,x
sta $700,x sta $700,x
lda #$0f lda #$05
sta $d800,x sta $d800,x
sta $d900,x sta $d900,x
sta $da00,x sta $da00,x