Retrochallenge 2017/04:
Personal Computer Space Transactor 2001

Episode 6: Attractive Saucers

Were we're introducing the fierce saucers (here still peaceful) and get, while not as simple as intended, the attract mode for free.

Code – write-up balance is really something, I've to improve on in order to progress with this project. There were some things I wanted to see next to another in a write-up, and, fortunately, we've done this already. But now, as we're coming to the more complex things, we wont be able to keep up with the previous level of detail. This may be sad, as there are lots of things to mention and to discuss, but, yeah….

On the bright side, we arrive at what is already the fully implemented attract mode including all the logic regarding saucer movement and animation. For testing purpose, we're also doing a few things that will be not in attract mode, namely ticking the clock and inverting the screen, as the clock wraps around at 99/00. And this is, what looks like:

Saucers/attract screen in Personal Computer Space Transactor 2001 (green phosphor)

Hieroglyphs in space? — Saucers, flying saucers!

Try it in in-browser emulation.

General Obeservations

Before we touch any of the details, there are actually a few things to write home about. As a few of the readers may recall, I implemented the game for RetroChallenge 2016/10 for the early 1960's DEC PDP-1 (announced Nov/Dec. 1959). While the PDP-1 features just 2 usable registers and a rather restricted, RISC-like instruction set, coding the same game in PDP-1 assembler was actually fun and intuitive, thanks to the straight-forward instruction set and universal indirect addressing. While the PDP-1 is far from an orthogonal machine, coding for it was much more orthogonal experience, when it came to approaching specific tasks.

The 6502, while providing 3 principal registers and a stack, proved much more complicated: Frequently, we've to handle 3 things at the same time, like x and y coordinates and a value (e.g., screen-x, screen-y, and a screen code to go there). If there's one more thing to handle, like processing any of this values with regard to yet another one, you're running out of resources. So there's still the stack. But we may push the accumulator only, so we may preserve only 2 out of 3 registers, since we'll have to destruct the contents of one of them. Also, the order of execution matters, since the stack is last-in-first-out (LIFO) and, if there is a subroutine involved, the processor is accessing the stack, too. So you have to observe nesting levels of code, which isn't always an option.

But the biggest hassle is indirect addressing, because — apart from the jmp instruction — it's only available for zero page addresses. Moreover, there's always either the X or the Y register involved, so, while the zero-page is really more like a set of additional registers, you're losing another register in the process. The 6502 is noticeably designed with higher languages in mind and coding in assembler is often worse than with the humble PDP-8 (the epitome of the mini computer — sharing the notion of zero page memory as a set of additional registers, but actually optimizing on this by auto-indexing registers and a more general indirect addressing scheme). As a result, the path from the idea of an algorithm to implementation is a much more complicated one as on the PDP-1, where a thought translates directly to code, forcing us, while coding for the 6502, into a state of mind which is more and more about schemes and patterns that may be used to arrive at an implementation. Overall, this renders coding for the 6502 a comparatively much more nerdy experience.

Dirty Details

And here are the nasty details:

Asynchrounous Screen Updates

We mentioned before that we were going to have a queue for storing screen addresses and screen codes to be updated during V BLANK by the interrupt routine. Actually, we're going to have two of them, one for resetting background characters and one for fresh content. Looping over a repeating structure of bytes as in address Lo, address Hi, screen code, ... and copying the value (screen code) into the given address in screen memory should be easy. But, in fact, it isn't. Neither of the indirect address modes is of help, as none of them allows us to use the address bytes already in the queue as a pointer (that is, if the queue isn't in the zero page, which is sadly not an option). Copying the address and reaccessing them by indirect addressing would cost us 12 cycles per address byte and isn't an option for a loop in the interrupt routine, so we've to do it with self-modifying code:

; symbols / constants

charQueue = $027A     ;start of cassette buffer, used as a drawing buffer
resetQueue = charQueue+60 ;buffer for screen resets

; zero-page addresses

qPosX = $2B           ;temp x coor for display purpose
qPosY = $2C           ;temp y coor for display purpose
qScreenCode = $2D     ;temp screen code for display purpose
charQueuePtr = $2E    ;pointer to top offset of charQueue
resetQueuePtr = $2F   ;pointer to top offset of charQueue

; draws chars in charQueue of (screenCode, addrLo, addrHi)*
; self-modifying (sets address at .dcqScreen, sta xxxx)
drawCharQueue
                ldx charQueuePtr          ;get top-of-queue pointer
                beq .dcqDone              ;exit, if empty
                dex
.dcqLoop        lda charQueue, x          ;get screen address hi-byte
                sta .dcqScreen+2          ;fix-up
                dex
                lda charQueue, x          ;get screen address lo-byte
                sta .dcqScreen+1          ;fix-up
                dex
                lda charQueue, x          ;get screen code
                eor videoMask             ;adjust for normal/reverse video
.dcqScreen      sta $ffff                 ;store it (dummy address)
                dex
                bpl .dcqLoop
                lda #0                    ;reset top-of-queue pointer
                sta charQueuePtr
.dcqDone        rts

And there's also a copy of this code (drawResetQueue) for drawing the characters stored in the reset-queue (resetQueue).

This is the code for pushing a screen code/character and an address onto the queue, which also eclipses any off-screen characters:

; a single character 'sprite routine'
; pushes a screen code and address onto the charQueue, if on-screen
pushScreenCode
                lda qPosY
                bmi .pcqDone  ;negative
                cmp #25       ;gte 25 (off-screen to the bottom)?
                bcs .pcqDone
                lda qPosX
                bmi .pcqDone  ;negative
                cmp #40       ;gte 40 (off-screen to the right)?
                bcs .pcqDone

                ldx charQueuePtr
                lda qScreenCode
                sta charQueue, x
                inx
                ldy qPosY
                lda qPosX
                clc
                adc screenLinesLo, y
                sta charQueue, x
                inx
                lda #0
                adc screenLinesHi, y
                sta charQueue, x
                inx
                stx charQueuePtr

.pcqDone        rts

And, yes, there's another copy of this code (pushScreenReset) for servicing the reset-queue.

Pushing Saucers

On the bright side, we've abstracted much of what is involved in servicing the screen. Therefor, pushing the characters of the saucer outline is rather straight forward. As a saucer is 3 characters wide (see below), there may be a negative offset of two horizontal screen positions with a bit of the saucer still left visible. Thus, we've either to use negative offsets, or we've to use a positive offset in our internal system of coordinates. We decide to go with the latter, adding an offset of 2 both to the x and y coordinates respectively.

;saucer outline, $20 (blank) ignored

!byte $20,$64,$20  ;  ▁
!byte $73,$20,$6B  ; ┤ ├
!byte $20,$63,$20  ;  ▔
displaySaucer ;pushes a saucer at saucerX /saucerY onto the charQueue
                ldx saucerY
                dex                ;2 pos offset
                dex
                dex                ;-1 for top row
                stx qPosY
                ldx saucerX
                dex                ;2 pos offset
                dex
                stx qPosX
                lda #$64
                sta qScreenCode
                jsr pushScreenCode  ;$64 at x, y-1
                ldx qPosY
                inx
                stx qPosY
                ldx qPosX
                dex
                stx qPosX
                lda #$73
                sta qScreenCode
                jsr pushScreenCode  ;$73 at x-1, y
                ldx qPosX
                inx
                stx qPosX
                ldx saucerPhase
                lda saucerPhases, x
                sta qScreenCode
                jsr pushScreenCode  ;center code at x, y
                ldx qPosX
                inx
                stx qPosX
                lda #$6B
                sta qScreenCode
                jsr pushScreenCode  ;$6B at x+1, y
                ldx qPosY
                inx
                stx qPosY
                ldx qPosX
                dex
                stx qPosX
                lda #$63
                sta qScreenCode
                jsr pushScreenCode ; $63 at x, y+1
                rts

And there's a similar routine for clearing a saucer at it's current position, using our getStar routine for the right background screen code. We could optimize our code here for specific movements, but we've to go for the worst case with regard to run time anyway. So we decide to go on — so there's still a chance of us finishing the project — and stick to the worst case approach, resettimng and redrawing the entire outline each time the saucer moves.

The animation of the saucer's center is yet another routine, which is to be called more often.

animateSaucer ;saucer center animation
                lda saucerPhaseDir ;flag for animation direction: 0 = left, 1 = right
                beq .asLeft
                ldx saucerPhase
                inx
                cpx #10
                bne .asNext
                ldx #0
                beq .asNext
.asLeft
                ldx saucerPhase
                dex
                bpl .asNext
                ldx #9
.asNext         stx saucerPhase
                lda saucerPhases, x
                sta qScreenCode
                ldx saucerX
                dex                ;2 pos offset
                dex
                stx qPosX
                ldx saucerY
                dex                ;2 pos offset
                dex
                stx qPosY
                jsr pushScreenCode
                rts

; variables

saucerX         !byte 0
saucerY         !byte 0
saucerDx        !byte 0
saucerDy        !byte 0
saucerPhase     !byte 0
saucerPhaseDir  !byte 0
saucerPhaseMask !byte 0
saucerCnt       !byte 0
saucerLegCnt    !byte 0

; data

saucerPhases
                !byte $20,$65,$54,$47,$42,$5D,$48,$59,$67,$20

Finally, regarding display code, we've to service the saucer twice by an offset. For this we introduce a routine flipping the saucer's y coordinate by an offset (assembler symbol saucerOffset = maxY/2 = 15):

flipSaucer ;flips saucerY by saucerOffset
                lda saucerY
                clc
                adc #saucerOffset
                cmp #maxY
                bcc .fpSave
                sec
                sbc #maxY
.fpSave         sta saucerY
                rts

Roaming the Heavens

This leaves us yet the task of moving the saucer around. We'll do this every 7 frames and we're going to control this by a counter of its own (allowing us to freely configure the speed to our liking). As the saucer(s) move(s) for a certain time and then either sits idle or changes its direction, we have to set up a leg-count and decide on dx and dy values and also for the direction and speed of the center animation for this leg. For this we implement a simple 1-byte random number generator:

ran = $31             ;random number (1 byte)

random ; a simple random number generator
                lda ran
                ror
                lda ran
                ror
                eor %11011001
                sta ran
                rts

The rest is rather a matter of sitting down and tediously coding our random-based decision tree for setting up all the respective values controlling the saucer and ccalling the routines for clearing, display and animation as needed. (See the listing below for details.)

And here we are. For the purpose of testing, we stick with the counting seconds, which should be really set to "00" in attract mode. (This reveals a tiny glitch, regarding our plane stacking and mixing scheme, still to be addressed.) Also, we move the switch to reverse video to the seconds counter fully wrapping around, from 99 to 00.

And this is what it looks in white:

Saucers/attract screen in Personal Computer Space Transactor 2001 (white phosphor)

White phosphor (emulation).

And in reverse video:

Saucers/attract screen in Personal Computer Space Transactor 2001 (reverse video)

Reverse video (emulation).

Try it in in-browser emulation.

Code Listing

And here is our code, in its entirety (yes, we more than doubled the byte count since last episode):

! Caution, the interrupt routine used in this version does not preserve registers! (Not an issue here.)

!to "saucer.prg", cbm ;set output file and format

; symbols / constants

ticksPerSecond = 60   ;60: time in game corresponds to NTSC timing
charQueue = $027A     ;start of cassette buffer, used as a drawing buffer
resetQueue = charQueue+60 ;buffer for screen resets

maxX = 45             ;x-coors max value
maxY = 30             ;y-coors max value

saucerSpeed = 7       ;frames
saucerOffset = 15     ;screen lines y offset

; zero-page
; BASIC input buffer at $23 .. $5A may be reused safely (cf, PET 2001 manual)

gameState = $23       ;0: attract, 1: active
fIRQ  = $24           ;flag to synchronize irq operations
fRepaint = $25        ;flag for video rendering/irq control
ticks = $26           ;ticks counter
videoMask = $27       ;0: normal, $80: reverse (xor-ed)
IRQVector = $28       ;backup of original irq vector (2 bytes)
frameCounter = $2A    ;counter for animations
qPosX = $2B           ;temp x coor for display purpose
qPosY = $2C           ;temp y coor for display purpose
qScreenCode = $2D     ;temp screen code for display purpose
charQueuePtr = $2E    ;pointer to top offset of charQueue
resetQueuePtr = $2F   ;pointer to top offset of charQueue
scoreRepaint = $30    ;flag to request a repaint (buffer to fRepaint)
ran = $31             ;random number (1 byte)
PT1 = $50             ;versatile pointer (2 bytes)
PT2 = $52             ;versatile pointer (2 bytes)

; intro

; insert a tiny BASIC program, calling our code at $044C (1100)
;
; 10 REM PERSONAL COMPUTER SPACE
; 20 REM TRANSACTOR 2001 (NL,2017)
; 30 SYS 1100

                * = $0401

                !byte $1F, $04, $0A, $00, $8F, $20, $50, $45 ; $0401
                !byte $52, $53, $4F, $4E, $41, $4C, $20, $43 ; $0409
                !byte $4F, $4D, $50, $55, $54, $45, $52, $20 ; $0411
                !byte $53, $50, $41, $43, $45, $00, $3F, $04 ; $0419
                !byte $14, $00, $8F, $20, $54, $52, $41, $4E ; $0421
                !byte $53, $41, $43, $54, $4F, $52, $20, $32 ; $0429
                !byte $30, $30, $31, $20, $28, $4E, $4C, $2C ; $0431
                !byte $32, $30, $31, $37, $29, $00, $4A, $04 ; $0439
                !byte $1E, $00, $9E, $20, $31, $31, $30, $30 ; $0441
                !byte $00, $00, $00 ; $0449 .. $044B


; main

                * = $044C
                ; reset / setup
                cld             ;reset BCD flag
                lda #0
                sta fRepaint

setup           ; setup irq vector
                sei
                lda $91
                and #$F0
                cmp #$E0        ;is it ROM 2.0 or higher?
                bne .rom1       ;no, it's ROM 1.0
.rom2           lda $90
                sta IRQVector
                lda $91
                sta IRQVector+1
                lda #<irqRoutine
                sta $90
                lda #>irqRoutine
                sta $91
                jmp .setupDone
.rom1           lda $219
                sta IRQVector
                lda $21A
                sta IRQVector+1
                lda #<irqRoutine
                sta $219
                lda #>irqRoutine
                sta $21A
.setupDone      cli

init
                lda #0
                sta gameState
                sta videoMask
                sta fRepaint
                jsr background
                lda #0
                sta score1
                sta score2
                sta time1
                sta time2
                sta ticks
                sta frameCounter
                sta charQueuePtr
                sta saucerCnt
                sta saucerLegCnt

                lda $E844  ; initialize random number from VIA timer 1 
                sta ran

                lda #10
                sta saucerY
                lda #18
                sta saucerX
                jsr displaySaucer
                jsr animateSaucer

                lda #1
                sta fRepaint
                sta fIRQ


; main job loop
loop
                lda fIRQ
                bne loop

                ;manage a frame
                lda #0
                sta scoreRepaint
                lda ticks             ;manage time
                sec
                sbc #ticksPerSecond   ;has a second passed?
                bcc .gameFrame        ;no
                sta ticks
                inc time1
                lda time1
                cmp #$0A
                bne .loopScoresFinal
                lda #0
                sta time1
                inc time2
                lda time2
                cmp #$0A
                bne .loopScoresFinal
                lda #0
                sta time2
                jsr revertVideo
.loopScoresFinal
                lda #1
                sta scoreRepaint

.gameFrame
                jsr saucerHandler

.loopIter sei
                lda scoreRepaint
                ora resetQueuePtr
                ora charQueuePtr
                sta fRepaint
.loopEnd        lda #1
                sta fIRQ
                cli
                jmp loop


; irq handling

irqRoutine

                inc ticks             ;manage time
                inc frameCounter

.checkRepaint
                lda fRepaint
                beq .irqDone
                jsr drawResetQueue
                jsr drawScores
                jsr drawCharQueue

.irqDone
                lda #0
                sta fRepaint
                sta fIRQ
                jmp (IRQVector)


; subroutines

background ;fills the screen with stars
                ldx #24
.row            lda screenLinesLo, x
                sta PT1
                lda screenLinesHi, x
                sta PT1+1
                ldy #39
.col            jsr getStar
                sta (PT1), y
                dey
                bpl .col
                dex
                bpl .row
                rts


getStar ;returns a background screen code (in AC) for row X, col Y
                lda starMaskY, x
                beq .blank
                and starMaskX, y
                beq .blank
                lda #$2E ; return a dot
                rts
.blank
                lda #$20 ; return a blank
                rts


; score and time display
; screen locations of score and time numerals
screenAddressScore1 = $8000 + 4*40 + 36
screenAddressScore2 = $8000 + 10*40 + 36
screenAddressTime1 = $8000 + 16*40 + 36
screenAddressTime2 = $8000 + 16*40 + 33

drawScores ;draws scores and time display
                ldy score1
                lda #<screenAddressScore1
                sta PT1
                lda #>screenAddressScore1
                sta PT1+1
                jsr drawDigit
                ldy score2
                lda #<screenAddressScore2
                sta PT1
                lda #>screenAddressScore2
                sta PT1+1
                jsr drawDigit
                ldy time1
                lda #<screenAddressTime1
                sta PT1
                lda #>screenAddressTime1
                sta PT1+1
                jsr drawDigit
                ldy time2
                lda #<screenAddressTime2
                sta PT1
                lda #>screenAddressTime2
                sta PT1+1
                jsr drawDigit
                rts

drawDigit ;draws a digit (screen address in PT1, digit in Y)
                ldx digitOffsets, y
                ldy #0
                lda #4
                sta PT2
.dgRow          lda digits, x
                eor videoMask ;adjust for normal/reverse video
                sta (PT1), y
                inx
                iny
                lda digits, x
                eor videoMask
                sta (PT1), y
                dec PT2
                beq .dgDone
                inx
                dey             ;reset y to zero and increment PT1 by a screen line
                clc
                lda PT1
                adc #40
                sta PT1
                bcc .dgRow
                inc PT1+1
                jmp .dgRow
.dgDone         rts


revertVideo ;reverts the screen video
                lda videoMask
                eor #$80
                sta videoMask
                ldx #24
.rvRow          lda screenLinesLo, x
                sta PT1
                lda screenLinesHi, x
                sta PT1+1
                ldy #39
.rvCol          lda (PT1), y
                eor #$80
                sta (PT1), y
                dey
                bpl .rvCol
                dex
                bpl .rvRow
                rts


; draws chars in charQueue of (screenCode, addrLo, addrHi)*
; self-modifying (sets address at .dcqScreen, sta xxxx)
drawCharQueue
                ldx charQueuePtr          ;get top-of-queue pointer
                beq .dcqDone              ;exit, if empty
                dex
.dcqLoop        lda charQueue, x          ;get screen address hi-byte
                sta .dcqScreen+2          ;fix-up
                dex
                lda charQueue, x          ;get screen address lo-byte
                sta .dcqScreen+1          ;fix-up
                dex
                lda charQueue, x          ;get screen code
                eor videoMask             ;adjust for normal/reverse video
.dcqScreen      sta $ffff                 ;store it (dummy address)
                dex
                bpl .dcqLoop
                lda #0                    ;reset top-of-queue pointer
                sta charQueuePtr
.dcqDone        rts

; same as above, but for resetQueue
drawResetQueue
                ldx resetQueuePtr
                beq .drqDone
                dex
.drqLoop        lda resetQueue, x
                sta .drqScreen+2
                dex
                lda resetQueue, x
                sta .drqScreen+1
                dex
                lda resetQueue, x
                eor videoMask
.drqScreen      sta $ffff
                dex
                bpl .drqLoop
                lda #0
                sta resetQueuePtr
.drqDone        rts


; a single character 'sprite routine'
; pushes a screen code and address onto the charQueue, if on-screen
pushScreenCode
                lda qPosY
                bmi .pcqDone  ;negative
                cmp #25       ;gte 25 (off-screen to the bottom)?
                bcs .pcqDone
                lda qPosX
                bmi .pcqDone  ;negative
                cmp #40       ;gte 40 (off-screen to the right)?
                bcs .pcqDone

                ldx charQueuePtr
                lda qScreenCode
                sta charQueue, x
                inx
                ldy qPosY
                lda qPosX
                clc
                adc screenLinesLo, y
                sta charQueue, x
                inx
                lda #0
                adc screenLinesHi, y
                sta charQueue, x
                inx
                stx charQueuePtr

.pcqDone        rts

; same as above,but for resetQueue
pushScreenReset
                lda qPosY
                bmi .psrDone
                cmp #25
                bcs .psrDone
                lda qPosX
                bmi .psrDone
                cmp #40
                bcs .psrDone

                ldx resetQueuePtr
                lda qScreenCode
                sta resetQueue, x
                inx
                ldy qPosY
                lda qPosX
                clc
                adc screenLinesLo, y
                sta resetQueue, x
                inx
                lda #0
                adc screenLinesHi, y
                sta resetQueue, x
                inx
                stx resetQueuePtr

.psrDone        rts


random ; a simple random number generator
                lda ran
                ror
                lda ran
                ror
                eor %11011001
                sta ran
                rts


; saucer(s)

saucerHandler
                dec saucerCnt
                bmi .shUpdate
                lda scoreRepaint   ;do we have a score/time update?
                bne .shRedraw      ;yes, redraw the saucers
                jmp .shAnimate     ;just check the animation state
.shRedraw       jmp .shDisplay

.shUpdate       lda #saucerSpeed
                sta saucerCnt
                jsr clearSaucer
                jsr flipSaucer
                jsr clearSaucer
                jsr flipSaucer

                dec saucerLegCnt
                bpl .shMoveY
                jsr random         ;new random number in ac and ran
                and #15
                clc
                adc #7
                sta saucerLegCnt   ;7..22
                lda ran
                and #1
                sta saucerPhaseDir ;0/1
                ldx #3
                lda ran
                bpl .shAnimSpeed
                ldx #7
.shAnimSpeed    stx saucerPhaseMask ;3/7
                jsr random
                and #$3F
                beq .shStop         ;another opportunity to stop
                and #3
                cmp #3
                bne .shSaveDx       ;0,1,2
                lda #0
.shSaveDx       sta saucerDx
                jsr random
                and #3
                cmp #3
                bne .shSaveDy
                lda #0
.shSaveDy       sta saucerDy       ;0,1,2

.shMoveY        ldx saucerY
                lda saucerDy
                beq .shMoveX
                cmp #1
                beq .shMoveY1
                inx
                cpx #maxY
                bcc .shSaveY
                ldx #0
                beq .shSaveY
.shMoveY1       dex
                bpl .shSaveY
                ldx #maxY-1
.shSaveY        stx saucerY

.shMoveX        ldx saucerX
                lda saucerDx
                beq .shDisplay
                cmp #1
                beq .shMoveX1
                inx
                cpx #maxX
                bcc .shSaveX
                ldx #0
                beq .shSaveX
.shMoveX1       dex
                bpl .shSaveX
                ldx #maxX-1
.shSaveX        stx saucerX

.shDisplay
                jsr displaySaucer
                jsr flipSaucer
                jsr displaySaucer
                jsr flipSaucer

.shAnimate      lda frameCounter
                and saucerPhaseMask
                bne .shDone
                jsr animateSaucer

.shDone         rts

.shStop
                lda #0
                sta saucerDx
                sta saucerDy
                jmp .shMoveY


flipSaucer ;flips saucerY by saucerOffset
                lda saucerY
                clc
                adc #saucerOffset
                cmp #maxY
                bcc .fpSave
                sec
                sbc #maxY
.fpSave         sta saucerY
                rts


displaySaucer ;pushes a saucer at saucerX /saucerY onto the charQueue
                ldx saucerY
                dex                ;2 pos offset
                dex
                dex                ;-1 for top row
                stx qPosY
                ldx saucerX
                dex                ;2 pos offset
                dex
                stx qPosX
                lda #$64
                sta qScreenCode
                jsr pushScreenCode  ;$64 at x, y-1
                ldx qPosY
                inx
                stx qPosY
                ldx qPosX
                dex
                stx qPosX
                lda #$73
                sta qScreenCode
                jsr pushScreenCode  ;$73 at x-1, y
                ldx qPosX
                inx
                stx qPosX
                ldx saucerPhase
                lda saucerPhases, x
                sta qScreenCode
                jsr pushScreenCode  ;center code at x, y
                ldx qPosX
                inx
                stx qPosX
                lda #$6B
                sta qScreenCode
                jsr pushScreenCode  ;$6B at x+1, y
                ldx qPosY
                inx
                stx qPosY
                ldx qPosX
                dex
                stx qPosX
                lda #$63
                sta qScreenCode
                jsr pushScreenCode ; $63 at x, y+1
                rts

clearSaucer ;pushes a saucer at saucerX /saucerY onto the resetQueue
                ldx saucerY
                dex                ;2 pos offset
                dex
                dex                ;-1 for top row
                stx qPosY
                ldy saucerX
                dey                ;2 pos offset
                dey
                sty qPosX
                jsr getStar
                sta qScreenCode
                jsr pushScreenReset
                ldx qPosY
                inx
                stx qPosY
                ldy qPosX
                dey
                sty qPosX
                jsr getStar
                sta qScreenCode
                jsr pushScreenReset
                ldx qPosY
                ldy qPosX
                iny
                sty qPosX
                jsr getStar
                sta qScreenCode
                jsr pushScreenReset
                ldx qPosY
                ldy qPosX
                iny
                sty qPosX
                jsr getStar
                sta qScreenCode
                jsr pushScreenReset
                ldx qPosY
                inx
                stx qPosY
                ldy qPosX
                dey
                sty qPosX
                jsr getStar
                sta qScreenCode
                jsr pushScreenReset
                rts


animateSaucer ;saucer center animation
                lda saucerPhaseDir
                beq .asLeft
                ldx saucerPhase
                inx
                cpx #10
                bne .asNext
                ldx #0
                beq .asNext
.asLeft
                ldx saucerPhase
                dex
                bpl .asNext
                ldx #9
.asNext         stx saucerPhase
                lda saucerPhases, x
                sta qScreenCode
                ldx saucerX
                dex                ;2 pos offset
                dex
                stx qPosX
                ldx saucerY
                dex                ;2 pos offset
                dex
                stx qPosY
                jsr pushScreenCode
                rts


; variables

score1          !byte 0
score2          !byte 0
time1           !byte 0
time2           !byte 0

saucerX         !byte 0
saucerY         !byte 0
saucerDx        !byte 0
saucerDy        !byte 0
saucerPhase     !byte 0
saucerPhaseDir  !byte 0
saucerPhaseMask !byte 0
saucerCnt       !byte 0
saucerLegCnt    !byte 0


; data

starMaskX
                !byte $20, $00, $40, $0A, $08, $01, $82, $00
                !byte $00, $00, $00, $00, $40, $00, $00, $02
                !byte $00, $04, $20, $10, $88, $44, $00, $40
                !byte $00, $01, $20, $00, $00, $42, $14, $00
                !byte $48, $20, $00, $10, $18, $00, $00, $40

starMaskY
                !byte $40, $00, $01, $00, $00, $08, $00, $04
                !byte $00, $40, $00, $02, $00, $00, $01, $00
                !byte $04, $00, $10, $00, $20, $00, $01, $00
                !byte $80

screenLinesHi
                !byte $80
                !byte $80
                !byte $80
                !byte $80
                !byte $80
                !byte $80
                !byte $80
                !byte $81
                !byte $81
                !byte $81
                !byte $81
                !byte $81
                !byte $81
                !byte $82
                !byte $82
                !byte $82
                !byte $82
                !byte $82
                !byte $82
                !byte $82
                !byte $83
                !byte $83
                !byte $83
                !byte $83
                !byte $83

screenLinesLo
                !byte $00
                !byte $28
                !byte $50
                !byte $78
                !byte $A0
                !byte $C8
                !byte $F0
                !byte $18
                !byte $40
                !byte $68
                !byte $90
                !byte $B8
                !byte $E0
                !byte $08
                !byte $30
                !byte $58
                !byte $80
                !byte $A8
                !byte $D0
                !byte $F8
                !byte $20
                !byte $48
                !byte $70
                !byte $98
                !byte $C0

digits
                ;0
                !byte $62,$62
                !byte $61,$E1
                !byte $61,$E1
                !byte $FC,$FE

                ;1
                !byte $20,$6C
                !byte $20,$E1
                !byte $20,$E1
                !byte $20,$E1

                ;2
                !byte $62,$62
                !byte $20,$E1
                !byte $EC,$E2
                !byte $FC,$62

                ;3
                !byte $62,$62
                !byte $20,$E1
                !byte $7C,$FB
                !byte $62,$FE

                ;4
                !byte $7B,$6C
                !byte $61,$E1
                !byte $E2,$FB
                !byte $20,$E1

                ;5
                !byte $62,$62
                !byte $61,$20
                !byte $E2,$FB
                !byte $62,$FE

                ;6
                !byte $7B,$20
                !byte $61,$20
                !byte $EC,$FB
                !byte $FC,$FE

                ;7
                !byte $62,$62
                !byte $20,$E1
                !byte $20,$E1
                !byte $20,$E1

                ;8
                !byte $62,$62
                !byte $61,$E1
                !byte $EC,$FB
                !byte $FC,$FE

                ;9
                !byte $62,$62
                !byte $61,$E1
                !byte $E2,$FB
                !byte $20,$E1

digitOffsets
                !byte 0, 8, 16, 24, 32, 40, 48, 56, 64, 72

saucerPhases
                !byte $20,$65,$54,$47,$42,$5D,$48,$59,$67,$20

(Assembles to 1,309 bytes of binary code.)

 

— Stay tuned! —

 

Next:  Episode 7: Rocket (Phew!)

Previous:  Episode 5: Sync!

Back to the index.

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