Back to Hardware

Anaconda

22 Dec 2018
Progress: Complete

This is page 6 of the Games Console project.

If you didn't recognise it yet, the first three games I made are a tribute to Timesplitters 2. One of the most surprisingly delightful easter eggs in all of video games is the temporal uplink. This device is a little laptop that's used to show you the map, your objectives, enemy locations and so on. But hidden throughout the levels are game cartridges, which when plugged into the temporal uplink start these excellent little minigames. Anaconda is the first one you find.

What I loved about Timesplitters 2 is that you could be on a really difficult stealth mission, totally serious, and then you pull out the temporal uplink and start playing jolly little Anaconda. And true to the Free Radical philosophy, the Anaconda soundtrack could be selected as backing music during deathmatches. Oh, nostalgia...

I'm not sure if I thought to look at screenshots at the time or if I just did it all from memory, but here's what the game looked like:

Screenshot of Anaconda

In my version I either forgot or couldn't be bothered with the stripes. Also I should have made the snake's head bigger, as you probably saw in the video it's quite easy to just miss the food dots.

Oscilloscope screenshot of Anaconda

Now that I think about it, they shouldn't be dots, they should be crosses. And some of them should move. Tut tut, I really could have done a lot better with this one.

Music

Let's start by looking at the audio, which exists in a separate file (audio.asm) that's included into most of the games. The ATmega128 has four timers, two are 8-bit and two are 16-bit. The first timer, timer0, is used for frame timing. It's configured to overflow at about 16ms, so approximately 60 times a second. There's no need to use an interrupt, at the end of the frame drawing, we can just poll the timer's flag to see when it's time to draw the next frame.

This leaves three timers for sound generation. The two 16-bit timers can be used directly. The 8-bit timer has a much smaller range of in-tune notes it could produce, so I reserved this for just bass notes. Later, when I got into the ATtiny MIDI stuff, I realized that you can extend the resolution of an 8-bit timer by working with the prescalers too, but in this project we didn't do that.

The Javascript MIDI processor is very simple, it just samples the file every 16ms, and writes down which notes are on. For my purposes this was a good enough timing resolution, and means we can run the audio routine in sync with the drawing routine. Since MIDI note data is 7-bits, and the noise channel is just an on/off state, the noise channel is stored as the MSB of one of the other channels. There's no compression, but 2 minutes of music data takes up only about 10kB, and the cartridges are 64kB, so I didn't worry about it.

One further thing is sound effects. The music processing is run every frame, but when something happens in-game we need to override it. The fixed areas of SRAM that were defined in the bootloader are used to send messages to the audio code. The code is quite short, here's the file that's included into any game that needs it (along with a huge file filled with the music data).

### audio.asm ###



/*
    To init music:

    ldi r16, HIGH(music1*2)
    sts MUSIC_START_H, r16
    ldi r16,  LOW(music1*2)
    sts MUSIC_START_L, r16
    rcall resetMusic
    
    
    On each frame call:
    
    rcall processAudio
    
*/
    


processAudio:
    
    ldi r17,0
    lds ZH, EFFECT_H
    lds ZL, EFFECT_L
    lpm r16,Z
    cpi r16,0
    brne processSoundEffect

continueProcessAudio:
    lds ZH, MUSIC_H
    lds ZL, MUSIC_L

    lpm r16,Z+
    cpi r16,0
    breq resetMusic

    
    rcall setNote1
    lpm r16,Z+
    sbrs r17,0
    rcall setNote2
    lpm r16,Z+  
    rcall setNote3
    
    sts MUSIC_H, ZH
    sts MUSIC_L, ZL

    ret

resetMusic:
    lds ZH, MUSIC_START_H
    lds ZL, MUSIC_START_L
    sts MUSIC_H, ZH
    sts MUSIC_L, ZL
    rcall allNotesOff
    rjmp processAudio

processSoundEffect:
    sbrc r16,7
    rjmp effectIsNoise

    rcall setNote2

soundEffectEnd:
    adiw Z,1
    sts EFFECT_H, ZH
    sts EFFECT_L, ZL
    sbr r17,1
    rjmp continueProcessAudio
    

effectIsNoise:
    ;ldi r17,0
    cbr r17,0b00010000
    sbrc r16,7
    ;ldi r17, 0b00010000
    sbr r17,0b00010000
    out PORTE,r17

    rjmp soundEffectEnd


    
setNote1:
    cpi r16,127
    breq note1Off
    
    push ZL
    push ZH
    ldi ZL, LOW(musicNoteLookup*2)
    ldi ZH,HIGH(musicNoteLookup*2)

    sbrc r17,0          ; if noise channel is already on due to an effect, skip
    rjmp setNote1Next
    ;ldi r17,0  
    cbr r17,0b00010000
    sbrc r16,7
    sbr r17,0b00010000
    ;ldi r17, 0b00010000
    out PORTE,r17
    
setNote1Next:

    lsl r16
    add ZL, r16
    clr r16
    adc ZH, r16

    lpm r16,Z+
    out OCR1AL, r16
    lpm r16,Z+
    out OCR1AH, r16
    
    pop ZH
    pop ZL
    ldi r16, (1<<WGM12)|(1<<CS10)
    out TCCR1B, r16         ; CTC/waveform generation mode, clock select
    ret
note1Off:
    ldi r16,0
    out PORTE,r16
    out TCCR1B, r16 
    ret

setNote2:
    cpi r16,127
    breq note2Off
    push ZL
    push ZH
    ldi ZL, LOW(musicNoteLookup*2)
    ldi ZH,HIGH(musicNoteLookup*2)
    
    lsl r16
    add ZL, r16
    clr r16
    adc ZH, r16
    
    lpm r16,Z+
    subi r16,1
    sts OCR3AL, r16
    lpm r16,Z+
    sts OCR3AH, r16
    
    pop ZH
    pop ZL
    ldi r16, (1<<WGM12)|(1<<CS10)
    sts TCCR3B, r16 ; CTC/waveform generation mode, clock select
    ret
note2Off:
    ldi r16,0
    sts TCCR3B, r16
    ret

setNote3:
    cpi r16,127
    breq note3Off
    
    push ZL
    push ZH
    ldi ZL, LOW(musicNoteLookup*2)
    ldi ZH,HIGH(musicNoteLookup*2)
    
    subi r16,12
    lsl r16
    add ZL, r16
    clr r16
    adc ZH, r16
    
    push r17
    lpm r17,Z+
    lpm r16,Z+
    sbrs r17,7
    subi r16,1
    out OCR2, r16
    pop r17
    
    pop ZH
    pop ZL
    ldi r16,(1<<WGM21)|(1<<COM20)|(1<<CS22)
    out TCCR2,r16
    ret
    
note3Off:
    ldi r16,0
    out TCCR2,r16
    ret

allNotesOff:
    rcall note1Off
    rcall note2Off
    rcall note3Off
    ldi r16, HIGH(audioEffectOff*2)
    sts EFFECT_H, r16
    ldi r16,  LOW(audioEffectOff*2)
    sts EFFECT_L, r16
    ret
    

audioEffectOff: .db 0,0

musicNoteLookup:    
.dw $FFFF,$F1A1,$E411,$D744,$CB2F,$BFC8,$B504,$AADB,$A144,$9837,$8FAC,$879C,$8000,$78D0,$7209,$6BA2,$6598,$5FE4,$5A82,$556E,$50A2,$4C1C,$47D6,$43CE,$4000,$3C68,$3904,$35D1,$32CC,$2FF2,$2D41,$2AB7,$2851,$260E,$23EB,$21E7,$2000,$1E34,$1C82,$1AE9,$1966,$17F9,$16A1,$155B,$1429,$1307,$11F6,$10F3,$1000,$0F1A,$0E41,$0D74,$0CB3,$0BFC,$0B50,$0AAE,$0A14,$0983,$08FB,$087A,$0800,$078D,$0721,$06BA,$0659,$05FE,$05A8,$0557,$050A,$04C2,$047D,$043D,$0400,$03C7,$0390,$035D,$032D,$02FF,$02D4,$02AB,$0285,$0261,$023F,$021E,$0200,$01E3,$01C8,$01AF,$0196,$0180,$016A,$0156,$0143,$0130,$011F,$010F,$0100,$00F2,$00E4,$00D7,$00CB,$00C0,$00B5,$00AB,$00A1,$0098,$0090,$0088,$0080,$0079,$0072,$006C,$0066,$0060,$005B,$0055,$0051,$004C,$0048,$0044,$0040,$003C,$0039,$0036,$0033,$0030,$002D


Note that the same lookup table is used for both 16 and 8 bit timers, we just ignore the least significant byte. That's not entirely true, now that I look at the code, what I actually did is round up if bit 7 was set. I have a vague recollection of wondering if this is the correct behaviour to implement, it's essentially the difference between doing floor() and round(). I doubt anyone could hear the difference though.

Trig Tables

Doing trigonometry isn't hard but there are a couple of things which make it simpler. For a start, instead of dividing the circle into 360 slices, we divide it into 256. Slightly lower resolution is a small price to pay for having easy binary calculations. It makes the most sense to have our lookup table as 256 signed bytes, full scale. Later on, when we get to the 3D stuff, we needed to worry about fiddly fractional multiplication cascades, but here it's fairly straight-forward.

Labelled diagram of how trigonometry is used to move the snake's head

The head of our snake has a direction (theta), an X and a Y coordinate. Each step, X needs to increase by cos(theta) and Y needs to increase by sin(theta). We only need one lookup table, since one lookup is just a phase shift of the other, we can add 64 (a quarter circle) and the lookup table will wrap automatically at 256. Actually, the position needs to change by our speed multiplied by the trig amounts. The lookup table gives an answer in the range of -128 to +127, but each frame we only want to move a few pixels (a few more, if the button is held down). In order to avoid an extremely jerky motion, the X and Y coordinates are double precision. The high byte is our screen coordinate, the low byte is the fractional part.

/* Function sinS(coordinate, dir)
 * Scales 8bit signed coordinate by sine of the direction
 */
sinS:
    .def cor=r16
    .def dir=r17

    push ZH
    push ZL
    ; As there is no add-immediate-with-carry, it is faster to
    ; go to the end of the table and walk backwards
    ldi ZH, HIGH(sineTable*2+255)
    ldi ZL,  LOW(sineTable*2+255)
    sub ZL, dir
    sbci ZH, $00            ; sub-with-carry 0 from high byte
    lpm dir, Z
    fmuls cor,dir
;   mov sinTheta,r1         ; result is in r1:r0
;   sbrc r0,7               ; round number up if necessary
;   inc sinTheta
    
    pop ZL
    pop ZH
    ret

fmuls is the fractional multiplication instruction and the result is stored in r1:r0. Evidently I originally planned to just round the result to 8-bit and use that, but it probably didn't work very well. The cosine function is the same except we add 64 before the lookup.

That gives us a dot that we can move around, but now we need to make a snake behind it. Each step, we push our current position and direction into a stack, then shift each element of the stack along by one, so that each part of the tail moves to the position in front of it. Instead of storing the direction directly, it made more sense to store the sin and cos values, to avoid doing a million lookups as we draw it. This means each tail segment is four bytes.

With the sin and cos offsets, if we change the order that we use them (swapping subtractions and additions), it has the effect of reversing the direction. Similarly, if we swap only one of them, it has the effect of rotating by 90 degrees. So, to draw the tail, all we do is use these same cached sin and cos amounts, first using them to stick out to the left of the snake's tail, then behind it, then to the right, and finally in front of it. This neatly draws the outline of the snake with a finite thickness.

I've written a bit more about the line-drawing algorithm on the astrolander page.

The rest of the game code is just the food, and a tedious amount of collision checking. Checking for if we've bitten ourselves is the tricky one, which means iterating over the whole tail length and seeing if it's within a certain distance of our mouth. Looking at the code, I cheated slightly here, using the manhattan distance instead of doing it properly. But over a length of 4 pixels it probably isn't too noticeable.

Right, there'll be plenty more trigonometry in the next section, so that's all for this one.

### Anaconda.asm ###



.ORG 0

    ; init frame counter
    ldi r16,0
    out TCNT0, r16
    ldi r16, (1<<CS02)|(1<<CS01)|(1<<CS00)
    out TCCR0, r16
    ldi r16, 128
    out OCR0, r16
    
    
    ; Init music
    ldi r16, HIGH(Music*2)
    sts MUSIC_START_H, r16
    ldi r16,  LOW(Music*2)
    sts MUSIC_START_L, r16
    rcall resetMusic
    

.equ snakeMaxLength = D_START+2048



.def theta=r20
.def aXL = r7
.def aYL = r8
; Format: x,y,sintheta,costheta
.def aX=r12
.def aY=r13
.def sinTheta=r14
.def cosTheta=r15

.def staticFoodX=r5
.def staticFoodY=r6
.def movingFoodX=r4
.def movingFoodY=r3
.def foodTimer  =r2

    ldi r16,0
    mov theta,r16
    mov sinTheta,r16
    ldi r16,4
    mov cosTheta,r16
    ldi r16,128
    mov aX,r16
    mov aY,r16
    
    ldi r16,255
    mov foodTimer,r16

    ldi ZH, HIGH(D_START)
    ldi ZL,  LOW(D_START)
    ldi r16,40
fillRamLoop:
    ;dec aX
    st Z+,aX
    st Z+,aY
    st Z+,sinTheta
    st Z+,cosTheta
    dec r16
    brne fillRamLoop
    
    ldi r22,2   ; snake speed timer
    
    rcall newStaticFoodPos
    
    
    ; Reset score
    ldi r16,0
    sts SCORE_L,r16
    sts SCORE_M,r16
    sts SCORE_H,r16
    
    
Main:

    ; Every so often, move the food about
    dec foodTimer
    brne foodTimerNotZero
    ldi r16,255
    mov foodTimer,r16
    call BootRandomNumber
    lds r16,RND_H
    andi r16,0b11000000
    brne dontMoveStaticFood
    rcall newStaticFoodPos  ; with 25% chance, move static food
dontMoveStaticFood:
    
    ; move /hide moving food?

foodTimerNotZero:


    rcall readController
    sbrc r16,ctrlLeft
    subi theta,-3
    sbrc r16,ctrlRight
    subi theta,3

    sbrc r16,ctrlA
    ldi r22,1

    ;sbrc r16,ctrlStart ; debug
    ;rcall lengthenSnake
    
    sbrc r16,ctrlStart
    rcall PauseGame
    
    
    dec r22
    brne dontAdvanceSnake
    

    ldi r16,2
    mov r17,theta
    rcall sinS      ; Calculate 2*sin(theta) - result is in r1:r0
    
    add aYL,r0      ; add to position
    adc aY, r1
    
    rol r0          ; Now double it and save the value
    rol r1
    mov sinTheta,r1 
    sbrc r0,7       
    inc sinTheta
    
    
    ldi r16,2       ;same for cos
    mov r17,theta
    rcall cosS

    add aXL,r0
    adc aX, r1
    
    rol r0
    rol r1
    mov cosTheta,r1 
    sbrc r0,7       
    inc cosTheta
    
    ; Remember end of table
    push ZH
    push ZL
    ldi r18,  LOW(D_START)
    ldi r19, HIGH(D_START)
    subi ZL, 4  ; Skip the last one
    sbci ZH, 0
    
shiftPosition:
    ld r16,-Z       ; Each bytes needs to move 4 spaces along...
    std Z+4,r16
    cp  ZL, r18     ; Have we reached the start of the table?
    cpc ZH, r19
    brne shiftPosition
    
    ;load new position
    push aX
    push aY
    mov r16,aX
    sbrc aXL,7
    inc aX
    st Z+,aX
    mov r16,aY
    sbrc aYL,7
    inc aY
    st Z+,aY
    st Z+,sinTheta
    st Z+,cosTheta
    pop aY
    pop aX
    
    pop ZL
    pop ZH
    
    ldi r22,2
dontAdvanceSnake:

    ;check for hitting a wall
    mov r16,aX
    cpi r16,4
    brcc notHittingWall1
    rjmp deathAnimation
notHittingWall1:
    cpi r16,251
    brcs notHittingWall2
    rjmp deathAnimation
notHittingWall2:
    mov r16,aY
    cpi r16,13
    brcc notHittingWall3
    rjmp deathAnimation
notHittingWall3:
    cpi r16,251
    brcs notHittingWall4
    rjmp deathAnimation
notHittingWall4:
    
    ; check for eating food.
    mov r16,aX
    subi r16,-4
    cp r16, staticFoodX
    brcs notEatingStaticFood
    subi r16,7
    cp r16, staticFoodX
    brcc notEatingStaticFood
    mov r16,aY
    subi r16,-4
    cp r16, staticFoodY
    brcs notEatingStaticFood
    subi r16,7
    cp r16, staticFoodY
    brcc notEatingStaticFood
    
    rcall lengthenSnake
    rcall lengthenSnake
    rcall newStaticFoodPos
    ldi r16,255
    mov foodTimer,r16
    lds r16, SCORE_L
    subi r16,-10
    sts SCORE_L, r16
    lds r16, SCORE_M
    sbci r16,-1
    sts SCORE_M, r16
    lds r16, SCORE_H
    sbci r16,-1
    sts SCORE_H, r16
    
    ldi r16, HIGH(soundEat*2)
    sts EFFECT_H, r16
    ldi r16,  LOW(soundEat*2)
    sts EFFECT_L, r16
    
    
notEatingStaticFood:

    ; check for biting ourselves
    
    push ZH
    push ZL
    mov r9,ZH
    mov r10,ZL
    ldi ZL,  LOW(D_START+40*4)  ; Don't check against our neck
    ldi ZH, HIGH(D_START+40*4)  

checkBitingLoop:
    cp r9,ZH
    cpc r10,ZL
    breq notBitingOurselves
    
    ld r18,Z+
    ld r19,Z+
    ld sinTheta,Z+
    ld cosTheta,Z+
    adiw Z,12
    
    subi r18,-4
    cp r18, aX
    brcs checkBitingLoop
    subi r18,7
    cp r18, aX
    brcc checkBitingLoop
    subi r19,-4
    cp r19, aY
    brcs checkBitingLoop
    subi r19,7
    cp r19, aY
    brcc checkBitingLoop

    pop ZL
    pop ZH
    rjmp deathAnimation
    
    
notBitingOurselves:
    pop ZL
    pop ZH

    
    
    rcall drawSnake

    ; draw Food
    out PORTA, staticFoodX
    out PORTC, staticFoodY  
    ldi r16,255
delFood:
    nop
    nop
    nop
    dec r16
    brne delFood
    
    push ZH
    push ZL
    call processAudio
    pop ZL
    pop ZH
    
    ldi r16,0
    out PORTA,r16
    out PORTC,r16
    rcall waitforframe
    
    
    rjmp Main

waitforframe:
    in r16, TIFR
    sbrs r16, OCF0
    rjmp waitforframe
    ldi r16, (1<<OCF0)
    out TIFR, r16
    ldi r16, 0
    out TCNT0, r16
    ret

; Function drawSnake
drawSnake:

    ldi r16,1
    ldi r17,10
    ldi r18,253
    ldi r19,244
    rcall drawRectangle
    
    ldi r16,240
    ldi r17,8
    ldi r18,'S'
    rcall drawChar
    ldi r18,'C'
    rcall drawChar
    ldi r18,'O'
    rcall drawChar
    ldi r18,'R'
    rcall drawChar
    ldi r18,'E'
    rcall drawChar
    subi r16,6
    push r20
    push r21
    push r22
    lds r20, SCORE_L
    lds r21, SCORE_M
    lds r22, SCORE_H
    rcall drawDec24bit
    pop r22
    pop r21
    pop r20
    
    push r9
    push r10
    
    sbiw Z,16   ; Miss the last coord
    mov r9, ZH
    mov r10, ZL
    
    ldi ZH, HIGH(D_START)
    ldi ZL,  LOW(D_START)
    /*
    ld r16,Z+
    ld r17,Z+
    ld sinTheta,Z+
    ld cosTheta,Z+
    
    ; Draw head
    mov r18,r16
    mov r19,r17
    sub r18,sinTheta
    add r19,cosTheta
    rcall drawLine
    
    
    adiw Z,12
    */
    mov r16,aX
    mov r17,aY
    adiw Z,16
    
drawRightLoop:
    cp  ZL, r10     ; Have we reached the end?
    cpc ZH, r9
    breq drawTail
    ld r18,Z+
    ld r19,Z+
    ld sinTheta,Z+
    ld cosTheta,Z+
    adiw Z,12
    
    add r18,sinTheta
    sub r19,cosTheta
    rcall drawLine
    
    rjmp drawRightLoop
    
    
drawTail:
    ld r18,Z+
    ld r19,Z+
    ld sinTheta,Z+  ;Move to the last position - don't add displacement this time
    ld cosTheta,Z+
    adiw Z,12
    rcall drawLine
    
    push ZH
    push ZL
    ldi r18, HIGH(D_START)
    ldi r19, LOW(D_START)
    mov r9,r18
    mov r10,r19
    sbiw Z,32
    
drawLeftLoop:
    cp  ZL, r10     ; Have we reached the start?
    cpc ZH, r9
    breq drawEnd
    ld cosTheta,-Z
    ld sinTheta,-Z
    ld r19,-Z
    ld r18,-Z
    sbiw Z,12
    sub r18,sinTheta
    add r19,cosTheta
    rcall drawLine
    
    
    rjmp drawLeftLoop

drawEnd:
    
    mov r18,aX
    mov r19,aY
    rcall drawLine
    
    pop ZL
    pop ZH
    pop r10
    pop r9
    
    ret







; Function lengthenSnake
lengthenSnake:
    cpi ZL, LOW(snakeMaxLength)
    brne startLengthening
    cpi ZH, HIGH(snakeMaxLength)
    brne startLengthening
    
    ret
    
startLengthening:
    push r16
    push r17
    ldi r17,16
    sbiw Z,4
    
lengthLoop:
    ld r16,Z+
    std Z+3,r16
    dec r17
    brne lengthLoop
    
    adiw Z,4
    
    pop r17
    pop r16
    ret

    
; function newStaticFoodPos
newStaticFoodPos:
    call BootRandomNumber
    lds r16, RND_H
    call BootRandomNumber
    lds r17, RND_H
    
    ;check that it hasn't spawned within the snake
    rcall checkFoodPosOK
    brne newStaticFoodPos
    
    mov staticFoodX, r16
    mov staticFoodY, r17
    
    ret

; function chechFoodPosOK (x=r16,y=r17)
; Ensures position is not within the snake
checkFoodPosOK:
    ; check it isn't too close to the edges
    cpi r16,5
    brcs cFoodPosNotOK
    cpi r16,250
    brcc cFoodPosNotOK
    cpi r17,250
    brcc cFoodPosNotOK
    cpi r17,14              ; leave room for score display
    brcs cFoodPosNotOK
    
    ; now check collision with snake
    push ZH
    push ZL
    mov r9,ZH
    mov r10,ZL
    ldi r18,  LOW(D_START)
    ldi r19, HIGH(D_START)
checkFoodPosLoop:
    cp  ZL, r10     ; Have we reached the end?
    cpc ZH, r9
    breq checkFoodPosEnd
    
    ld r18,Z+
    ld r19,Z+
    ld sinTheta,Z+
    ld cosTheta,Z+
    adiw Z,12
    
    subi r18,-4
    cp r18, r16
    brcs checkFoodPosLoop
    subi r18,7
    cp r18, r16
    brcc checkFoodPosLoop
    subi r19,-4
    cp r19, r17
    brcs checkFoodPosLoop
    subi r19,7
    cp r19, r17
    brcc checkFoodPosLoop

cFoodPosNotOK:
    ; it collides - end loop and return.
    clz
    ret
    
checkFoodPosEnd:
    pop ZL
    pop ZH
    sez ; return zero flag
    
    ret




deathAnimation:
    call allNotesOff
    
deathLoop1:
    mov r17,ZH
    mov r16,ZL
    lsr r17
    ror r16
    lsr r17
    ror r16
    lsr r17
    ror r16
    lsr r17
    ror r16
    call setNote1
    
    rcall drawSnake
    
    sbiw Z,16
    cpi ZH, HIGH(D_START+16)
    brne deathAnimCont
    cpi ZL,  LOW(D_START+16)
    brne deathAnimCont

    ; Highscore table...
    ; jmp 0
    call allNotesOff
    jmp BootRunHighscores
    
deathAnimCont:
    rcall waitforframe
    
    rjmp deathAnimation
    

    
    
    
PauseGame:
    call allnotesoff
    ldi r16, 150 ; X
    ldi r17, 100 ; Y

    ldi r18, '*'
    rcall drawChar
    ldi r18, '*'
    rcall drawChar
    ldi r18, ' '
    rcall drawChar
    ldi r18, 'P'
    rcall drawChar
    ldi r18, 'A'
    rcall drawChar
    ldi r18, 'U'
    rcall drawChar
    ldi r18, 'S'
    rcall drawChar
    ldi r18, 'E'
    rcall drawChar
    ldi r18, ' '
    rcall drawChar
    ldi r18, '*'
    rcall drawChar
    ldi r18, '*'
    rcall drawChar

    rcall readController
    sbrs r16, ctrlA
    rjmp PauseGame


    ret
    
    
    
    
    
    
    
    
    

cancelDrawLine: ret

/*  Function drawLine (x0,y0,x1,y1)
 *  My implementation of Bresenham line algorithm
 *  based on pseudocode/description from wikipedia
 */
drawLine:
    cp r16,r18
    cpc r17,r19
    breq cancelDrawLine
    
    ;Function arguments
.def x0=r16
.def y0=r17
.def dx=r18
.def dy=r19
    
    ;Local variables
    push r20
    push r21
    push r22
    push r23
    push r24
    push r25
.def slowx=r20
.def slowy=r21
.def fastx=r22
.def fasty=r23
.def err = r24
.def t   = r25

    ; First we split the magnitude and direction
    ; Need to be careful/explicit because mag could be >127

    cp dx,x0
    breq lineXeq
    brcs lineXneg       ; Carry flag set if it overflowed
    
    ldi slowx,1         ; slowx is the direction
    sub dx,x0           ; dx is now the magnitude
    rjmp lineY

lineXneg:
    ldi slowx,-1
    mov t, x0           ; t as temp var
    sub t, dx
    mov dx, t
    rjmp lineY

lineXeq:
    clr slowx
    clr dx
    
lineY:                  ; Now do the same for y
    cp dy,y0
    breq lineYeq
    brcs lineYneg
    
    ldi slowy,1
    sub dy,y0
    rjmp lineCheckDistance

lineYneg:
    ldi slowy,-1
    mov t, y0           ; t as temp var
    sub t, dy
    mov dy, t
    rjmp lineCheckDistance

lineYeq:
    clr slowy
    clr dy

lineCheckDistance:      ; Now to find which direction is "faster"
    cp dx, dy
    brcs lineDxLessthanDy
    
    mov fastx, slowx    ; x is the fast direction
    clr fasty

    eor dx, dy          ; Tripple XOR, the classy way to
    eor dy, dx          ; swap two registers
    eor dx, dy

    rjmp lineInit   

lineDxLessthanDy:
    mov fasty, slowy    ; y is the fast direction, no need to swap
    clr fastx

lineInit:
    mov err, dy         ; set err to half the furthest distance
    lsr err
    
    mov t, dy

lineNextPixel:
    sub err, dx         ; Update error term
    brcc lineStepParallel

    add err, dy         ; Make error term positive again
    add x0,slowx        ; Step diagonally
    add y0,slowy
    
    rjmp lineLoopBack

lineStepParallel:
    add x0,fastx        ; Step parallel
    add y0,fasty

lineLoopBack:
    out PORTA, x0
    out PORTC, y0
    rcall lineDel

    dec t
    brne lineNextPixel

    pop r25
    pop r24
    pop r23
    pop r22
    pop r21
    pop r20

    ret                 ; End of drawLine

lineDel:
    push r16
    ldi r16,5
lineDelLoop:
    dec r16
    brne lineDelLoop
    pop r16
    ret



//  Function drawRectangle (x,y,width,height)
drawRectangle:
    ;Function arguments
.def x0=r16
.def y0=r17
.def width=r18
.def height=r19
    
    push height
    out PORTA,x0

drawRectDown:
    inc y0
    out PORTC,y0
    rcall dRectDel
    dec height
    brne drawRectDown
    pop height  
    push width

drawRectRight:  
    inc x0
    out PORTA,x0
    rcall dRectDel
    dec width
    brne drawRectRight
    pop width

drawRectUp:
    dec y0
    out PORTC,y0
    rcall dRectDel
    dec height
    brne drawRectUp

drawRectLeft:   
    dec x0
    out PORTA,x0
    rcall dRectDel
    dec width
    brne drawRectLeft

    ret 
    
dRectDel:
    nop
    nop
    nop
    nop
    nop
    ret


/* Function readController
 * Outputs to r16: A,B,select,start,up,down,left,right
 */
readController:
    sbis SPSR,SPIF
    rjmp readController     ; Wait for reception complete
    in r16,SPDR             ; Read received data
    com r16
    push r16

    ldi r16,0b00000000      ; init controller read again
    out SPDR,r16
    pop r16
    ret


/* Function sinS(coordinate, dir)
 * Scales 8bit signed coordinate by sine of the direction
 */
sinS:
    .def cor=r16
    .def dir=r17

    push ZH
    push ZL
    ; As there is no add-immediate-with-carry, it is faster to
    ; go to the end of the table and walk backwards
    ldi ZH, HIGH(sineTable*2+255)
    ldi ZL,  LOW(sineTable*2+255)
    sub ZL, dir
    sbci ZH, $00            ; sub-with-carry 0 from high byte
    lpm dir, Z
    fmuls cor,dir
;   mov sinTheta,r1         ; result is in r1:r0
;   sbrc r0,7               ; round number up if necessary
;   inc sinTheta
    
    pop ZL
    pop ZH
    ret

/* Function cosS(coordinate, dir)
 * Scales 8bit signed coordinate by cosine of the direction
 */
cosS:
    .def cor=r16
    .def dir=r17

    push ZH
    push ZL
    ldi ZH, HIGH(sineTable*2+255)
    ldi ZL,  LOW(sineTable*2+255)   ; reuse table, but shift by pi/2
    subi dir, 192                   ; which in our notation is 64 (-192)
    sub ZL, dir
    sbci ZH, $00
    lpm dir, Z
    fmuls cor,dir
;   mov cosTheta,r1         ; result is in r1:r0
;   sbrc r0,7               ; round number up if necessary
;   inc cosTheta

    pop ZL
    pop ZH
    ret

/* Function drawChar(x0,y0,char)
 */
drawChar:
.def x0=r16
.def y0=r17
.def char=r18
    push r19
    push ZH
    push ZL
    ; Each character is a 5 byte bitmap

    ldi ZL,  LOW(bitmapFontTable*2)
    ldi ZH, HIGH(bitmapFontTable*2)
    subi char,32                    ; Font starts at ascii 32

    ldi r19,5
    mul char,r19                    ; Multiply char by 5
    movw char,r0                    ; Result is in R1:R0

    add ZL, char                    ; Add this to Z pointer
    adc ZH, r19

    ldi r19,5

drawCharLoopByte:
    lpm char, Z+
    push y0
    
drawCharLoopBit:

    sbrs char,0
    rjmp drawCharNextBit
    
    out PORTC,y0
    out PORTA,x0
    rcall delayChar
    
drawCharNextBit:
    dec y0
    lsr char
    brne drawCharLoopBit
    dec x0
    pop y0

    dec r19
    brne drawCharLoopByte
    
    dec x0                  ; Move cursor ready to draw next character
    pop ZL
    pop ZH
    pop r19
    ret

delayChar:
    push r16
    ldi r16,$07
count2:
    dec r16
    brne count2
    pop r16
    ret 

/* Function drawDec24bit(x,y,low,med,high)
 * draws a three byte number in decimal up to 9,999,999
 */
drawDec24bit:
    ; arguments
    ; x    = r16    ; x and y pass through to drawChar unchanged
    ; y    = r17
.def byteL = r20
.def byteM = r21
.def byteH = r22
    ; local
    push r18
    push r23
    ldi r18, '0'-1
    
    cpi r20, BYTE1(1000000)     ; Remove leading zeros...
    ldi r23, BYTE2(1000000)
    cpc r21, r23
    ldi r23, BYTE3(1000000)
    cpc r22, r23
    brcc d24bitChkMil
    
    cpi r20, BYTE1(100000)
    ldi r23, BYTE2(100000)
    cpc r21, r23
    ldi r23, BYTE3(100000)
    cpc r22, r23
    brcc d24bitChkHundThou
    
    cpi r20,  LOW(10000)
    ldi r23, HIGH(10000)
    cpc r21, r23
    brcc d24bitChkTenThou
    
    cpi r20,  LOW(1000)
    ldi r23, HIGH(1000)
    cpc r21, r23
    brcc d24bitChkThou
    
    cpi r20,  LOW(100)
    ldi r23, HIGH(100)
    cpc r21, r23
    brcc d24bitChkHund
    
    cpi r20,  10
    brcc d24bitChkTens
    
    rjmp d24bitRemainder
    
d24bitChkMil:
    inc r18
    subi byteL,BYTE1(1000000)
    sbci byteM,BYTE2(1000000)
    sbci byteH,BYTE3(1000000)
    brcc d24bitChkMil
    
    subi byteL,BYTE1(-1000000)
    sbci byteM,BYTE2(-1000000)
    sbci byteH,BYTE3(-1000000)
    rcall drawChar
    
    ldi r18, '0'-1
d24bitChkHundThou:
    inc r18
    subi byteL,BYTE1(100000)
    sbci byteM,BYTE2(100000)
    sbci byteH,BYTE3(100000)
    brcc d24bitChkHundThou
    
    subi byteL,BYTE1(-100000)
    sbci byteM,BYTE2(-100000)
    sbci byteH,BYTE3(-100000)
    rcall drawChar

    ldi r18, '0'-1      ; From here on we know byteH = 0
d24bitChkTenThou:
    inc r18
    subi byteL, LOW(10000)
    sbci byteM,HIGH(10000)
    brcc d24bitChkTenThou
    
    subi byteL, LOW(-10000)
    sbci byteM,HIGH(-10000)

    rcall drawChar

    ldi r18, '0'-1
d24bitChkThou:
    inc r18
    subi byteL, LOW(1000)
    sbci byteM,HIGH(1000)
    brcc d24bitChkThou
    
    subi byteL, LOW(-1000)
    sbci byteM,HIGH(-1000)

    rcall drawChar

    ldi r18, '0'-1
d24bitChkHund:
    inc r18
    subi byteL, LOW(100)
    sbci byteM,HIGH(100)
    brcc d24bitChkHund

    subi byteL, LOW(-100)
    sbci byteM,HIGH(-100)

    rcall drawChar

    ldi r18, '0'-1
d24bitChkTens:
    inc r18
    subi byteL, LOW(10)
    sbci byteM,HIGH(10)
    brcc d24bitChkTens

    subi byteL, LOW(-10)
    sbci byteM,HIGH(-10)

    rcall drawChar
d24bitRemainder:
    ldi r18, '0'
    add r18, byteL

    rcall drawChar

    pop r23
    pop r18
    ret



; signed values, in reverse order
sineTable: 
.db $FD,$FA,$F7,$F4,$F0,$ED,$EA,$E7,$E4,$E1,$DE,$DB,$D8,$D5,$D2,$CF,$CD,$CA,$C7,$C4,$C1,$BF,$BC,$B9,$B7,$B4,$B2,$AF,$AD,$AB,$A8,$A6,$A4,$A2,$A0,$9E,$9C,$9A,$98,$96,$95,$93,$91,$90,$8F,$8D,$8C,$8B,$8A,$88,$87,$86,$86,$85,$84,$83,$83,$82,$82,$82,$81,$81,$81,$81,$81,$81,$81,$82,$82,$82,$83,$83,$84,$85,$86,$86,$87,$88,$8A,$8B,$8C,$8D,$8F,$90,$91,$93,$95,$96,$98,$9A,$9C,$9E,$A0,$A2,$A4,$A6,$A8,$AB,$AD,$AF,$B2,$B4,$B7,$B9,$BC,$BF,$C1,$C4,$C7,$CA,$CD,$CF,$D2,$D5,$D8,$DB,$DE,$E1,$E4,$E7,$EA,$ED,$F0,$F4,$F7,$FA,$FD,$00,$03,$06,$09,$0C,$10,$13,$16,$19,$1C,$1F,$22,$25,$28,$2B,$2E,$31,$33,$36,$39,$3C,$3F,$41,$44,$47,$49,$4C,$4E,$51,$53,$55,$58,$5A,$5C,$5E,$60,$62,$64,$66,$68,$6A,$6B,$6D,$6F,$70,$71,$73,$74,$75,$76,$78,$79,$7A,$7A,$7B,$7C,$7D,$7D,$7E,$7E,$7E,$7F,$7F,$7F,$7F,$7F,$7F,$7F,$7E,$7E,$7E,$7D,$7D,$7C,$7B,$7A,$7A,$79,$78,$76,$75,$74,$73,$71,$70,$6F,$6D,$6B,$6A,$68,$66,$64,$62,$60,$5E,$5C,$5A,$58,$55,$53,$51,$4E,$4C,$49,$47,$44,$41,$3F,$3C,$39,$36,$33,$31,$2E,$2B,$28,$25,$22,$1F,$1C,$19,$16,$13,$10,$0C,$09,$06,$03,$00

bitmapFontTable: 
.db $00,$00,$00,$00,$00,$00,$00,$FA,$00,$00,$00,$E0,$00,$E0,$00,$28,$FE,$28,$FE,$28,$24,$54,$FE,$54,$48,$C4,$C8,$10,$26,$46,$6C,$92,$6A,$04,$0A,$00,$00,$E0,$00,$00,$38,$44,$82,$00,$00,$00,$00,$82,$44,$38,$44,$28,$FE,$28,$44,$10,$10,$7C,$10,$10,$00,$02,$0C,$00,$00,$10,$10,$10,$10,$10,$00,$00,$02,$00,$00,$04,$08,$10,$20,$40,$7C,$8A,$92,$A2,$7C,$00,$42,$FE,$02,$00,$46,$8A,$92,$92,$62,$84,$82,$92,$B2,$CC,$18,$28,$48,$FE,$08,$E4,$A2,$A2,$A2,$9C,$3C,$52,$92,$92,$8C,$80,$8E,$90,$A0,$C0,$6C,$92,$92,$92,$6C,$62,$92,$92,$94,$78,$00,$00,$28,$00,$00,$00,$02,$2C,$00,$00,$10,$28,$44,$82,$00,$28,$28,$28,$28,$28,$00,$82,$44,$28,$10,$40,$80,$9A,$A0,$40,$7C,$82,$BA,$9A,$72,$3E,$48,$88,$48,$3E,$FE,$92,$92,$92,$6C,$7C,$82,$82,$82,$44,$FE,$82,$82,$82,$7C,$FE,$92,$92,$92,$82,$FE,$90,$90,$90,$80,$7C,$82,$82,$8A,$8E,$FE,$10,$10,$10,$FE,$00,$82,$FE,$82,$00,$04,$02,$02,$02,$FC,$FE,$10,$28,$44,$82,$FE,$02,$02,$02,$02,$FE,$40,$30,$40,$FE,$FE,$20,$10,$08,$FE,$7C,$82,$82,$82,$7C,$FE,$90,$90,$90,$60,$7C,$82,$8A,$84,$7A,$FE,$90,$98,$94,$62,$64,$92,$92,$92,$4C,$80,$80,$FE,$80,$80,$FC,$02,$02,$02,$FC,$F8,$04,$02,$04,$F8,$FE,$04,$18,$04,$FE,$C6,$28,$10,$28,$C6,$C0,$20,$1E,$20,$C0,$86,$8A,$92,$A2,$C2,$00,$FE,$82,$82,$00,$40,$20,$10,$08,$04,$00,$82,$82,$FE,$00,$20,$40,$80,$40,$20,$01,$01,$01,$01,$01,$00,$80,$40,$20,$00,$04,$2A,$2A,$2A,$1E,$FE,$22,$22,$22,$1C,$1C,$22,$22,$22,$22,$1C,$22,$22,$22,$FE,$1C,$2A,$2A,$2A,$1A,$10,$7E,$90,$90,$40,$18,$25,$25,$25,$1E,$FE,$20,$20,$20,$1E,$00,$22,$BE,$02,$00,$02,$01,$21,$BE,$00,$FE,$08,$08,$14,$22,$00,$82,$FE,$02,$00,$3E,$20,$1C,$20,$3E,$3E,$20,$20,$20,$1E,$1C,$22,$22,$22,$1C,$3F,$24,$24,$24,$18,$18,$24,$24,$24,$3F,$3E,$10,$20,$20,$20,$12,$2A,$2A,$2A,$24,$20,$FC,$22,$22,$04,$3C,$02,$02,$04,$3E,$38,$04,$02,$04,$38,$3E,$02,$0C,$02,$3E,$22,$14,$08,$14,$22,$38,$05,$05,$05,$3E,$22,$26,$2A,$32,$22,$10,$6C,$82,$82,$00,$00,$00,$FF,$00,$00,$00,$82,$82,$6C,$10,$40,$80,$C0,$40,$80,$54,$28,$54,$28,$54,$00,$00,$00,$00,$00


soundEat:
.db 60,60,60,60,60,60,52,52,52,52,52,52,52,0

.include "audio.asm"
Music:
.include "Music/AnacondaMusic.asm"

.include "Bootloader.asm"

Our journey continues on Page 7.