refactoring: wip: move code segments

This commit is contained in:
giomba 2021-11-07 18:14:59 +01:00
parent 51477cff9d
commit 85ac2cf971
13 changed files with 101 additions and 85 deletions

View File

@ -1,7 +1,7 @@
.POSIX: .POSIX:
ASM=$(wildcard src/*.asm) ASM=$(wildcard src/*.asm)
RES=res.bin/amour.sid res.bin/levels.bin res.bin/unlzg.bin RES=res.bin/amour2.sid res.bin/levels.bin res.bin/unlzg.bin
.PHONY: debug env clean all .PHONY: debug env clean all
@ -43,8 +43,8 @@ env:
bin/explodefont: util/explodefont.cpp bin/explodefont: util/explodefont.cpp
g++ -o bin/explodefont util/explodefont.cpp g++ -o bin/explodefont util/explodefont.cpp
res.bin/amour.sid: res.bin/amour2.sid:
cp res.org/amour.sid res.bin/amour.sid cp res.org/amour2.sid res.bin/amour2.sid
res.bin/levels.bin: bin/level res.org/levels.txt res.bin/levels.bin: bin/level res.org/levels.txt
bin/level < res.org/levels.txt > res.bin/levels.bin bin/level < res.org/levels.txt > res.bin/levels.bin

Binary file not shown.

BIN
res.org/amour2.sid Normal file

Binary file not shown.

View File

@ -2,11 +2,10 @@
SEG.U zeropageSegment SEG.U zeropageSegment
org $02 org $02
INCLUDE "zeropage.asm" SEG loaderSegment
SEG cartridgeSegment
org $8000 org $8000
SEG loaderSegment
cartridge SUBROUTINE cartridge SUBROUTINE
WORD .coldstart WORD .coldstart
WORD .warmstart WORD .warmstart
@ -55,4 +54,3 @@ cartridge SUBROUTINE
; force filler for the *PROM ; force filler for the *PROM
. = $9fff . = $9fff
BYTE #$ff BYTE #$ff

View File

@ -2,6 +2,7 @@
LASTINIT SET . LASTINIT SET .
#endif #endif
SEG programSegment
statusPlay: ; do Game statusPlay: ; do Game
; Check counter ; Check counter
ldx irqn ldx irqn

View File

@ -2,6 +2,12 @@
LASTINIT SET . LASTINIT SET .
#endif #endif
SEG zeropageSegment
; Generic src/dst copy pointers
srcPointer DS 2
dstPointer DS 2
SEG programSegment
introreset SUBROUTINE introreset SUBROUTINE
jsr multicolorOff jsr multicolorOff
@ -425,7 +431,7 @@ statusMenuReset SUBROUTINE
; Print Game Title: big "SNAKE" ; Print Game Title: big "SNAKE"
; color first ; color first
MEMSET #$d800, #$02, #200 MEMSET #$d800, #$02, #150
; actual "text" ; actual "text"
lda #$00 lda #$00
sta dstPointer sta dstPointer
@ -514,6 +520,11 @@ SnakeText:
HEX 80 80 80 80 80 80 80 80 80 80 80 a0 80 a0 80 80 a0 80 a0 80 80 a0 80 a0 a0 f7 80 a0 80 80 80 80 80 80 80 80 80 80 80 80 HEX 80 80 80 80 80 80 80 80 80 80 80 a0 80 a0 80 80 a0 80 a0 80 80 a0 80 a0 a0 f7 80 a0 80 80 80 80 80 80 80 80 80 80 80 80
HEX 80 80 80 80 80 80 80 80 f6 a0 a0 f9 80 f8 80 80 f8 80 f9 80 80 f8 80 a0 f8 f9 80 f8 a0 a0 f7 80 80 80 80 80 80 80 80 80 HEX 80 80 80 80 80 80 80 80 f6 a0 a0 f9 80 f8 80 80 f8 80 f9 80 80 f8 80 a0 f8 f9 80 f8 a0 a0 f7 80 80 80 80 80 80 80 80 80
;ParabolicSpaceChars:
; HEX 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 01 00 00 00 00 00 00 00 00 01 00 00 00 00 00 01 00 00 00 00 00 01 00 00 00 00 01 00 00 00 00 01 00 00 00 00 00 01 00 00 00 00 00 01 00 00 00 00 00 00 00 01 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
;ParabolicSpaceScroll:
; HEX 00 01 01 01 01 01 01 01 02 02 02 03 03 04 04 05 06 06 07 00 00 01 02 03 04 05 06 07 00 01 02 04 05 06 00 01 02 04 05 07 00 02 04 05 07 00 01 03 04 06 00 01 03 04 06 07 00 02 03 04 06 07 00 01 02 03 04 05 06 07 00 01 02 02 03 04 04 05 05 06 06 06 07 06 07 07 07 07 07 07 07
setupXScrollInterrupt SUBROUTINE setupXScrollInterrupt SUBROUTINE
ldx #<XScrollInterruptH ldx #<XScrollInterruptH
ldy #>XScrollInterruptH ldy #>XScrollInterruptH

View File

@ -2,6 +2,12 @@
LASTINIT SET . LASTINIT SET .
#endif #endif
SEG zeropageSegment
; Pointer to video memory used in the level loading routine
levelVideoPointer WORD
levelColorPointer WORD
SEG programSegment
; load new level on the screen ; load new level on the screen
statusLevelTitle SUBROUTINE statusLevelTitle SUBROUTINE
jsr multicolorOff jsr multicolorOff

View File

@ -1,10 +1,9 @@
processor 6502 processor 6502
SEG.U SEG.U zeropageSegment
org $02 org $02
INCLUDE "zeropage.asm"
SEG autostart SEG loaderSegment
org $801 org $801
autostartRoutine SUBROUTINE autostartRoutine SUBROUTINE
; this is at $801 ; this is at $801
@ -50,6 +49,7 @@ autostartRoutine SUBROUTINE
; DATA ; DATA
; ------------------------------------- ; -------------------------------------
SEG loaderSegment
packFileName: packFileName:
BYTE "PACKLZ" BYTE "PACKLZ"
packFileNameEnd: packFileNameEnd:

View File

@ -1,44 +1,48 @@
inflate SUBROUTINE SEG zeropageSegment
.inEnd EQU 2 srcPointer WORD
.offset EQU 4 dstPointer WORD
.length EQU 6 inEnd WORD
.symbol EQU 25 offset WORD
.marker1 EQU 30 length BYTE
.marker2 EQU 31 symbol BYTE
.marker3 EQU 32 marker1 BYTE
.marker4 EQU 33 marker2 BYTE
.copy EQU 34 marker3 BYTE
marker4 BYTE
copy WORD
SEG loaderSegment
inflate SUBROUTINE
clc clc
ldy #10 ldy #10
lda (srcPointer),y lda (srcPointer),y
adc srcPointer adc srcPointer
sta .inEnd sta inEnd
dey dey
lda (srcPointer),y lda (srcPointer),y
adc srcPointer + 1 adc srcPointer + 1
sta .inEnd + 1 sta inEnd + 1
clc clc
lda .inEnd lda inEnd
adc #16 adc #16
sta .inEnd sta inEnd
lda .inEnd + 1 lda inEnd + 1
adc #0 adc #0
sta .inEnd + 1 sta inEnd + 1
; Get the marker symbols ; Get the marker symbols
ldy #16 ldy #16
lda (srcPointer),y lda (srcPointer),y
sta .marker1 sta marker1
iny iny
lda (srcPointer),y lda (srcPointer),y
sta .marker2 sta marker2
iny iny
lda (srcPointer),y lda (srcPointer),y
sta .marker3 sta marker3
iny iny
lda (srcPointer),y lda (srcPointer),y
sta .marker4 sta marker4
; Skip header + marker symbols (16 + 4 bytes) ; Skip header + marker symbols (16 + 4 bytes)
clc clc
@ -53,30 +57,30 @@ inflate SUBROUTINE
ldy #0 ; Make sure that Y is zero ldy #0 ; Make sure that Y is zero
.mainloop: .mainloop:
lda srcPointer ; done? lda srcPointer ; done?
cmp .inEnd cmp inEnd
bne .notdone bne .notdone
lda srcPointer + 1 lda srcPointer + 1
cmp .inEnd + 1 cmp inEnd + 1
bne .notdone bne .notdone
rts rts
.notdone: .notdone:
lda (srcPointer),y ; A = symbol lda (srcPointer),y ; A = symbol
sta .symbol sta symbol
sta $d020 sta $d020
inc srcPointer inc srcPointer
bne .noinc1 bne .noinc1
inc srcPointer + 1 inc srcPointer + 1
.noinc1: .noinc1:
cmp .marker1 ; Marker1? cmp marker1 ; Marker1?
beq .domarker1 beq .domarker1
cmp .marker2 ; Marker2? cmp marker2 ; Marker2?
beq .domarker2 beq .domarker2
cmp .marker3 ; Marker3? cmp marker3 ; Marker3?
beq .domarker3 beq .domarker3
cmp .marker4 ; Marker4? cmp marker4 ; Marker4?
beq .domarker4 beq .domarker4
.literal: .literal:
lda .symbol lda symbol
sta (dstPointer),y ; Plain copy sta (dstPointer),y ; Plain copy
inc dstPointer inc dstPointer
bne .mainloop bne .mainloop
@ -101,15 +105,15 @@ inflate SUBROUTINE
lsr lsr
lsr lsr
lsr lsr
sta .offset sta offset
inc .offset inc offset
lda #0 lda #0
sta .offset + 1 ; offset = (b >> 5) + 1 sta offset + 1 ; offset = (b >> 5) + 1
txa txa
and #$1f and #$1f
tax tax
lda .LZG_LENGTH_DECODE_LUT,x lda .LZG_LENGTH_DECODE_LUT,x
sta .length ; length = .LZG_LENGTH_DECODE_LUT[b & 0x1f] sta length ; length = .LZG_LENGTH_DECODE_LUT[b & 0x1f]
jmp .docopy jmp .docopy
; marker3 - "Short copy" ; marker3 - "Short copy"
@ -130,13 +134,13 @@ inflate SUBROUTINE
lsr lsr
clc clc
adc #3 adc #3
sta .length ; length = (b >> 6) + 3 sta length ; length = (b >> 6) + 3
txa txa
and #$3f and #$3f
adc #8 adc #8
sta .offset sta offset
lda #0 lda #0
sta .offset + 1 ; offset = (b & 0x3f) + 8 sta offset + 1 ; offset = (b & 0x3f) + 8
beq .docopy beq .docopy
; marker2 - "Medium copy" ; marker2 - "Medium copy"
@ -154,7 +158,7 @@ inflate SUBROUTINE
lsr lsr
lsr lsr
lsr lsr
sta .offset + 1 sta offset + 1
lda (srcPointer),y lda (srcPointer),y
inc srcPointer inc srcPointer
bne .noinc6 bne .noinc6
@ -162,15 +166,15 @@ inflate SUBROUTINE
.noinc6: .noinc6:
clc clc
adc #8 adc #8
sta .offset sta offset
bcc .noinc7 bcc .noinc7
inc .offset + 1 ; offset = (((b & 0xe0) << 3) | b2) + 8 inc offset + 1 ; offset = (((b & 0xe0) << 3) | b2) + 8
.noinc7: .noinc7:
txa txa
and #$1f and #$1f
tax tax
lda .LZG_LENGTH_DECODE_LUT,x lda .LZG_LENGTH_DECODE_LUT,x
sta .length ; length = .LZG_LENGTH_DECODE_LUT[b & 0x1f] sta length ; length = .LZG_LENGTH_DECODE_LUT[b & 0x1f]
bne .docopy bne .docopy
.literal2: .literal2:
@ -188,13 +192,13 @@ inflate SUBROUTINE
and #$1f and #$1f
tax tax
lda .LZG_LENGTH_DECODE_LUT,x lda .LZG_LENGTH_DECODE_LUT,x
sta .length ; length = .LZG_LENGTH_DECODE_LUT[b & 0x1f] sta length ; length = .LZG_LENGTH_DECODE_LUT[b & 0x1f]
lda (srcPointer),y lda (srcPointer),y
inc srcPointer inc srcPointer
bne .noinc9 bne .noinc9
inc srcPointer + 1 inc srcPointer + 1
.noinc9: .noinc9:
sta .offset + 1 sta offset + 1
lda (srcPointer),y lda (srcPointer),y
inc srcPointer inc srcPointer
bne .noinc10 bne .noinc10
@ -202,31 +206,31 @@ inflate SUBROUTINE
.noinc10: .noinc10:
clc clc
adc #$08 adc #$08
sta .offset sta offset
lda .offset + 1 lda offset + 1
adc #$08 adc #$08
sta .offset + 1 ; offset = ((b2 << 8) | (*src++)) + 2056 sta offset + 1 ; offset = ((b2 << 8) | (*src++)) + 2056
; Copy corresponding data from history window ; Copy corresponding data from history window
.docopy: .docopy:
sec sec
lda dstPointer lda dstPointer
sbc .offset sbc offset
sta .copy sta copy
lda dstPointer + 1 lda dstPointer + 1
sbc .offset + 1 sbc offset + 1
sta .copy + 1 sta copy + 1
.loop1: .loop1:
lda (.copy),y lda (copy),y
sta (dstPointer),y sta (dstPointer),y
iny iny
cpy .length cpy length
bne .loop1 bne .loop1
ldy #0 ; Make sure that Y is zero ldy #0 ; Make sure that Y is zero
clc clc
lda dstPointer lda dstPointer
adc .length adc length
sta dstPointer sta dstPointer
bcc .noinc11 bcc .noinc11
inc dstPointer + 1 inc dstPointer + 1

View File

@ -1,8 +1,6 @@
SEG zeropageSegment SEG zeropageSegment
ptrDstStart: ptrDstStart WORD
WORD ptrDstEnd WORD
ptrDstEnd:
WORD
MACRO MEMSET MACRO MEMSET
SEG programSegment SEG programSegment

View File

@ -13,7 +13,6 @@
; ---------------------------------------------------------------------- ; ----------------------------------------------------------------------
SEG.U zeropageSegment SEG.U zeropageSegment
org $02 org $02
INCLUDE "zeropage.asm"
#if VERBOSE = 1 #if VERBOSE = 1
; Locations $90-$FF in zeropage are used by kernal ; Locations $90-$FF in zeropage are used by kernal
@ -74,8 +73,11 @@ sidtune:
listX DS 256 listX DS 256
listY DS 256 listY DS 256
; Includes
INCLUDE "zeropage.asm"
; ;
; coded 2017, 2018, 2019, 2020 ; coded 2017, 2018, 2019, 2020, 2021
; by giomba -- giomba at glgprograms.it ; by giomba -- giomba at glgprograms.it
; this software is free software and is distributed ; this software is free software and is distributed
; under the terms of GNU GPL v3 license ; under the terms of GNU GPL v3 license

View File

@ -4,7 +4,12 @@ LASTINIT SET .
; Subroutines ; Subroutines
; ---------------------------------------------------------------------- ; ----------------------------------------------------------------------
SEG zeropageSegment
; Where is the snake head in video memory? Do math to calculate address
; using pointer at tileMem
tileMem WORD
SEG programSegment
; Clear screen -- easy ; Clear screen -- easy
clearScreen SUBROUTINE clearScreen SUBROUTINE
ldx #$ff ldx #$ff
@ -91,6 +96,13 @@ printByte SUBROUTINE
rts rts
SEG zeropageSegment
; Pointer to string
srcStringPointer WORD
; Pointer to screen position where to print intro string
dstScreenPointer DS 2
SEG programSegment
printString SUBROUTINE printString SUBROUTINE
; Print string ; Print string
; Input parameters: ; Input parameters:

View File

@ -1,31 +1,15 @@
; Zero page utility pointers ; Zero page utility pointers
; ---------------------------------------------------------------------- ; ----------------------------------------------------------------------
; Where is the snake head in video memory? Do math to calculate address SEG zeropageSegment
; using pointer at tileMem,tileMem+1
tileMem DS 2
; Pointer to string
srcStringPointer DS 2
; Pointer to screen position where to print intro string
dstScreenPointer DS 2
; Pointer to level struct ; Pointer to level struct
levelPointer DS 2 levelPointer DS 2
; Pointer to video memory used in the level loading routine
levelVideoPointer DS 2
levelColorPointer DS 2
; Pointer for Pointer in the NextPointer routine ; Pointer for Pointer in the NextPointer routine
nextPointerPointer DS 2 nextPointerPointer DS 2
; Pointer to string for strlen routine ; Pointer to string for strlen routine
strlenString DS 2 strlenString DS 2
; Generic src/dst copy pointers
srcPointer DS 2
dstPointer DS 2
; Interrupt counter ; Interrupt counter
counter DS 2 counter DS 2