started on VCS library

This commit is contained in:
Steven Hugg 2018-08-27 13:57:20 -04:00
parent 8581fcabd6
commit 61d7860e12
9 changed files with 1018 additions and 0 deletions

View File

@ -54,6 +54,8 @@ TODO:
- better VCS single stepping, maybe also listings
- New File (include file)
- VCS skips step on lsr/lsr after run to line
- update window list after building 2nd time?
- stop debugging where mouse clicked
FYI: Image links for the books on http://8bitworkshop.com/ are broken
On the website the additional grey spacing next to the program line numbers is not dynamically resized when the web browser window size is changed. Intentional?

144
presets/vcs/6digit.inc Normal file
View File

@ -0,0 +1,144 @@
seg.u Variables
; Pointers to bitmap for each digit
Digit0 .word
Digit1 .word
Digit2 .word
Digit3 .word
Digit4 .word
Digit5 .word
BCDScore hex 000000
THREE_COPIES equ %011 ; for NUSIZ registers
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
seg Code
; setup 6-digit score
Digit6Setup: subroutine
lda #$18
sta COLUP0
lda #$28
sta COLUP1
lda #THREE_COPIES
sta NUSIZ0
sta NUSIZ1
; set horizontal position of player objects
sta WSYNC
SLEEP 26
sta RESP0
sta RESP1
lda #$10
sta HMP1
sta WSYNC
sta HMOVE
sta HMCLR
lda #0
sta REFP0
sta REFP1
sta GRP0
sta GRP1
lda #1
sta VDELP0
sta VDELP1
rts
; Adds value to 6-BCD-digit score.
; A = 1st BCD digit
; X = 2nd BCD digit
; Y = 3rd BCD digit
AddScore: subroutine
.temp equ Temp1
sed ; enter BCD mode
clc ; clear carry
sta .temp
lda BCDScore
adc .temp
sta BCDScore
stx .temp
lda BCDScore+1
adc .temp
sta BCDScore+1
sty .temp
lda BCDScore+2
adc .temp
sta BCDScore+2
cld ; exit BCD mode
rts
GetDigitPtrs: subroutine
ldx #0 ; leftmost bitmap
ldy #2 ; start from most-sigificant BCD value
.Loop
lda BCDScore,y ; get BCD value
and #$f0 ; isolate high nibble (* 16)
lsr ; shift right 1 bit (* 8)
sta Digit0,x ; store pointer lo byte
lda #>Digit6Font
sta Digit0+1,x ; store pointer hi byte
inx
inx ; next bitmap pointer
lda BCDScore,y ; get BCD value (again)
and #$f ; isolate low nibble
asl
asl
asl ; * 8
sta Digit0,x ; store pointer lo byte
lda #>Digit6Font
sta Digit0+1,x ; store pointer hi byte
inx
inx ; next bitmap pointer
dey ; next BCD value
bpl .Loop ; repeat until < 0
rts
; Display the resulting 48x8 bitmap
; using the Digit0-5 pointers.
DrawDigits: subroutine
.temp equ Temp1
.count equ Temp2
sta WSYNC
SLEEP 40 ; start near end of scanline
lda #7
sta .count
.bigloop
ldy .count ; counts backwards
lda (Digit0),y ; load B0 (1st sprite byte)
sta GRP0 ; B0 -> [GRP0]
lda (Digit1),y ; load B1 -> A
sta GRP1 ; B1 -> [GRP1], B0 -> GRP0
sta WSYNC ; sync to next scanline
lda (Digit2),y ; load B2 -> A
sta GRP0 ; B2 -> [GRP0], B1 -> GRP1
lda (Digit5),y ; load B5 -> A
sta .temp ; B5 -> temp
lda (Digit4),y ; load B4
tax ; -> X
lda (Digit3),y ; load B3 -> A
ldy .temp ; load B5 -> Y
sta GRP1 ; B3 -> [GRP1]; B2 -> GRP0
stx GRP0 ; B4 -> [GRP0]; B3 -> GRP1
sty GRP1 ; B5 -> [GRP1]; B4 -> GRP0
sta GRP0 ; ?? -> [GRP0]; B5 -> GRP1
dec .count ; go to next line
bpl .bigloop ; repeat until < 0
lda #0 ; clear the sprite registers
sta GRP0
sta GRP1
sta GRP0
sta GRP1
rts
; Font table for digits 0-9 (8x8 pixels)
align $100 ; make sure data doesn't cross page boundary
Digit6Font:
hex 003c6666766e663c007e181818381818
hex 007e60300c06663c003c66061c06663c
hex 0006067f661e0e06003c6606067c607e
hex 003c66667c60663c00181818180c667e
hex 003c66663c66663c003c66063e66663c

View File

@ -0,0 +1,257 @@
processor 6502
include "vcs.h"
include "macro.h"
include "xmacro.h"
include "xtimer.h"
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
seg.u Variables
org $80
Temp1 .byte
Temp2 .byte
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
seg Code
org $f000
jmp Start
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
include "setpos.inc" ; SetHorizPos routine
include "xtimer.inc" ; WaitForScanline routine and lookup table
include "multisprite.inc" ; multi 2-player color 2-line kernel w/ background
include "6digit.inc" ; 6-digit scoreboard
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Initialize and set initial X and Y offsets of objects.
Start
CLEAN_START
jsr MSpriteInit
ldx #0
lda #MinYPos
ldy #40
InitLoop
sty XPos0,x
sta YPos0,x
sta Flags0,x
clc
adc #13
iny
iny
iny
iny
iny
iny
inx
cpx #NSprites
bne InitLoop
lda #0
sta Shape0
lda #1
sta Shape0+1
lda #2
sta Shape0+2
sta Shape0+4
sta Shape0+6
lda #3
sta Shape0+3
sta Shape0+5
sta Shape0+7
lda #>Start
sta PF0Ptr+1
lda #>Start+1
sta PF1Ptr+1
lda #>Start+1
sta PF2Ptr+1
; Next frame loop
NextFrame
VERTICAL_SYNC
TIMER_SETUP 37
; Do joystick movement
ldy #1
jsr MoveJoystick
jsr Digit6Setup
jsr GetDigitPtrs
jsr MSpritePre
TIMER_WAIT
; end of VBLANK
TIMER_TABLE_SETUP
; Scoreboard
jsr DrawDigits
; Scanline loop
lda #$90
sta COLUBK
lda #22
jsr MSpriteDraw2
; Overscan
TIMER_SETUP 28
; Clear all colors to black before overscan
ldx #0
stx COLUBK
stx COLUP0
stx COLUP1
stx COLUPF
; 30-2 lines of overscan
TIMER_WAIT
; Go to next frame
jmp NextFrame
; Read joystick movement and apply to object 0
MoveJoystick subroutine
; Move vertically
ldx YPos0,y
lda #%00010000 ;Up?
bit SWCHA
bne .SkipMoveUp
cpx #MinYPos+1
bcc .SkipMoveUp
dex
.SkipMoveUp
lda #%00100000 ;Down?
bit SWCHA
bne .SkipMoveDown
cpx #180
bcs .SkipMoveDown
inx
.SkipMoveDown
stx YPos0,y
; Move horizontally
ldx XPos0,y
lda #%01000000 ;Left?
bit SWCHA
bne .SkipMoveLeft
cpx #5
bcc .SkipMoveLeft
dex
lda #$08
sta Flags0,y
.SkipMoveLeft
lda #%10000000 ;Right?
bit SWCHA
bne .SkipMoveRight
cpx #160
bcs .SkipMoveRight
inx
lda #$00
sta Flags0,y
.SkipMoveRight
stx XPos0,y
rts
; TODO: do we need trailing padding?
; Bitmap data "standing" position
Frame0
.byte #0
.byte #%01101100;$F6
.byte #%00101000;$86
.byte #%00101000;$86
.byte #%00111000;$86
.byte #%10111010;$C2
.byte #%10111010;$C2
.byte #%01111100;$C2
.byte #%00111000;$C2
.byte #%00111000;$16
.byte #%01000100;$16
.byte #%01111100;$16
.byte #%01111100;$18
.byte #%01010100;$18
.byte #%01111100;$18
.byte #%11111110;$F2
.byte #%00111000;$F4
; Bitmap data "throwing" position
Frame1
.byte #0
.byte #%01101100;$F6
.byte #%01000100;$86
.byte #%00101000;$86
.byte #%00111000;$86
.byte #%10111010;$C2
.byte #%10111101;$C2
.byte #%01111101;$C2
.byte #%00111001;$C2
.byte #%00111000;$16
.byte #%01101100;$16
.byte #%01111100;$16
.byte #%01111100;$18
.byte #%01010100;$18
.byte #%01111100;$18
.byte #%11111110;$F2
.byte #%00111000;$F4
; Color data for each line of sprite
ColorFrame0
.byte #16 ; height
.byte #$F6;
.byte #$86;
.byte #$86;
.byte #$86;
.byte #$C2;
.byte #$C2;
.byte #$C2;
.byte #$C2;
.byte #$16;
.byte #$16;
.byte #$16;
.byte #$18;
.byte #$18;
.byte #$18;
.byte #$F2;
.byte #$F4;
; Enemy cat-head graphics data
EnemyFrame0
.byte #0
.byte #%00111100;$AE
.byte #%01000010;$AE
.byte #%11100111;$AE
.byte #%11111111;$AC
.byte #%10011001;$8E
.byte #%01111110;$8E
.byte #%11000011;$98
.byte #%10000001;$98
; Enemy cat-head color data
EnemyColorFrame0
.byte #8 ; height
.byte #$AE;
.byte #$AC;
.byte #$A8;
.byte #$AC;
.byte #$8E;
.byte #$8E;
.byte #$98;
.byte #$94;
; Enemy cat-head color data
EnemyColorFrame1
.byte #8 ; height
.byte #$FE;
.byte #$FC;
.byte #$28;
.byte #$2C;
.byte #$EE;
.byte #$EE;
.byte #$D8;
.byte #$D4;
; Mapping of sprite shapes to sprite data
SpriteDataMap
.word Frame0,ColorFrame0
.word Frame1,ColorFrame0
.word EnemyFrame0,EnemyColorFrame0
.word EnemyFrame0,EnemyColorFrame1
; Epilogue
org $fffc
.word Start
.word Start

1
presets/vcs/km2pc2sb.inc Normal file
View File

@ -0,0 +1 @@

537
presets/vcs/multisprite.inc Normal file
View File

@ -0,0 +1,537 @@
; MULTISPRITE LIBRARY
; For lots of games, we'd like to display more than two sprites.
; There are lots of different ways to tackle this on the VCS,
; but we're going to try for a generalized approach that lets
; use have N different sprites at any X-Y coordinate, each with
; its own bitmap and color table. This is tricky because we can
; only do so much on each scanline.
; Our approach is to separate the problem into three phases.
; In the sort phase, we sort all sprites by Y coordinate.
; We do one sort pass per frame, so it may take several frames
; for the sort to stabilize.
; In the positioning phase, we look at the sprites in Y-sorted
; order, looking several lines ahead to see if a sprite is
; coming up. We then allocate it to one of the two player
; objects in hardware and set its position using the SetHorizPos
; method. We can set one or both of the player objects this way.
; In the display phase, we display the objects which we previously
; assigned and positioned. First we figure out how many scanlines are
; required. If only one object is scheduled, we just use its height.
; If two objects are scheduled, we go until the bottommost line has
; been displayed. We then loop through, fetching pixels and colors
; for one or both objects (up to four lookup tables) and setting
; registers at the appropriate time. We don't have time to do much
; else, so we don't look for any new objects to schedule until
; we're done with this loop.
; This scheme can only display up to two objects on a given
; scanline, so if the system tries to schedule a third, it will
; be ignored. Also, the positioning routine takes a few scanlines
; to complete, so if the top of a sprite is too close to the
; bottom of another sprite, the latter may not be displayed.
;
; To mitigate this, we increment a priority counter when a
; sprite entry is missed. In the sort phase, we move those sprites
; ahead of lower priority sprites in the sort order. This makes
; overlapping sprites flicker instead of randomly disappear.
; There are two separate multisprite kernels:
; MSpriteDraw1 - Single-line sprites, no playfield.
; This kernel requires TIMER_TABLE_SETUP at the 0th
; scanline, as it uses the timer to figure out the
; current scanline.
; MSpriteDraw2 - Double-line sprites with playfield.
; The playfield is updated and the sprites are positioned
; in 8-scanline segments.
; This kernel uses the timer internally, but does not
; use the timer table or TIMER_TABLE_SETUP.
; Your program must call MSpriteInit when it starts,
; and MSpritePre between every frame.
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
seg.u Variables
Scanline byte ; current scanline
CurIndex byte ; current sprite # to try to schedule
PData0 word ; pointer (lo/hi) to player 0 bitmap data
PData1 word ; pointer to player 1 bitmap data
PColr0 word ; pointer to player 0 color data
PColr1 word ; pointer to player 1 color data
SIndx0 byte ; next y-position to draw player 0
; or during draw, index into sprite
; zero means not assigned
SIndx1 byte ; ... for player 1
SSize0 byte ; sprite size for player 0
SSize1 byte ; sprite size for player 1
NSprites equ 8 ; max # of sprites
XPos0 ds NSprites ; x coord for each sprite
YPos0 ds NSprites ; y coord for each sprite
Shape0 ds NSprites ; shape index
Flags0 ds NSprites ; NUSIZ and reflection flags
Sorted0 ds NSprites ; sorted list of sprite indices
Priority0 ds NSprites ; sprite priority list, if missed
;MinYDist equ 0 ; min. Y distance to consider sprite (not used)
;MinYPos equ 1 ; TODO???
MinYDist equ 6 ; min. Y distance to consider sprite
MinYPos equ 2+MinYDist
PF0Ptr word ; pointer to playfield data
PF1Ptr word ; pointer to playfield data
PF2Ptr word ; pointer to playfield data
PFIndex byte ; offset into playfield array
PFCount byte ; lines left in this playfield segment
; temporary values for kernel
; TODO: share with global temporaries
Temp byte
Colp0 byte
Colp1 byte
tmpPF0 byte
tmpPF1 byte
tmpPF2 byte
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
seg Code
; call at start of program
MSpriteInit subroutine
; Initialize initial sort order
ldx #0
.loop
txa
sta Sorted0,x
inx
cpx #NSprites
bne .loop
rts
; call between frames
MSpritePre subroutine
; Do one iteration of bubble sort on sprite indices
ldx #NSprites-2
.SortLoop
jsr SwapSprites
dex
bpl .SortLoop ; loop until <= 0
; Reset scanline counter and sprite objects
ldx #0
stx CurIndex
stx SIndx0
stx SIndx1
stx SSize0
stx SSize1
rts
; single-line kernel routine
MSpriteDraw1 subroutine
.NextFindSprite
; Try to schedule sprites to both players
jsr FindAnotherSprite
jsr FindAnotherSprite
; Apply fine offsets
sta WSYNC ; start next scanline
sta HMOVE ; apply the previous fine position(s)
sta HMCLR ; clear motion registers
ldx #0
stx VDELP0 ; set vertical delay off
stx VDELP1 ; set vertical delay off
; See if time to draw
jsr DrawSprites1
; Repeat until all scanlines drawn
lda INTIM
cmp #$1f
bcs .NextFindSprite
lda #191
jmp WaitForScanline
; called by single-line kernel
DrawSprites1 subroutine
; Wait for next precise scanline
lda #0 ; 0 = wait for next
.AnotherScanline
jsr WaitForScanline
lda Timer2Scanline,y ; lookup scanline #
beq .AnotherScanline ; not if zero!
sta Scanline ; save it
; Calculate # of lines to draw for each sprite
; Sprite Y - current scanline + sprite height
lda SIndx0
beq .Empty0 ; sprite 0 is inactive?
sec
sbc Scanline
clc
adc SSize0
sta SIndx0 ; SIndx0 += SSize0 - Scanline
.Empty0
lda SIndx1
beq .Empty1 ; sprite 1 is inactive?
sec
sbc Scanline
clc
adc SSize1
sta SIndx1 ; SIndx1 += SSize1 - Scanline
.Empty1
; Find out the maximum # of lines to draw
; by taking the maximum of the two sprite heights
cmp SIndx0
bpl .Cmp1 ; sindx0 < sindx1?
lda SIndx0
.Cmp1
tax ; X = # of lines left to draw
beq .NoSprites ; X = 0? we're done
sta WSYNC ; next scanline
.DrawNextScanline
; Make sure player 0 index is within bounds
ldy SIndx0
cpy SSize0
bcs .Inactive0 ; index >= size? (or index < 0)
; Lookup pixels for player 0
lda (PData0),y
; Do WSYNC and then quickly store pixels for player 0
sta WSYNC
sta GRP0
; Lookup/store colors for player 0
lda (PColr0),y
sta COLUP0
.DrawSprite1
; Make sure player 1 index is within bounds
ldy SIndx1
cpy SSize1
bcs .Inactive1 ; index >= size? (or index < 0)
; Lookup/store pixels and colors for player 1
; Note that we are already 30-40 pixels into the scanline
; by this point...
lda (PData1),y
sta GRP1
lda (PColr1),y
sta COLUP1
.Inactive1
; Decrement the two sprite indices
dey
sty SIndx1
dec SIndx0
; Repeat until we've drawn all the scanlines for this job
dex
bne .DrawNextScanline
; Free up both player objects by zeroing them out
stx SIndx0
stx SIndx1
stx SSize0
stx SSize1
sta WSYNC
stx GRP0
stx GRP1
; No sprites were drawn; just exit
.NoSprites
rts
.Inactive0
; Alternate player 0 path when it is inactive
sta WSYNC
lda #0
sta GRP0
sta COLUP0
beq .DrawSprite1 ; always taken due to lda #0
MSpriteDraw2 subroutine
sta WSYNC
sta PFIndex ; 24 * 4 scanlines = 96 2xlines
lda #0
sta PFCount
sta VDELP1
lda #1
sta VDELP0 ; updates to GRP0 will be delayed
.KernelLoop
dec PFCount
bmi .NewSprites
.Draw8Lines
; Phase 0: Fetch PF0 byte
jsr DrawSprites2
ldy PFIndex
lda (PF0Ptr),y ; load PF0
sta tmpPF0
; Phase 1: Fetch PF1 byte
jsr DrawSprites2
ldy PFIndex
lda (PF1Ptr),y ; load PF1
sta tmpPF1
; Phase 2: Fetch PF2 byte
jsr DrawSprites2
ldy PFIndex
lda (PF2Ptr),y ; load PF2
sty PFIndex
sta tmpPF2
; Phase 3: Write PF0/PF1/PF2 registers
jsr DrawSprites2
lda tmpPF0
sta PF0
lda tmpPF1
sta PF1
lda tmpPF2
sta PF2
; Go to next scanline, unless playfield is done
dec PFIndex
bpl .KernelLoop
.NoMoreLines
rts
.NewSprites
; lda PFIndex
; sta COLUBK
lda PFIndex
asl
asl
eor #$7f
sbc #34
sta Scanline ; Scanlines = 127 - PFIndex*4
; Set up 0-2 player objects taking up to 8 scanlines
TIMER_SETUP 8
ldx #0
stx SSize0
stx SSize1
stx SIndx0
stx SIndx1
jsr FindAnotherSprite2
; jsr FindAnotherSprite2
jsr CalcSpriteEnd
; Update playfield
ldy PFIndex
lda (PF0Ptr),y ; load PF0 -> X
tax
lda (PF1Ptr),y ; load PF1 -> tmp
sta tmpPF1
lda (PF2Ptr),y ; load PF2 -> Y
tay
; Apply fine offsets
TIMER_WAIT ; wait for 8th scanlines and WSYNC
sta HMOVE ; apply the previous fine position(s)
sta HMCLR ; clear motion registers
; Store playfield registers
stx PF0
lda tmpPF1
sta PF1
sty PF2
dec PFIndex ; no more playfield?
bpl .KernelLoop
jmp .NoMoreLines
CalcSpriteEnd subroutine
; Calculate # of lines to draw for each sprite
; SIndx = 255 - ypos + scanline
lda SIndx0
beq .zero0
sec
sbc Scanline
eor #$ff
sta SIndx0
sec
sbc SSize0
.zero0
sta Temp
lda SIndx1
beq .zero1
sec
sbc Scanline
eor #$ff
sta SIndx1
sec
sbc SSize1
cmp Temp
bmi .cmp1 ; sindx0 < sindx1?
.zero1
lda Temp ; load higher number
.cmp1
; Compute the number of 8x lines in this section
eor #$ff
clc
adc #5
lsr
lsr
sta PFCount
rts
;;;
;;; COMMON ROUTINES
;;;
; We were too late to display a sprite.
; Put it earlier in the sort order and try next frame.
; X = sort index
.MissedSprite subroutine
; Have we already looked at all the sprites?
; Increment priority for this sort entry
inc Priority0,x
; Go to next sort index, until we get to the end
inx
stx CurIndex
.OutOfSprites
rts
; Try to assign the next sprite in the sort order into
; one of the two player slots.
; If sprite found, uses at least 3 scanlines for SetHorizPos.
FindAnotherSprite ; subroutine entry point
; Get the approximate scanline
GET_APPROX_SCANLINE
clc
adc #MinYDist
sta Scanline
FindAnotherSprite2 ; alternate entry point when scanline known
; Calculate the distance to next sprite
ldx CurIndex
cpx #NSprites
bcs .OutOfSprites
ldy Sorted0,x ; get sprite index # in Y-sorted order
lda YPos0,y ; get Y position of sprite
cmp Scanline ; SpriteY - Scanline
; Don't schedule the sprite if it's too soon or its scanline
; has already passed -- mark it missed
bmi .MissedSprite ; passed it? (or > 127 lines away)
; A sprite is starting soon, now we need to schedule it
; to either one of the player objects
lda XPos0,y
; Is player 1 available?
ldx SIndx1
bne .Plyr1NotReady
; Due to timing issues, we have artifacts if player 1 is
; too close to the left edge of the screen. So we'd prefer to
; put those sprites in the player 0 slot.
cmp #34 ; X < 34
bcc .Plyr1NotReady
; First let's set its horizontal offset
ldx #1
jsr SetHorizPos ; set horizontal position (does WSYNC)
; Assign the sprite's Y position to player 1
lda YPos0,y
sta SIndx1
; Set player 1 reflection/number/size flags
lda Flags0,y
sta REFP1 ; reflection flag
sta NUSIZ1 ; number-size
; Get index into SpriteDataMap (index * 4)
lda Shape0,y
asl
asl
tax
; Copy addresses of pixel/color maps to player 1
lda SpriteDataMap,x
sta PData1
lda SpriteDataMap+1,x
sta PData1+1
lda SpriteDataMap+2,x
sta PColr1
lda SpriteDataMap+3,x
sta PColr1+1
; Get the sprite height as the first byte of the color map
ldy #0
lda (PColr1),y
sta SSize1
inc SSize1 ; +1 to size
jmp .SetupDone
.Plyr1NotReady
ldx SIndx0
bne .NoNearSprite ; both players in use
; Player 0 is available
; This is essentially the same as the player 1 routine
ldx #0
jsr SetHorizPos
lda YPos0,y
sta SIndx0
lda Flags0,y
sta REFP0 ; reflection flag
sta NUSIZ0 ; number-size
lda Shape0,y
asl
asl
tax
lda SpriteDataMap,x
sta PData0
lda SpriteDataMap+1,x
sta PData0+1
lda SpriteDataMap+2,x
sta PColr0
lda SpriteDataMap+3,x
sta PColr0+1
ldy #0
lda (PColr0),y
sta SSize0
inc SSize0 ; +1 to size
.SetupDone
inc CurIndex ; go to next sprite in sort order
.NoNearSprite
rts
; called by 2-line kernel
DrawSprites2 subroutine
; Fetch sprite 0 values
lda SSize0 ; height in 2xlines
sec
isb SIndx0 ; INC yp0, then SBC yp0
bcs DoDraw0 ; inside bounds?
lda #0 ; no, load the padding offset (0)
DoDraw0
tay ; -> Y
lda (PColr0),y ; color for both lines
sta Colp0 ; -> colp0
lda (PData0),y ; bitmap for first line
sta GRP0 ; -> [GRP0] (delayed due to VDEL)
; Fetch sprite 1 values
lda SSize1 ; height in 2xlines
sec
isb SIndx1 ; INC yp0, then SBC yp0
bcs DoDraw1 ; inside bounds?
lda #0 ; no, load the padding offset (0)
DoDraw1
tay ; -> Y
lda (PColr1),y ; color for both lines
tax
lda (PData1),y ; bitmap for first line
tay
; WSYNC and store sprite values
lda Colp0
sta WSYNC
sty GRP1 ; GRP0 is also updated due to VDELP0 flag
stx COLUP1
sta COLUP0
; Return to caller
rts
; Perform one sort iteration
; X register contains sort index (0 to NSprites-1)
SwapSprites subroutine
; First compare Priority[i] and Priority[i+1]
lda Priority0,x
cmp Priority0+1,x
bcs .CompareYPos
; If Priority[i] < Priority[i+1], do the swap
; anyway after resetting priorities
lda #0
sta Priority0,x
sta Priority0+1,x ; reset
ldy Sorted0+1,x
bcc .DoSwap ; swap due to priority
.CompareYPos
; Compare Y[i] and Y[i+1]
ldy Sorted0,x
lda YPos0,y
ldy Sorted0+1,x
cmp YPos0,y
bcc .NoSwap ; Y[i] < Y[i+1]? don't swap
.DoSwap
; Swap Sorted[i] and Sorted[i+1]
lda Sorted0,x ; A <- Sorted[i]
sty Sorted0,x ; Y -> Sorted[i]
sta Sorted0+1,x ; A -> Sorted[i+1]
.NoSwap
rts

25
presets/vcs/setpos.inc Normal file
View File

@ -0,0 +1,25 @@
; SetHorizPos - Sets the horizontal position of an object.
; The X register contains the index of the desired object:
; X=0: player 0
; X=1: player 1
; X=2: missile 0
; X=3: missile 1
; X=4: ball
; NOTE: This version of the routine does a NEWLINE before executing.
; It does NOT do a HMOVE and HCLR.
SetHorizPos subroutine
sec ; set carry flag
sta WSYNC ; start a new line
.DivideLoop
sbc #15 ; subtract 15
bcs .DivideLoop ; branch until negative
eor #7 ; calculate fine offset
asl
asl
asl
asl
sta HMP0,x ; set fine offset
sta RESP0,x ; fix coarse position
rts ; return to caller

10
presets/vcs/xtimer.h Normal file
View File

@ -0,0 +1,10 @@
; Fetchs the approximate scanline (could be off by +/- 1)
; into A. Takes 11 or 14 cycles.
MAC GET_APPROX_SCANLINE
ldy INTIM
lda Timer2Scanline,y
bne .Ok
lda Timer2Scanline-1,y
.Ok
ENDM

41
presets/vcs/xtimer.inc Normal file
View File

@ -0,0 +1,41 @@
; Set up macro for timer table
MAC TIMER_TABLE_SETUP
lda #255
sta WSYNC
sta TIM64T
ENDM
; Timer -> Scanline table
Timer2Scanline
.byte 215, 0,214,213,212,211,210, 0,209,208,207,206,205,204, 0,203
.byte 202,201,200,199, 0,198,197,196,195,194, 0,193,192,191,190,189
.byte 188, 0,187,186,185,184,183, 0,182,181,180,179,178, 0,177,176
.byte 175,174,173,172, 0,171,170,169,168,167, 0,166,165,164,163,162
.byte 0,161,160,159,158,157,156, 0,155,154,153,152,151, 0,150,149
.byte 148,147,146, 0,145,144,143,142,141,140, 0,139,138,137,136,135
.byte 0,134,133,132,131,130, 0,129,128,127,126,125,124, 0,123,122
.byte 121,120,119, 0,118,117,116,115,114, 0,113,112,111,110,109,108
.byte 0,107,106,105,104,103, 0,102,101,100, 99, 98, 0, 97, 96, 95
.byte 94, 93, 92, 0, 91, 90, 89, 88, 87, 0, 86, 85, 84, 83, 82, 0
.byte 81, 80, 79, 78, 77, 76, 0, 75, 74, 73, 72, 71, 0, 70, 69, 68
.byte 67, 66, 0, 65, 64, 63, 62, 61, 60, 0, 59, 58, 57, 56, 55, 0
.byte 54, 53, 52, 51, 50, 0, 49, 48, 47, 46, 45, 44, 0, 43, 42, 41
.byte 40, 39, 0, 38, 37, 36, 35, 34, 0, 33, 32, 31, 30, 29, 28, 0
.byte 27, 26, 25, 24, 23, 0, 22, 21, 20, 19, 18, 0, 17, 16, 15, 14
.byte 13, 12, 0, 11, 10, 9, 8, 7, 0, 6, 5, 4, 3, 2, 0, 1
; Pass: A = desired scanline
; Returns: Y = timer value - 1
align $10
WaitForScanline subroutine
ldy INTIM ; Fetch timer value
.Wait
cpy INTIM
beq .Wait ; Wait for it to change
sta WSYNC ; Sync with scan line
cmp Timer2Scanline,y ; lookup scanline
bcs WaitForScanline ; repeat until >=
rts

View File

@ -38,6 +38,7 @@ const VCS_PRESETS = [
{id:'examples/wavetable', chapter:36, name:'Wavetable Sound'},
{id:'examples/fracpitch', name:'Fractional Pitch'},
{id:'examples/pal', name:'PAL Video Output'},
{id:'examples/testlibrary', name:'VCS Library Demo'},
// {id:'examples/music2', name:'Pitch-Accurate Music'},
// {id:'examples/fullgame', name:'Thru Hike: The Game', title:'Thru Hike'},
];