Back to Hardware

Text and Brainfuck

22 Dec 2018
Progress: Complete

This is page 5 of the Games Console project.

At the time of this project, I had only a casual interest in brainfuck. By now you're probably thinking I have a somewhat unhealthy obsession with it.

So I won't talk too much about the logic of the program, but here are the interesting bits:

Drawing Text

I started with a screenshot of a pixel font I liked. Each character is 8 pixels high by 5 pixels wide, so it made sense to store it as five bytes, and scan each character vertically. The lookup table is in the normal ASCII order, of course. With five bytes per character, we need to multiply the ASCII value by five. If we'd padded the table so they were 8 bytes apart, that'd be even simpler, but to be honest we don't need to worry because the ATmega chip has a hardware multiplier, so multiplying by 5 is easy.

Pixel font

A tiny javascript program analysed the image and spit out the binary data we needed.

From here the drawing rountine is just a series of shifts and conditional delays. The register used to pass the X coordinate is not really trashed. Conveniently, it's used directly as the counter for the X column, so at the end of the routine it's left in the correct horizontal position for drawing the next character. So in a loop where we're drawing text, we can set the X coordinate once and call the drawChar routine repeatedly.

A convenient part of having a screen resolution of 256 by 256 is that things wrap automatically. On my 'to-do' list was to make the text wrap automatically at word-breaks, which wouldn't be too hard but I guess it's not important for anything apart from the brainfuck pseudo-terminal output.

Oscilloscope screenshot of the brainfuck interpreter, running 99 bottles of beer on the wall

Scrolling is implemented by having all the terminal characters in SRAM. Each frame (I set it to every 256 BF instructions) these characters are drawn to the display. When we output some text to the display, it adds to this block of SRAM, and if it reaches the end of the line, or a line-feed character is detected, it repeatedly copies each line into the block of memory before it. See the pushCharSRAM function below, there should be enough comments to make it clear.

Relative jumps

The relative branch instructions can only add or subtract a very small amount to the program counter, just 64 words. The core of the interpreter is essentially a switch statement, with branches to each of the functions that handle those characters. The program is so short that this nearly all fit within the range of relative branches. It's not hard to extend the range, when you need to: just reverse the condition logic and branch over a jump. But since I was so close to fitting it all in range, I realized I was only branching forwards, and the relative branch is signed. So by putting some of the functions above and before the main loop, we can keep it all tightly optimized. I find this satisfying, anyone trying to interpret the code probably doesn't.

That's all I have to say about this one, so take a gander below or head onwards to page 6

### brainfuck.asm ###



.org 0


Init: 

;/////////////////
;   Initialize pointers and memory
;////////////////
    ; Set the end-of-terminal-text markers
    ldi r25, HIGH($0100 +(42*24))   ; Display is 42 by 24 characters
    ldi r24,  LOW($0100 +(42*24))

    ; Set cursor to the start of the last line
    ldi YH, HIGH($0100 +(42*23))
    ldi YL,  LOW($0100 +(42*23))

    ; Set the program pointer
    ldi ZH, HIGH(BFprog*2)
    ldi ZL,  LOW(BFprog*2)
tempReset:
    ; Pre-fill the ram with zeros
    ldi XH, HIGH(RAMEND)
    ldi XL,  LOW(RAMEND)
    ldi r16,0
ramFill:
    sbiw X, 1
    st X, r16
    cp  XL,r24
    cpc XH,r25      ; Stop when we get to the text buffer
    brne ramFill

    ; Empty the console of text
    ldi r16,24      ; 24 lines
    ldi r18,10      ; Newline character
textFill:
    rcall pushCharSRAM
    dec r16
    brne textFill

    rjmp Main

;/////////////////////
; To make them within range of the relative branch, some
; of the routines have been placed before the main loop
;//////////////////////
BFendOfProgram:
    push ZH
    push ZL
    ldi ZL,  LOW(MessEndOfProg*2)
    ldi ZH, HIGH(MessEndOfProg*2)
    rcall pushPMtextSRAM
    pop ZL
    pop ZH

    ;rcall readController
    ;sbrc r11,ctrlStart
    rjmp tempReset
    
    ;sbiw Z,1
    
    rjmp nextInstruction
BFplus:
    ld r17, X               ; Increment current cell
    inc r17
    st X, r17
    rjmp nextInstruction

BFminus:
    ld r17, X               ; Decrement current cell
    dec r17
    st X, r17
    rjmp nextInstruction

BFdot:
    ld r18, X               ; Output current cell to terminal
    rcall pushCharSRAM
    rjmp nextInstruction

BFless:
    sbiw X, 1               ; Decrement cell pointer
    cp  XL,r24              ; Check if we hit the bottom
    cpc XH,r25
    brcs MemOverflow        ; If so, show error
    rjmp nextInstruction

BFgreater:
    adiw X, 1               ; Increment cell pointer
    in r14,SPL              ; Check for collision with Stack
    in r15,SPH
    cp  XL,r14
    cpc XH,r15
    breq MemOverflow
    rjmp nextInstruction


; Error message
MemOverflow:
    ldi ZL,  LOW(MessOutOfMem*2)    ; Display error message
    ldi ZH, HIGH(MessOutOfMem*2)
    rcall pushPMtextSRAM
    ldi r16, $FF                    ; Stop execution of BF
    rjmp nextInstruction            ; But we still want the screen to refresh

;///////////////////////////
;   Main Loop
;/////////////////////////
Main:

    ; Y pointer is to terminal text in SRAM
    ; Z pointer is to program memory for reading commands
    ; X pointer is used as BF cell pointer
    ; r25:r24 is the end of the terminal display
    
.def depthL=r20         ; Depth is used to count the number of nested loops.
.def depthH=r21         ; We'll make it a word just in case

    ldi r23, 255        ; Loop this many times each frame
runInterpreter:
    cpi r16, $FF        ; If program has ended, skip to draw routine
    breq drawScreen     ; (r16 is initialized as zero)

    lpm r16, Z+

    ; There are only 8 instructions, so it's easiest to just compare each one
    cpi r16, '['
    breq BFopen
    cpi r16, ']'
    breq BFclose
    cpi r16, '+'
    breq BFplus
    cpi r16, '-'
    breq BFminus
    cpi r16, '.'
    breq BFdot
    cpi r16, ','
    breq BFcomma
    cpi r16, '<'
    breq BFless
    cpi r16, '>'
    breq BFgreater
    
    cpi r16, $FF
    breq BFendOfProgram

nextInstruction:
    dec r23
    brne runInterpreter

drawScreen:
    rcall displayTerminal
    rjmp Main


;/////////////
;   Wait for user input: Select a character via the controller
;/////////////
BFcomma:
    push r16
    push r17
    ldi r18, 32         ; Make space on the screen by pushing a space
    rcall pushCharSRAM
    sbiw Y, 1           ; Rewind cursor so we'll overwrite that space
    ldi r18, 65         ; Start off at a printable character
    rjmp BFcommaLoop
    ; Continues below (to avoid relative branch range issues)


;/////////////////
;   Start a conditional loop
;/////////////////
BFopen:
    ld r17, X
    cpi r17, 0
    brne nextInstruction

    ldi depthL, 1
    ldi depthH, 0
BFopenLoop:                 ; Cell is zero, so move ahead to closing bracket
    lpm r17, Z+

    cpi r17, '['
    breq BFopenIncDepth     ; Every open bracket, increase the depth
    cpi r17, ']'
    breq BFopenDecDepth

    rjmp BFopenLoop         ; Keep going until final closing bracket

BFopenIncDepth:
    subi depthL, -1; Add 1 to depthH:depthL
    sbci depthH, -1; Non-intuitive but correct
    rjmp BFopenLoop

BFopenDecDepth:
    subi depthL,1
    sbci depthH,0
    brne BFopenLoop         ; If a closing bracket and depth=0, we can
    rjmp nextInstruction    ; go back to the main program


;/////////////////
;   End a conditional loop
;/////////////////
BFclose:
    ld r17, X
    cpi r17, 0
    breq nextInstruction    ; If zero, move along...
    
    ldi depthL, 1           ; Else we need to rewind to the opening bracket
    ldi depthH, 0
    sbiw Z, 1               ; Undo the postincrement of the last LPM
BFcloseLoop:
    sbiw Z, 1               ; Rewind and load (there is no lpm -Z instruction)
    lpm r17, Z
    
    cpi r17, ']'
    breq BFcloseIncDepth    ; Every close bracket, increase the depth
    cpi r17, '['
    breq BFcloseDecDepth

    rjmp BFcloseLoop

BFcloseIncDepth:
    subi depthL, -1; Add 1 to depthH:depthL
    sbci depthH, -1; Non-intuitive but correct
    rjmp BFcloseLoop
    
BFcloseDecDepth:
    subi depthL, 1
    sbci depthH, 0
    brne BFcloseLoop        ; If it's an opening bracket and depth=0,
    adiw Z, 1               ; increment and go to the next instruction
    rjmp nextInstruction





;//////////////
; Wait for user input (continued)
;/////////////

BFcommaLoop:
    rcall readController
    sbrc r12, 3         ; Pressed UP
    inc r18
    sbrc r12, 2         ; Pressed DOWN
    dec r18
    sbrc r12, 4         ; Pressed START
    rjmp BFcommaLF      ; Insert a linefeed character

    rcall displayTerminal
    ; We want to display the currently selected character
    ; First calculate the X/Y coordinates of the cursor
    mov r16, YL
    mov r17, YH
    subi r16,  LOW($0100 +(42*23))      ; Subtracting this gives us the 
    sbci r17, HIGH($0100 +(42*23))      ; horizontal cursor position
    ; r16 should now contain a number between 0 and 42
    ldi r17, 6          ; Characters are 6 pixels wide
    mul r16, r17        ; result is in r1:r0
    ldi r16, 252        ; Now subtract that value from the starting X value
    sub r16, r0
    ldi r17, 239        ; Finally set the Y position
    
    push r16            ; Now draw it to the screen
    push r17
    push r18
    rcall drawChar      ; Twice, so that it's extra bright
    pop r18
    pop r17
    pop r16
    push r18
    rcall drawChar
    pop r18

    sbrs r12, 7         ; Pressed A? - store the char and return
    rjmp BFcommaLoop

BFcommaEnd:
    st X, r18           ; Store into the cell
    rcall pushCharSRAM  ; Display on the screen
    pop r17
    pop r16
    rjmp nextInstruction

BFcommaLF:
    ldi r18, 10
    rjmp BFcommaEnd




; Draw text from our area of SRAM buffer to screen.
displayTerminal:
    push YH
    push YL
    ldi YH, HIGH($0100)
    ldi YL,  LOW($0100)
    rcall drawTextSRAM
    pop YL
    pop YH
    ret







; Function readController
; r11 is buttons held down. r12 is buttons only just pressed.
; A,B,select,start,up,down,left,right
readController:
    sbis SPSR,SPIF          ; Wait for previous reception to complete
    rjmp readController
    in r11,SPDR             ; Read received data
    com r11                 ; Invert (logic low is button down)

    ; Work out what buttons have just been pressed.
    ; r13 is the button states from the previous reading
    mov r12,r11             ; Copy into r12
    eor r12,r13             ; XOR gives us the buttons which have changed
    and r12,r11             ; AND it with the the buttons currently held down

    mov r13, r11            ; Save button states into r13 for next time

    push r16
    ldi r16,0b00000000      ; Initiate the next reading
    out SPDR,r16
    pop r16
    ret



; Delay functions
delayPixel:
    cpi r16,252
    breq delCountBegin
    nop
    nop
    ret 
delCountBegin:
    push r16
    ldi r16,15
delCount:
    dec r16
    brne delCount
    pop r16
    ret 



/* Function pushCharSRAM(char, [Y pointer])
 * Pushes a character onto the terminal, and linefeeds if needed
 */
pushCharSRAM:
    cpi r18, 10         ; Is this a carriage return?
    brne pushCharSRAMnext
    
    ldi r18, 32         ; fill the rest of the line with spaces

pushCharSRAMfill:
    rcall pushCharSRAMnext  ; Call repeatedly until it returns 10
    cpi r18, 10
    brne pushCharSRAMfill
    ret

pushCharSRAMnext:
    st Y+, r18
    cp  YL,r24          ; Have we reached the end?
    cpc YH,r25
    brne pushCharSRAMend
    
    ; scroll text
    sbiw r25:r24, 42    ; Temporarily rewind the "end" registers by one line

    ldi YH, HIGH($0100) ; Fully rewind the cursor
    ldi YL,  LOW($0100)

scrollTextLoop:
    ldd r18, Y+42       ; Load the character directly underneath
    st Y+, r18          ; Store here and advance cursor

    cp  YL,r24          ; Have we reached the final line?
    cpc YH,r25
    brne scrollTextLoop
    
    ; Fill the final line with spaces
    adiw r25:r24, 42    ; reset the line-end registers to the actual end
    ldi r18, 32         ; Fill with spaces

scrollTextLastLine:
    st Y+, r18
    cp  YL,r24          ; Have we reached the real end of it?
    cpc YH,r25
    brne scrollTextLastLine
    
    ; Finally set cursor to the start of the last line
    sbiw YH:YL, 42

    ldi r18, 10         ; Return value that the line has ended

pushCharSRAMend:
    ret



/* Function pushPMtextSRAM(z pointer)
 * Pushes a string from prog mem onto the terminal.
 */
pushPMtextSRAM:
    lpm r18,Z+
    cpi r18,0               ; null terminated string
    breq pushPMtextEnd
    rcall pushCharSRAM      ; Just keep pushing characters until we hit 0
    rjmp pushPMtextSRAM

pushPMtextEnd:
    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,33                    ; Font starts at ascii 33
    brsh drawCharMain               ; if printable, draw it

    subi x0,5                       ; Otherwise, just move the 
    rjmp drawCharCheckEOL           ; cursor 5 pixels and continue

drawCharMain:
    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 delayPixel
    
drawCharNextBit:
    dec y0
    lsr char
    brne drawCharLoopBit
    dec x0
    pop y0

    dec r19
    brne drawCharLoopByte

drawCharCheckEOL:
    dec x0                  ; Move cursor ready to draw next character
    brne drawCharEnd        ; end of line?
    ldi x0, 252             ; wrap
    subi y0, -10
;   out PORTC,y0            ; try and give it a little more time to stabilize?
;   out PORTA,x0
    
drawCharEnd:
    pop ZL
    pop ZH
    pop r19
    ret



/*  Function drawTextSRAM
 *  draws a message from data space, starting at YH:YL and ending at r25:r24
 */
drawTextSRAM:
    push r16
    push r17
    push r18
    ldi x0,252
    ldi y0,9
    out PORTC,y0            ; move the beam in advance to reduce artifacts
    out PORTA,x0


drawTextSRAMLoop:
    cp  YL,r24
    cpc YH,r25              ; Have we reached the end?
    breq drawTextSRAMend
    ld r18,Y+               ; Load next character
    rcall drawChar          ; x and y are passed straight through to drawChar
    rjmp drawTextSRAMLoop

drawTextSRAMend:
    pop r18
    pop r17
    pop r16
    ret 




bitmapFontTable: 
.db $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,0


MessOutOfMem: .db "OUT OF MEMORY",10,0
MessEndOfProg: .db 10,"END OF PROGRAM",10,0


BFprog:
; HelloWorld x10
;.db " >>>>>>>++++++++++ [<<<<<<<   >++++++++[<+++++++++>-]<.>>+>+>++>[-]+<[>[->+<<++++>]<<]>.+++++++..+++.>>+++++++.<<<[[-]<[-]>]<+++++++++++++++.>>.+++.------.--------.>>+.>++++.   <<<<<[-]>[-]>[-]>[-]>[-]>[-]>[-]>-] ",$FF
; HelloWorld
;.db ">++++++++[<+++++++++>-]<.>>+>+>++>[-]+<[>[->+<<++++>]<<]>.+++++++..+++.>>+++++++.<<<[[-]<[-]>]<+++++++++++++++.>>.+++.------.--------.>>+.>++++.",$FF

; Primes
.db ">>>>>>>>>  >++++++++[<++++++++>-]<++++++++++++++++.[-]>++++++++++[<++++++++++>-]<++++++++++++++.[-]>++++++++++[<++++++++++>-]<+++++.[-]>++++++++++[<++++++++++>-]<+++++++++.[-]>++++++++++[<++++++++++>-]<+.[-]>++++++++++[<++++++++++>-]<+++++++++++++++.[-]>+++++[<+++++>-]<+++++++.[-]>++++++++++[<++++++++++>-]<+++++++++++++++++.[-]>++++++++++[<++++++++++>-]<++++++++++++.[-]>+++++[<+++++>-]<+++++++.[-]>++++++++++[<++++++++++>-]<++++++++++++++++.[-]>++++++++++[<++++++++++>-]<+++++++++++.[-]>+++++++[<+++++++>-]<+++++++++.[-]>+++++[<+++++>-]<+++++++.[-]+[->,----------[<+>-------------------------------------->[>+>+<<-]>>[<<+>>-]<>>>+++++++++[<<<[>+>+<<-]>>[<<+>>-]<[<<+>>-]>>-]<<<[-]<<[>+<-]]<]>>[<<+>>-]<<>+<-[>+[>+>+<<-]>>[<<+>>-]<>+<-->>>>>>>>+<<<<<<<<[>+<-<[>>>+>+<<<<-]>>>>[<<<<+>>>>-]<<<>[>>+>+<<<-]>>>[<<<+>>>-]<<<<>>>[>+>+<<-]>>[<<+>>-]<<<[>>>>>+<<<[>+>+<<-]>>[<<+>>-]<[>>[-]<<-]>>[<<<<[>+>+<<-]>>[<<+>>-]<>>>-]<<<-<<-]+>>[<<[-]>>-]<<>[-]<[>>>>>>[-]<<<<<<-]<<>>[-]>[-]<<<]>>>>>>>>[-<<<<<<<[-]<<[>>+>+<<<-]>>>[<<<+>>>-]<<<>>[>+<-]>[[>+>+<<-]>>[<<+>>-]<>+++++++++<[>>>+<<[>+>[-]<<-]>[<+>-]>[<<++++++++++>>-]<<-<-]+++++++++>[<->-]<[>+<-]<[>+<-]<[>+<-]>>>[<<<+>>>-]<>+++++++++<[>>>+<<[>+>[-]<<-]>[<+>-]>[<<++++++++++>>>+<-]<<-<-]>>>>[<<<<+>>>>-]<<<<>[-]<<+>]<[[>+<-]+++++++[<+++++++>-]<-><.[-]>>[<<+>>-]<<-]>++++[<++++++++>-]<.[-]>>>>>>>]<<<<<<<<>[-]<[-]<<-]++++++++++.[-]",$FF


;Fibonacci
;.db "+++++++++++>+>>>>++++++++++++++++++++++++++++++++++++++++++++>++++++++++++++++++++++++++++++++<<<<<<[>[>>>>>>+>+<<<<<<<-]>>>>>>>[<<<<<<<+>>>>>>>-]<[>++++++++++[-<-[>>+>+<<<-]>>>[<<<+>>>-]+<[>[-]<[-]]>[<<[>>>+<<<-]>>[-]]<<]>>>[>>+>+<<<-]>>>[<<<+>>>-]+<[>[-]<[-]]>[<<+>>[-]]<<<<<<<]>>>>>[++++++++++++++++++++++++++++++++++++++++++++++++.[-]]++++++++++<[->-<]>++++++++++++++++++++++++++++++++++++++++++++++++.[-]<<<<<<<<<<<<[>>>+>+<<<<-]>>>>[<<<<+>>>>-]<-[>>.>.<<<[-]]<<[>>+>+<<<-]>>>[<<<+>>>-]<<[<+>-]>[<+>-]<<<-]",$FF

;99 Bottles
.db ">+++++++++[<+++++++++++>-]<[>[-]>[-]<<[>+>+<<-]>>[<<+>>-]>>>[-]<<<+++++++++<[>>>+<<[>+>[-]<<-]>[<+>-]>[<<++++++++++>>>+<-]<<-<-]+++++++++>[<->-]>>+>[<[-]<<+>>>-]>[-]+<<[>+>-<<-]<<<[>>+>+<<<-]>>>[<<<+>>>-]>[<+>-]<<-[>[-]<[-]]>>+<[>[-]<-]<++++++++[<++++++<++++++>>-]>>>[>+>+<<-]>>[<<+>>-]<[<<<<<.>>>>>-]<<<<<<.>>[-]>[-]++++[<++++++++>-]<.>++++[<++++++++>-]<++.>+++++[<+++++++++>-]<.><+++++..--------.-------.>>[>>+>+<<<-]>>>[<<<+>>>-]<[<<<<++++++++++++++.>>>>-]<<<<[-]>++++[<++++++++>-]<.>+++++++++[<+++++++++>-]<--.---------.>+++++++[<---------->-]<.>++++++[<+++++++++++>-]<.+++..+++++++++++++.>++++++++[<---------->-]<--.>+++++++++[<+++++++++>-]<--.-.>++++++++[<---------->-]<++.>++++++++[<++++++++++>-]<++++.------------.---.>+++++++[<---------->-]<+.>++++++++[<+++++++++++>-]<-.>++[<----------->-]<.+++++++++++..>+++++++++[<---------->-]<-----.---.>>>[>+>+<<-]>>[<<+>>-]<[<<<<<.>>>>>-]<<<<<<.>>>++++[<++++++>-]<--.>++++[<++++++++>-]<++.>+++++[<+++++++++>-]<.><+++++..--------.-------.>>[>>+>+<<<-]>>>[<<<+>>>-]<[<<<<++++++++++++++.>>>>-]<<<<[-]>++++[<++++++++>-]<.>+++++++++[<+++++++++>-]<--.---------.>+++++++[<---------->-]<.>++++++[<+++++++++++>-]<.+++..+++++++++++++.>++++++++++[<---------->-]<-.---.>+++++++[<++++++++++>-]<++++.+++++++++++++.++++++++++.------.>+++++++[<---------->-]<+.>"
.db "++++++++[<++++++++++>-]<-.-.---------.>+++++++[<---------->-]<+.>+++++++[<++++++++++>-]<--.+++++++++++.++++++++.---------.>++++++++[<---------->-]<++.>+++++[<+++++++++++++>-]<.+++++++++++++.----------.>+++++++[<---------->-]<++.>++++++++[<++++++++++>-]<.>+++[<----->-]<.>+++[<++++++>-]<..>+++++++++[<--------->-]<--.>+++++++[<++++++++++>-]<+++.+++++++++++.>++++++++[<----------->-]<++++.>+++++[<+++++++++++++>-]<.>+++[<++++++>-]<-.---.++++++.-------.----------.>++++++++[<----------->-]<+.---.[-]<<<->[-]>[-]<<[>+>+<<-]>>[<<+>>-]>>>[-]<<<+++++++++<[>>>+<<[>+>[-]<<-]>[<+>-]>[<<++++++++++>>>+<-]<<-<-]+++++++++>[<->-]>>+>[<[-]<<+>>>-]>[-]+<<[>+>-<<-]<<<[>>+>+<<<-]>>>[<<<+>>>-]<>>[<+>-]<<-[>[-]<[-]]>>+<[>[-]<-]<++++++++[<++++++<++++++>>-]>>>[>+>+<<-]>>[<<+>>-]<[<<<<<.>>>>>-]<<<<<<.>>[-]>[-]++++[<++++++++>-]<.>++++[<++++++++>-]<++.>+++++[<+++++++++>-]<.><+++++..--------.-------.>>[>>+>+<<<-]>>>[<<<+>>>-]<[<<<<++++++++++++++.>>>>-]<<<<[-]>++++[<++++++++>-]<.>+++++++++[<+++++++++>-]<--.---------.>+++++++[<---------->-]<.>++++++[<+++++++++++>-]<.+++..+++++++++++++.>++++++++[<---------->-]<--.>+++++++++[<+++++++++>-]<--.-.>++++++++[<---------->-]<++.>++++++++[<++++++++++>-]<++++.------------.---.>+++++++[<---------->-]<+.>++++++++[<+++++++++++>-]<-.>++[<----------->-]<.+++++++++++..>+++++++++[<---------->-]<-----.---.+++.---.[-]<<<]",$FF




.include "Bootloader.asm"


Next up, Anaconda, audio and some maths.