some code documentation + memset macro

This commit is contained in:
giomba 2021-11-07 16:10:02 +01:00
parent b19754f3d5
commit 51477cff9d
4 changed files with 74 additions and 30 deletions

View File

@ -39,24 +39,23 @@ introreset SUBROUTINE
rts rts
statusIntro0 SUBROUTINE statusIntro0 SUBROUTINE
lda introYscroll ; arrives raster interrupt, move moustache one line below
.enter:
inc moustacheLine inc moustacheLine
lda $d011 lda $d011 ; load current vertical offset from VIC-II
and #$07 and #$07
cmp #$07 cmp #$07
beq .nextline beq .nextline ; if 7, then it is next text line
inc $d011 inc $d011 ; else setup moustache interrupt to trigger next raster line...
jsr setupMoustacheInterrupt jsr setupMoustacheInterrupt
rts rts ; ...and return: my job here is done
.nextline: .nextline:
lda $d011 lda $d011 ; reset raster offset to 0...
and #$f8 and #$f8
sta $d011 sta $d011
ldy #0 ldy #0 ; ... clear text line ...
lda #$80 lda #$80
.clearLineLoop: .clearLineLoop:
sta (dstPointer),y sta (dstPointer),y
@ -64,7 +63,7 @@ statusIntro0 SUBROUTINE
cpy #40 cpy #40
bne .clearLineLoop bne .clearLineLoop
clc clc ; ... move dstPointer to next text line ...
lda dstPointer lda dstPointer
adc #40 adc #40
sta dstPointer sta dstPointer
@ -72,7 +71,7 @@ statusIntro0 SUBROUTINE
adc #0 adc #0
sta dstPointer + 1 sta dstPointer + 1
ldy #$00 ldy #$00 ; ... and copy "GLG Programs" text to next text line
.glgLoop: .glgLoop:
lda GLGProgramsText,y lda GLGProgramsText,y
sta (dstPointer),y sta (dstPointer),y
@ -80,11 +79,10 @@ statusIntro0 SUBROUTINE
cpy #200 cpy #200
bne .glgLoop bne .glgLoop
dec introYscroll dec introYscroll ; remember that we are one line below
beq .next beq .next ; if we reached the end of the vertical scroll, advance status
jsr setupMoustacheInterrupt
jsr setupMoustacheInterrupt ; else just continue with the moustache
rts rts
.next: .next:
@ -106,6 +104,7 @@ setupMoustacheInterrupt SUBROUTINE
rts rts
.moustacheInterruptH: .moustacheInterruptH:
; "higher" moustache interrupt (on the right of the screen)
; +36 ; +36
dec $d019 ; +42, EOI dec $d019 ; +42, EOI
lda #$02 ; +44, color lda #$02 ; +44, color
@ -139,12 +138,13 @@ setupMoustacheInterrupt SUBROUTINE
sty $315 sty $315
clc clc
lda moustacheLine lda moustacheLine
adc #23 adc #23 ; "lower" moustache is 23 raster lines below higher one
sta $d012 sta $d012
jmp $ea31 jmp $ea31
.moustacheInterruptL: .moustacheInterruptL:
; "lower" moustache interrupt (on the left of the screen)
; +36 ; +36
dec $d019 ; +42, EOI dec $d019 ; +42, EOI
inc $0800 ; +48, timing inc $0800 ; +48, timing
@ -176,7 +176,7 @@ setupMoustacheInterrupt SUBROUTINE
inc $0800 ; +18, timing inc $0800 ; +18, timing
sta $d020 ; +22, color sta $d020 ; +22, color
ldx #<irq ldx #<irq ; restore main raster interrupt handler
ldy #>irq ldy #>irq
stx $314 stx $314
sty $315 sty $315
@ -185,7 +185,7 @@ setupMoustacheInterrupt SUBROUTINE
jmp $ea31 jmp $ea31
GLGProgramsText: GLGProgramsText: ; fancy PETSCII-looking brand name
BYTE #$80,#$80,#$80,#$80,#$80,#$80,#$80,#$f0,#$f4,#$80,#$80,#$80,#$f0,#$f4,#$80,#$80,#$f0,#$f4,#$f1,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80 BYTE #$80,#$80,#$80,#$80,#$80,#$80,#$80,#$f0,#$f4,#$80,#$80,#$80,#$f0,#$f4,#$80,#$80,#$f0,#$f4,#$f1,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80
BYTE #$80,#$80,#$80,#$80,#$80,#$80,#$80,#$f5,#$80,#$80,#$f5,#$80,#$f5,#$80,#$80,#$80,#$f5,#$80,#$f5,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$f1,#$80,#$80,#$80,#$f0,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4 BYTE #$80,#$80,#$80,#$80,#$80,#$80,#$80,#$f5,#$80,#$80,#$f5,#$80,#$f5,#$80,#$80,#$80,#$f5,#$80,#$f5,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$f1,#$80,#$80,#$80,#$f0,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4
BYTE #$80,#$80,#$80,#$80,#$80,#$80,#$80,#$f5,#$80,#$f5,#$f5,#$80,#$f5,#$80,#$f5,#$80,#$fd,#$f4,#$f3,#$f0,#$f0,#$f1,#$f0,#$f1,#$f0,#$f0,#$fc,#$f0,#$fb,#$f1,#$f2,#$f1,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80 BYTE #$80,#$80,#$80,#$80,#$80,#$80,#$80,#$f5,#$80,#$f5,#$f5,#$80,#$f5,#$80,#$f5,#$80,#$fd,#$f4,#$f3,#$f0,#$f0,#$f1,#$f0,#$f1,#$f0,#$f0,#$fc,#$f0,#$fb,#$f1,#$f2,#$f1,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80
@ -193,10 +193,11 @@ GLGProgramsText:
BYTE #$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$fa,#$f4,#$f4,#$f4,#$f4,#$f3,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$f3,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80 BYTE #$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$f4,#$fa,#$f4,#$f4,#$f4,#$f4,#$f3,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$f3,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80,#$80
statusIntro1 SUBROUTINE statusIntro1 SUBROUTINE
lda $d011 ; continue moving moustaches down, up to 4 raster lines (middle of text)
lda $d011
and #$07 and #$07
cmp #$04 cmp #$04
beq .next beq .next ; if interrupt is in the middle, don't move it anymore, and...
inc $d011 inc $d011
inc moustacheLine inc moustacheLine
@ -205,9 +206,9 @@ statusIntro1 SUBROUTINE
rts rts
.next: .next:
jsr setupMoustacheInterrupt jsr setupMoustacheInterrupt ; ... always remember to display moustache, anyhow ...
lda counter lda counter ; wait for song synchronization up to interrupt $0080
cmp #$80 cmp #$80
bne .end bne .end
lda counter + 1 lda counter + 1
@ -422,13 +423,15 @@ statusMenuReset SUBROUTINE
cpy #80 cpy #80
bne .lastlineColorLoop bne .lastlineColorLoop
; Print Game Title ; Print Game Title: big "SNAKE"
; color first
MEMSET #$d800, #$02, #200
; actual "text"
lda #$00 lda #$00
sta dstPointer sta dstPointer
lda #$04 lda #$04
sta dstPointer + 1 sta dstPointer + 1
; Print big "SNAKE"
ldx #<SnakeText ldx #<SnakeText
ldy #>SnakeText ldy #>SnakeText
stx srcPointer stx srcPointer
@ -474,17 +477,24 @@ statusMenuReset SUBROUTINE
sta dstScreenPointer + 1 sta dstScreenPointer + 1
jsr printString jsr printString
lda #$f2 ; boat-shaped horizontal line (rounded edges toward the top)
; this overwrites the "present" word from the intro
lda #$f2 ; 3rd quadrant
sta $540 sta $540
lda #$f3 lda #$f3 ; 4th quadrant
sta $567 sta $567
lda #$07 ; color for edges
sta $540+$d800-$400
sta $567+$d800-$400
ldy #$1 ldy #$1
lda #$f4 .boatLineLoop:
.cancelPresent: lda #$f4 ; horizontal line
sta $540,y sta $540,y
lda #$07
sta $540+$d800-$400,y
iny iny
cpy #39 cpy #39
bne .cancelPresent bne .boatLineLoop
lda #$05 lda #$05
sta XCharOffset sta XCharOffset
@ -517,6 +527,7 @@ setupXScrollInterrupt SUBROUTINE
rts rts
XScrollInterruptH SUBROUTINE XScrollInterruptH SUBROUTINE
lda $d016 lda $d016
and #$f8 and #$f8
ora XScrollOffset ora XScrollOffset

32
src/macro.asm Normal file
View File

@ -0,0 +1,32 @@
SEG zeropageSegment
ptrDstStart:
WORD
ptrDstEnd:
WORD
MACRO MEMSET
SEG programSegment
clc
lda <{1}
sta ptrDstStart
adc <({3} + 1)
sta ptrDstEnd
lda >{1}
sta ptrDstStart + 1
adc >({3} + 1)
sta ptrDstEnd + 1
lda {2}
ldy #0
.loop:
sta (ptrDstStart),y
inc ptrDstStart
bne .skipInc
inc ptrDstStart + 1
.skipInc:
ldx ptrDstStart
cpx ptrDstEnd
bne .loop
ldx ptrDstStart + 1
cpx ptrDstEnd + 1
bne .loop
ENDM

View File

@ -62,6 +62,7 @@ sidtune:
SEG.U dataSegment SEG.U dataSegment
org $cd00 org $cd00
INCLUDE "data.asm" INCLUDE "data.asm"
INCLUDE "macro.asm"
#if VERBOSE = 1 #if VERBOSE = 1
ECHO "End of Data segment. Space left:",($ce00 - .) ECHO "End of Data segment. Space left:",($ce00 - .)
#endif #endif

View File

@ -120,7 +120,7 @@ menu SUBROUTINE
sta status ; put machine into menu status sta status ; put machine into menu status
jmp .menu ; and go there waiting for keypress jmp .menu ; and go there waiting for keypress
; Interrupt Handler ; Main Raster Interrupt Handler
; ---------------------------------------------------------------------- ; ----------------------------------------------------------------------
irq SUBROUTINE irq SUBROUTINE
; Things that must be done every interrupt (50Hz) ; Things that must be done every interrupt (50Hz)