Retrochallenge 2018/04 (Now in COLOR)
Refraction for the Atari 2600

Episode 4: Sprites II — Positioning

Time to have a look at sprite positioning, both horizontally and vertically. As on the VCS (Atari 2600) both dimensions exist only in a single one, namely time, it's going to be all about timing. In this episode, we'll have a look at the classic and proven approaches and algorithms and we'll see, how far this will us take. (*Spoiler*)

Horizontal Positioning

Horizontal positioning is to be done by strobing the appropriate register (there's one for each of the 5 sprites) at exactly the right time. As we already know, there are 3 color cycles performed by the TIA (i.e., 3 display pixels are rendered) per CPU cycle. Moreover, a 6502 instruction is at least 2 cycles and a minimal, empty loop 5 cycles. Thus, waiting for a certain cycle will give us an accuracy of 15 TIA clocks or pixels. Based on this, positioning is apparently a matter of sheer luck.

However, there are also the horizontal movement registers (again, one per object) and they allow us to move an object up to 7 pixels to the left or to the right, allowing us to fine adjust the position in a range of 15 pixels. What a coincidence! Once these are set up appropriately, we'll strobe the HMOVE register, which will cause to move all objects according to the value in the respective horizontal movement register. (This is applied each time, HMOVE is strobed. So, if we care not about absolut positions, but, say, just about colissions, like in Pong, we may move our objects solely by the use of the movement registers.)

Strobing HMOVE has a few requirements, it is to be done at the very beginning of a scan line and we are not to change any of the movement registers for the next 24 CPU cycles (roughly, for while in HBLANK). Morever, strobing HMOVE will cause the background to and playfield to drop to black, resulting in the well known black combes, we already discussed in episode 1. hence, it is best done during vertical blank (VBLANK).

Here is, what the Stella Programmer's Guide has to say on the matter:

Horizontal motion allows the programmer to move any of the 5 graphics objects relative to their current horizontal position. Each object has a 4 bit horizontal motion register (HMP0, HMP1, HMM0, HMM1, HMBL) that can be loaded with a value in the range of +7 to -8 (negative values are expressed in two's complement from). This motion is not executed until the HMOVE register is written to, at which time all motion registers move their respective objects. Objects can be moved repeatedly by simply executing HMOVE. Any object that is not to move must have a 0 in its motion register. With the horizontal positioning command confined to positioning objects at 15 color clock intervals, the motion registers fills in the gaps by moving objects +7 to -8 color clocks. Objects can not be placed at any color clock position across the screen. All 5 motion registers can be set to zero simultaneously by writing to the horizontal motion clear register (HMCLR).

There are timing constraints for the HMOVE command. The HMOVE command must immediately follow a WSYNC (Wait for SYNC) to insure the HMOVE operation occurs during horizontal blanking. This is to allow sufficient time for the motion registers to do their thing before the electron beam starts drawing the next scan line. Also, for mysterious internal hardware considerations, the motion registers should not be modified for at least 24 machine cycles after an HMOVE command.

The Rediscovered Battlezone Positioning Routine

So positioning comes down to burning cycles in a loop, spending 5 cycles per iteration and by this dividing the desired position by 15 pixels a time, and then picking the appropriate fine adjustment based on the remainder.

The approved method to do this, is based on code found in the disassembly of Battlezone. There are several versions of this, either using algorithms to determine the fine adjustment and others using a lookup table. The table-based approach has an advantage in runtime, while it requires a suitable alignment of the table in memory. (The lookup is done by an indexed load instruction, which will use an extra cycle, if page boundaries are crossed by the addition of the index. In this case, it's a desired feature and required for the timing of the strobe on the position register.) The computational approach is nice, if you do not want to care about page alignement and also it doesn't use the Y register, which may be of importance in some cases.

The routine looks like this, here in its table-based form:

; Battlezone style exact horizontal repositioning with lookup table
; A = horizontal position in pixel
; X = object
;     0 = Player0
;     1 = Player1
;     2 = Missile0
;     3 = Missile1
;     4 = Ball

    org $F8F0                ; lookup table will start at end of page

bzoneRepos                   ; addr,cycles
    sta WSYNC                ; $00, 3    start of scanline.
    sec                      ; $02, 2    set carry flag
divideby15
    sbc #15                  ; $03, 2    waste 5 cycles by dividing X-pos by 15
    bcs divideby15           ; $05, 2/3  now at 11/16/21/26/31/36/41/46/51/56/61/66

    tay                      ; $07, 2
    lda fineAdjustTable,Y    ; $08, 5    5 cycles by guaranteeing we cross a page boundary
    sta HMP0,X               ; $0B, 4    store fine adjustment

    sta RESP0,X              ; $0D, 4    set the rough position
    rts                      ; $0F, 6    now at 21/26/31/36/41/46/51/56/61/66/71
                             ; $10

; Note: loop at "bcs divideby15" must not cross a page boundary

;-----------------------------
; This table is on a page boundary to guarantee the processor
; will cross a page boundary and waste a cycle in order to be
; at the precise position

fineAdjustBegin
    .byte %01110000 ; Left 7
    .byte %01100000 ; Left 6
    .byte %01010000 ; Left 5
    .byte %01000000 ; Left 4
    .byte %00110000 ; Left 3
    .byte %00100000 ; Left 2
    .byte %00010000 ; Left 1
    .byte %00000000 ; No movement.
    .byte %11110000 ; Right 1
    .byte %11100000 ; Right 2
    .byte %11010000 ; Right 3
    .byte %11000000 ; Right 4
    .byte %10110000 ; Right 5
    .byte %10100000 ; Right 6
    .byte %10010000 ; Right 7

fineAdjustTable = fineAdjustBegin - %11110001   ; Note: %11110001 = -15

And it's to be called like this:

    lda #24          ; 24px from left edge
    ldx #0           ; player0
    jsr bzoneRepos
    lda #142         ; 142px from left edge
    ldx #1           ; player1
    jsr bzoneRepos
    sta WSYNC
    sta HMOVE        ; strobe HMOVE to set fine adjustments at once

The workings of this routine are pretty straight forward and amazingly simple, but hard to come up with, because of the fine adjustment in cycle timing: First, we perform our divide-by-15 in a loop and then, as we have looked up and stored the fine-adjustment, it's just the right time to strobe the position register. And, somehow, we've also taken into account the cycles to be spent during HBLANK. — Magic.

Vertcial Positioning

As we have already discussed briefly in the first episode, vertical positioning has to be handled by software, in the so-called kernel routine, while rendering the visible part of a frame. Vertical positioning is simply about determining, whether we're going to display a certain sprite on the current line or not, and if we would do so, determining the right bit-pattern to be loaded into the sprite register. The problem here is to do it in an econimical and fast way (optimized for CPU runtime.)

Skip Draw

Again, there is a proven method, the so-called Skip Draw. Before we dive into this, we may want to consider the way, a kernel is usually rendered, by use of a count-down, probably in one of the index registers. Doing so, we're logically rendering the screen bottom-up. If we derive any index from this counter, we'll be usually also going bottom-up. Which is also, why sprites are usually stored bottom-up in memory, so that they can be easilly scanned by the kernel routine in logical order.

The Skip Draw method does it just the same, but with a twist: Instead of adjusting the index to the adddress of the appropriate bit-pattern to be used for the sprite, all calcualtions are simply about determining, whether to draw or not (if the sprite is on the current scan line or not) — and the scan-line counter in the Y register is used as-is for the memory lookup. To do so, the pointer to the base address of the sprite has to be arranged accordingly, taking into account the offset from the bottom of the page. Just the same, the position, which will be used for the comparison, is from the bottom of the scan range to the top of the sprite.

Here we also see, why the Y register is commonly used as the scan line counter: If we want to scan memory from a variable base address, we're going to need a pointer. Usually, a sprite will have more than a single appearance, so we will want to select the image in memory as well. So we're going to need an instruction, which will add an index to an indirect memory lookup, using a pointer. There's only a single one on the 6502, namely the indirect indexed LDA using a zero page address for the pointer and the Y register for the index, as in "LDA (HH),Y".

(Using the X register for the index, the index would be added to the pointer before the lookup, pointing to a completely different segment in memory, instead of sequentially scanning a range from a base address.)

Anyway, back to Skip Draw: During setup (preferably while in VBLANK), we'll have to arrange the position used in the comparison and the sprite pointer to be used, both from the bottom of the playfield. The position is the distance from the bottom-edge of the screen to the top of the sprite, the pointer is to be pointing to the last byte in memory less the distance from the bottom edge of the playfield. The comparison consists of just two operations, first subtracting the sprite position from the current scan line (if greater, the carry will be cleared on underflow), then adding the height of the sprite (resetting the carry on overflow, else clearing it). As a result, the carry will be only set, if the sprite is on the current scan line and cleared else, meaning, we may branch on the state of the carry. If the sprite is on, we're going to load the sprite data and store it in one of the TIA's sprite registers, else, we burn the same amount of runtime and reset the carry for the next scan line or sprite comparison.

And this is, what it looks like:

; zero page addresses
SpPosY       = $80
SpGrPtr      = $81  ; 2 bytes
; vertical position from top of playfield
SPosFromTop  = 30

;(...)
; VBLANK ...

                        ; compute sprite Y from bottom:
                        ;  <Sprite-from-bottom> = PFHeight + 1 - spPosFromTop
                        ; and store it for comparison:
                        ;  SpPosY = <Sprite-from-bottom>
    lda #PFHeight+1
    sec
    sbc #spPosFromTop
    sta SpPosY
                        ; and set up graphics pointer for skip-draw
                        ; SpGrPtr  = SpriteEnd - <Sprite-from-bottom>
    lda #<SpriteEnd
    sec
    sbc SpPosY
    sta SpGrPtr
    lda #>SpriteEnd  ; we could do with just the lo-byte, if we align pages properly
    sbc #0
    sta SpGrPtr+1

;(...)
; playfield scan line loop

    ldy #PFHeight       ; store number of lines to draw in Y to count down on
    sec                 ; set carry flag for first subtraction

pfLoop
    sta WSYNC
    dey

    tya                 ; skip-draw style vertical sprite drawing
    sbc SpPosY          ; compare, Y ≥ sprite-top?
    adc #SpriteHeight   ; add height, in range?
    bcs skipDraw        ; if cary still set, branch to drawing
    nop                 ; nothing to draw
    nop                 ; take same amount of cycles like other part
    sec                 ; finally, reset carry
    bcs skipDrawEnd
skipDraw
    lda (SpGrPtr),Y     ; draw sprite (bottom-up), use Y as index
    sta GRP0
skipDrawEnd
    
    cpy #0
    bne pfLoop


;(...)
; data

Sprite                  ; just a smiley ... bottom-up ...
    .byte $00
    .byte $3C ; |  XXXX  |
    .byte $42 ; | X    X |
    .byte $99 ; |X  XX  X|
    .byte $A5 ; |X X  X X|
    .byte $81 ; |X      X|
    .byte $81 ; |X      X|
    .byte $A5 ; |X X  X X|
    .byte $81 ; |X      X|
    .byte $42 ; | X    X |
    .byte $3C ; |  XXXX  |

SpriteEnd = *
SpriteHeight = SpriteEnd - Sprite

Mind the zero byte at the top (logically: at the end) of the sprite data: While it doesn't display anything, it will switch off the sprite for the following scan lines.

There are also more optimized methods, using illegal opcodes and directly counting down on the Y position, e.g.:


; draw player sprite 0:
    lda #SPRITE_HEIGHT-1     ; 2 cycles
    dcp P0_Y                 ; 5 (DEC and CMP)
    bcs doDraw0              ; 2/3
    lda #0                   ; 2
    .byte $2c                ;-1 (BIT ABS to skip next 2 bytes)
doDraw0:
    lda (P0_Ptr),Y           ; 5
    sta GRP0                 ; 3 = 18 cycles (constant, if drawing or not!)

However, we may notice that even the tightly optimized versions still use 18 cycles per sprite. This amounts to 54 pixels! If we're starting just after the horizontal sync, we're nearly out of the horizontal blank, when we've drawn the first sprite. If there are more than a single sprite on the left edge of the screen on a given frame, we're in trouble! Also, there are only 228 TIA clocks per scan line, so the best we can do is 4 sprites concurrently, each 54 pixels apart.

Display Code

Whatever the concerns, we're going to implement this anyway to render a test display of our ships. It is also to see, what is all about in practise. Here is, what we achieve, two sprites, player0 and player1, using the same sprite data (player1 mirrored) at the same vertical position:

Test rendering of sprites

Test rendering (an extra dot is added to test the orientation).

(As may be observed, we let go of changing the playfield color midways, as this is just complicating things.)

And here's the code:


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;
; Program:        A Simple Playfield
; System:         Atari 2600
; Source Format:  DASM
; Author:         N. Landsteiner, 2018
;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

    processor 6502
    include vcs.h
    include macro.h


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;
; Constants
;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

; tv standard specifics
; uncomment for PAL
;PAL = 1

    ifnconst  PAL
;----------------------------- NTSC

; 262 lines: 3+37 VBlank, 192 kernel, 30 overscan
; timers (@ 64 cycles)
;  VBlank    43 * 64 = 2752 cycles = 36.21 lines
;  Overscan  35 * 64 = 2240 cycles = 29.47 lines

ScanLines      = 192
T64VBlank      =  43
T64Overscan    =  35

BorderHeight   =   6
BorderClr      = $64  ; purple
ScoreClr       = $EC  ; yellow
PlayerClr      = $0E  ; white

;-----------------------------
    else
;----------------------------- PAL

; 312 lines: 3+45 VBlank, 228 kernel, 36 overscan
; timers (@ 64 cycles)
;  VBlank    53 * 64 = 3392 cycles = 44.63 lines
;  Overscan  42 * 64 = 2688 cycles = 35.36 lines

ScanLines      = 228
T64VBlank      =  53
T64Overscan    =  42

BorderHeight   =   7
BorderClr      = $C4
ScoreClr       = $2C
PlayerClr      = $0E

;-----------------------------
    endif

; general definitions

ScoresHeight   =  10
PFHeight = ScanLines - ScoresHeight - 2 * BorderHeight

; vars

frCntr    = $80
lnCntr    = $81
pfMask    = $82

SpPosY    = $83
SpGrPtr   = $84  ; 2 bytes


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;
; Initialization
;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

    org $F000

Start
    sei             ; disable interrupts
    cld             ; clear BCD mode

    ldx #$FF
    txs             ; reset stack pointer

    lda #$00
    ldx #$28        ; clear TIA registers ($04-$2C)
TIAClear
    sta $04,X
    dex
    bpl TIAClear    ; loop exits with X=$FF

;    ldx #$FF
RAMClear
    sta $00,X       ; clear RAM ($FF-$80)
    dex
    bmi RAMClear    ; loop exits with X=$7F

    sta SWBCNT      ; set console I/O to INPUT
    sta SWACNT      ; set controller I/O to INPUT


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;
; Game Init
;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

    lda #1
    sta CTRLPF       ; set up symmetric playfield graphics
    lda #0
    sta pfMask
    sta frCntr
    lda #PlayerClr   ; set player sprite colors
    sta COLUP0
    sta COLUP1
    lda #8           ; flip player 1 horizontally
    sta REFP1


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;
; Start a new Frame / VBLANK
;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

Frame
    lda #$02
    sta WSYNC        ; wait for horizontal sync
    sta VBLANK       ; turn on VBLANK
    sta VSYNC        ; turn on VSYNC
    sta WSYNC        ; leave VSYNC on for 3 lines
    sta WSYNC
    sta WSYNC
    lda #$00
    sta VSYNC        ; turn VSYNC off

    lda #T64VBlank   ; set timer for VBlank
    sta TIM64T


                     ; set up sprites position (same each frame, anyway)
                     ; 30 px from top
SPosFromTop = 30
SpBottom = PFHeight + 1 - SPosFromTop

    lda #SpBottom
    sta SpPosY

                     ; and set up graphics pointer for skip-draw

    lda #<[SpriteEnd - SpBottom]
    sta SpGrPtr
    lda #>[SpriteEnd - SpBottom]
    sta SpGrPtr+1

    sta WSYNC        ; horizontal sprite positioning (ships inbounds at x = 8..155)
    lda #24          ; 16px from border
    ldx #0
    jsr bzoneRepos
    lda #142
    ldx #1
    jsr bzoneRepos
    sta WSYNC
    sta HMOVE        ; strobe HMOVE to set fine adjustment (activate h-movement)

    lda #0           ; all sprites off
    sta GRP0
    sta GRP1
    sta ENAM0
    sta ENAM1
    sta ENABL

VBlankWait
    lda     INTIM
    bne VBlankWait   ; wait for timer
    sta WSYNC        ; finish current line
    ;sta HMOVE
    sta VBLANK       ; turn off VBLANK


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;
; Visible Kernel
;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

Scores
    ; just a dummy, render alternating lines
    ldy #[ScoresHeight-1]
    ldx #0
    stx COLUBK

ScoresLoop
    sta WSYNC
    tya
    and #1
    beq s1
    lda #ScoreClr
s1    sta COLUBK
    dey
    bpl ScoresLoop


TopBorder
    sta WSYNC
    lda #BorderClr
    sta COLUBK
    ldy #BorderHeight
topLoop
    sta WSYNC
    dey
    bne topLoop


Playfield
    lda #$0         ; bg color to black
    sta COLUBK
    lda #BorderClr
    sta COLUPF      ; playfield color
    lda #16         ; set up playfield border
    sta PF0
    lda pfMask
    sta PF1

    ldy #[PFHeight]
    sec

PfLoop
    sta WSYNC
    dey

    tya              ; skip-draw style vertical sprite drawing
    sbc SpPosY
    adc #SpriteHeight
    bcs skipDraw
    nop              ; nothing to draw
    nop
    sec
    bcs skipDrawEnd
skipDraw
    lda (SpGrPtr),Y  ; draw sprite (bottom-up)
    sta GRP0         ; player0
    sta GRP1         ; player1
skipDrawEnd

    tya              ; flickering line animation
    and #1
    eor pfMask
    sta PF1

    cpy #0
    bne PfLoop


BottomBorder
    sta WSYNC
    lda #BorderClr
    sta COLUBK

    lda #0
    sta PF0           ; playfield off
    sta PF1
    sta PF2
    sta GRP0          ; all sprites off
    sta GRP1
    sta ENAM0
    sta ENAM1
    sta ENABL

    ldy #BorderHeight
btmLoop
    sta WSYNC
    dey
    bne btmLoop

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;
; Overscan
;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

OverscanStart
    lda #$02
    sta VBLANK
    sta WSYNC
    lda #T64Overscan  ; set timer for overscan
    sta TIM64T

    inc frCntr        ; increment frame counter
    lda frCntr
    and #3
    bne OverscanWait
    lda pfMask        ; flip playfield mask
    eor #1
    sta pfMask

OverscanWait
    lda INTIM
    bne OverscanWait  ; wait for timer
    jmp Frame


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;
; Horizontal Positioning
;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

    org $F8F0

; Battlezone style exact horizontal repositioning with lookup table
; A = horizontal position in pixel
; X = object
;     0 = Player0
;     1 = Player1
;     2 = Missile0
;     3 = Missile1
;     4 = Ball

bzoneRepos                 ; addr,cycles
    sta WSYNC              ; $00, 3    start of scanline.
    sec                    ; $02, 2    set carry flag
divideby15
    sbc #15                ; $03, 2    waste 5 cycles by dividing X-pos by 15
    bcs divideby15         ; $05, 2/3  now at 11/16/21/26/31/36/41/46/51/56/61/66

    tay                    ; $07, 2
    lda fineAdjustTable,Y  ; $08, 5    5 cycles by guaranteeing we cross a page boundary
    sta HMP0,X             ; $0B, 4    store fine adjustment

    sta RESP0,X            ; $0D, 4    set the rough position
    rts                    ; $0F, 6    now at 21/26/31/36/41/46/51/56/61/66/71
                           ; $10

; Note: loop at "bcs divideby15" must not cross a page boundary

;-----------------------------
; This table is on a page boundary to guarantee the processor
; will cross a page boundary and waste a cycle in order to be
; at the precise position

fineAdjustBegin
    .byte %01110000 ; Left 7
    .byte %01100000 ; Left 6
    .byte %01010000 ; Left 5
    .byte %01000000 ; Left 4
    .byte %00110000 ; Left 3
    .byte %00100000 ; Left 2
    .byte %00010000 ; Left 1
    .byte %00000000 ; No movement.
    .byte %11110000 ; Right 1
    .byte %11100000 ; Right 2
    .byte %11010000 ; Right 3
    .byte %11000000 ; Right 4
    .byte %10110000 ; Right 5
    .byte %10100000 ; Right 6
    .byte %10010000 ; Right 7

fineAdjustTable = fineAdjustBegin - %11110001   ; Note: %11110001 = -15


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;
; Data
;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;


    .byte $FF ; a full byte, just to check boundaries :-)

Sprite
    .byte $00
    .byte $10 ; |   X    |
    .byte $10 ; |   X    |
    .byte $58 ; | X XX   |
    .byte $BE ; |X XXXXX |
    .byte $73 ; | XXX  XX|
    .byte $6D ; | XX XX X|
    .byte $73 ; | XXX  XX|
    .byte $BE ; |X XXXXX |
    .byte $58 ; | X XX   |
    .byte $10 ; |   X    |
    .byte $11 ; |   X   X|   extra pixel at D0 to check vertical orientation

SpriteEnd = *

SpriteHeight = SpriteEnd - Sprite

    .byte $FF ; a full byte, just to check boundaries :-)

    .byte $00
    .byte $70 ; | XXX    |
    .byte $78 ; | XXXX   |
    .byte $5C ; | X XXX  |
    .byte $9E ; |X  XXXX |
    .byte $C3 ; |XX    XX|
    .byte $BC ; |X XXXX  |
    .byte $C3 ; |XX    XX|
    .byte $9E ; |X  XXXX |
    .byte $5C ; | X XXX  |
    .byte $78 ; | XXXX   |
    .byte $70 ; | XXX    |


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;
; Interrupt and reset vectors
;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

    org $FFFA
    .word Start       ; NMI
    .word Start       ; Reset
    .word Start       ; IRQ

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    end
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

Reconsidering Sprites

While this looks nice, it won't do: As soon as we hit the left border, there are at least two sprites which may show up, the ball and the missile of player1, closely followed by player0 and the missile0. Using this code, we will barely have the time to set up a single sprite in horizontal blank, not to speak of two of them. As we are done with the second, we're also half-ways into the screen. — Impossible!

Timings of sprites

Timings of sprites and where they (may) show up earliest (left most) on a scan-line.

After all, we may have been overly optimistic, when we considered our little project to be right in the comfort zone of the VCS! We may either have to switch to a double-line kernel, or have to content ourselves to go with an interlaced display, probably 3 different frames as in Pac-Man-style flickery. — Or we may come up with something completely different for vertical rendering.

But this is another story, or, well, the same, another episode.

 

 

Next:  Episode 5: Let's Waste Some Bytes!

Previous:   Episode 3: Sprites

Back to the index.

— This series is part of Retrochallenge 2018/04. —