; Diffusion Limited Aggregation ; B. Watson's asm rewrite of ChrisTOS's Atari 8-bit version. ; Original lives here: https://github.com/ctzio/DLA/ ; This version uses ANTIC narrow playfield mode, since the original ; uses fewer than 256 columns of a GR.8 screen. This gives a slight ; speed boost for 2 reasons: less DMA from the ANTIC chip, and we get ; to use 1 byte for the X coordinate. .include "atari.inc" .macpack atari ; for scrcode macro .include "xex.inc" loadaddr = $2000 screen = $4000 ; must be on a x000 (4K) boundary screen2 = screen + $1000 ; rest of screen RAM after 4K boundary linelen = $20 ; aka 32 bytes, antic F (GR.8) in narrow mode. maxlines = $C0 ; 192 lines of display screenbytes = maxlines * linelen dl_len = 202 ; remember to update this if you modify the display list! DMA_ON = $21 DEFAULTPART = 1000 screenptr = SAVMSC maxparticles = $80 ; 2 bytes addtmp = $82 pixptr = $82 pixmask = $84 cursor_x = $85 ; cursor x/y are args to plot/unplot/locate cursor_y = $86 min_x = $87 ; limits: if the particle gets outside this box, max_x = $88 ; delete it and spawn a new one. min_y = $89 max_y = $8a circlesize = $8b ; 0 to 3 part_x = $8c ; x/y coords of current particle part_y = $8d particles = $8e ; 2 bytes spawn_x = $90 ; 2 bytes spawn_y = $92 ; 2 bytes dlist = screen - dl_len linebuf = $0580 textbuf = $0590 fptmp = $05a0 cloksav = $a0 seedtype = $9f ; start of init segment. gets overwritten by the main program... ; and since the rest of the xex isn't loaded yet, can't call ; subroutines from it! xex_org loadaddr .include "io.s" ; printchrx and getchrx msg: .byte "Diffusion Limited Aggregate",$9b .byte "Urchlay's ASM version 0.0.7",$9b,$9b .byte "How many particles [",.sprintf("%d", DEFAULTPART),"]? ",$0 msg2: .byte $9b,"Seed Type: ",$9b,"1=Dot 2=Plus 3=4Dots 4=Line [1]? ",$0 init: ; set default particles (if user just hits return) lda #DEFAULTPART sta maxparticles+1 ; print banner and prompt. ldx #0 pmloop: lda msg,x beq pmdone jsr printchrx inx bne pmloop pmdone: ; read up to 5 digits. for now, no editing. ldx #0 readloop: jsr getchrx cmp #$9b ; is it Return? beq readdone ; if so, done reading. cmp #$30 ; is it a digit? bcc readloop ; if not, ignore it. cmp #$3a bcs readloop sta textbuf,x jsr printchrx inx cpx #5 bne readloop lda #0 sta textbuf,x ; zero-terminate readdone: cpx #0 beq usedefault ; add up input digits lda #0 sta maxparticles sta maxparticles+1 ldx #0 digloop: lda textbuf,x beq digitsdone ; hit zero terminator ldy #$0a lda #0 sta addtmp sta addtmp+1 mul10loop: clc lda addtmp adc maxparticles sta addtmp lda addtmp+1 adc maxparticles+1 sta addtmp+1 dey bne mul10loop lda textbuf,x and #$0f clc adc addtmp sta maxparticles lda addtmp+1 adc #0 sta maxparticles+1 inx bne digloop digitsdone: usedefault: ; print seed type prompt ldx #0 pm2loop: lda msg2,x beq pm2done jsr printchrx inx bne pm2loop pm2done: readgen: jsr getchrx cmp #$9b bne noteol lda #$31 noteol: cmp #$31 bcc readgen cmp #$35 bcs readgen and #$0f tax dex stx seedtype rts xex_init init ;;;;; end of init segment xex_org loadaddr main: ;;; start of main() lda #$90 sta COLOR2 lda #$0e sta COLOR1 jsr initscreen ; wait for shadow regs to get updated... lda RTCLOK+2 wl: cmp RTCLOK+2 beq wl lda #1 ; ...turn off shadow reg updates (tiny speed boost) sta CRITIC lda #0 sta particles sta particles+1 sta RTCLOK sta RTCLOK+1 sta RTCLOK+2 sta circlesize jsr set_limits lda #points_x sta spawn_x+1 lda #points_y sta spawn_y+1 jsr drawseed next_particle: ldy RANDOM ; spawn a new particle lda (spawn_x),y sta part_x lda (spawn_y),y sta part_y jsr drunkwalk ; walk it around beq next_particle ; if it went out of bounds, try again ; particle stuck to an existing pixel, draw it lda part_x sta cursor_x lda part_y sta cursor_y jsr plot inc particles bne ph_ok inc particles+1 ph_ok: ; increase circlesize at appropriate particle counts ; if(particles == 100 || particles == 300 || particles == 600) goto next_size; lda particles ldx particles+1 bne not_100 cmp #100 beq next_size not_100: cpx #>300 bne not_300 cmp #<300 beq next_size not_300: cpx #>600 bne checkmaxparts cmp #<600 beq next_size bne checkmaxparts next_size: inc circlesize jsr set_limits inc spawn_x+1 inc spawn_y+1 checkmaxparts: ; if(particles != maxparticles) goto next_particle; lda particles cmp maxparticles bne next_particle lda particles+1 cmp maxparticles+1 bne next_particle main_done: lda #0 sta CRITIC sta COLOR2 sta ATRACT lda #DMA_ON sta SDMCTL lda RTCLOK sta cloksav lda RTCLOK+1 sta cloksav+1 lda RTCLOK+2 sta cloksav+2 ; print menu ldx #menulen menuloop: lda menumsg,x sta textbuf,x dex bpl menuloop ; calculate and print elapsed time in minutes. our only use of ; the floating point ROM routines. ldx #0 stx FR0 inx stx FR0+1 jsr IFP ; FR0 now FP 256.0 jsr FMOVE ; FR1 = FR0 (both are 256.0) jsr FMUL ; FR0 = FR0 * FR1 (65536.0) jsr FMOVE ; FR1 = FR0 ldx #0 stx FR0+1 lda cloksav sta FR0 jsr IFP ; FR0 now cloksav in FP, FR1 = 65536.0 jsr FMUL ; FR0 = FR0 * FR1 jsr FMOVE ; FR1 = FR0, aka the high byte of cloksav in jiffies lda cloksav+1 ; convert low 2 bytes of cloksav to FP... sta FR0+1 lda cloksav+2 sta FR0 jsr IFP ; ...ok, now: jsr FADD ; add the high bytes in jiffies, result in FR0 again ; we now have the 3-byte jiffy count in FR0. ; 3600 NTSC jiffies or 3000 PAL jiffies = 1 minute, so divide. ; floating point constants: ; 3600.0 is $41,$36,$00,$00,$00,$00 ; 3000.0 is $41,$30,$00,$00,$00,$00 ldx #FR1 jsr ZF1 lda #$41 ; excess-64 base-100 exponent and sign (bit 7 = 0 means positive) sta FR1 ldx #$36 ; 1st mantissa BCD byte, NTSC lda PAL and #$0e bne ntsc ldx #$30 ; 1st mantissa BCD byte, PAL ntsc: stx FR1+1 jsr FDIV ; FR0 = FR0 / FR1 jsr FASC ; render as ASCII ; Now clean up the output from FASC and copy it to our menu line. ; FASC puts its results at LBUFF ($0580, aka linebuf). ; Unfortunately it can have a leading zero, and the last ; digit has the high bit set (as a terminator). We want only ; 6 characters including the decimal point, which could be e.g. ; 0.1234 (the 0 will show as a space) or 1.2345 12.345 123.45 1234.5 ; Really elegant software would print this as minutes and seconds, ; with tenths of seconds, e.g. 1:23.4. Not that worried about it though. ldx #$ff lda linebuf cmp #'0' ; skip the leading zero if present (a space will be seen in its place) bne ascloop inx ascloop: inx lda linebuf,x and #$df ; convert to screencode bmi ascdone ; hit the terminator digit sta textbuf,x cpx #6 bne ascloop beq xdone ascdone: and #$7f sta textbuf,x inx xdone: lda #$6d ; screen code for "m" sta textbuf,x ; user might have hit some random key during plotting; ignore it. keyloop: ldx #$ff stx CH waitkey: lda CH cmp #$ff beq waitkey ; see what key was hit and #$3f ; ignore shift and inverse cmp #$28 ; Redo bne notredo jmp main notredo: cmp #$2e ; WriteCSV beq writecsv cmp #$3e ; Save beq saveimage cmp #$2a ; Exit bne keyloop ; ignore any other keystroke ;rts ; exit to DOS jmp COLDSV ; reboot writecsv: saveimage: notyet: lda #$40 sta COLOR2 hang: jmp hang ; TODO: code to save image goes here. ;;; End of main() ; screen codes for menu menumsg: .byte $00,$00,$00 ; 3 digits of minutes .byte $00 ; 1 decimal point .byte $00,$00 ; 2 digits fractional minutes .byte $00 ; 1 the letter "m" .byte $00 ; 1 space .byte 'S'-$20+$80 ; 1 scrcode "ave " ; 3 .byte 'W'-$20+$80 ; 1 scrcode "rtCSV " ; 6 .byte 'R'-$20+$80 ; 1 scrcode "edo " ; 4 .byte 'E'-$20+$80 ; 1 scrcode "xit? " ; 5 .byte $80 ; 1 (cursor) .byte $00 ; 1 space (filler) to make 32 bytes menulen = * - menumsg ;;; Subroutine: set_limits ;;; Sets the X/Y min/max limits based on circlesize set_limits: ldx circlesize lda xmin,x sta min_x lda ymin,x sta min_y lda xmax,x sta max_x lda ymax,x sta max_y rts ;;; Subroutine: initscreen ;;; clear screen memory and point ANTIC to our display list. ;;; no arguments. trashes all registers. initscreen: jsr set_screenptr ; first, clear linebuf and textbuf lda #0 tay isloop0: sta linebuf,y iny cpy #$40 bne isloop0 ; next, clear screen memory ldx #>screenbytes ; clear this many pages tay ; 0 again isloop: sta (screenptr),y iny bne isloop inc screenptr+1 dex bne isloop lda #DMA_ON ; set ANTIC narrow playfield mode sta SDMCTL lda #dlist sta SDLSTH ; fall through to next subroutine ;;; Subroutine: set_screenptr ;;; Set screenptr to the start of screen memory. ;;; Trashes A, preserves X and Y. set_screenptr: lda #screen sta screenptr+1 rts ;;; Subroutine: plotsetup ;;; - set pixptr to point to screen memory at cursor_y. ;;; - set pixmask to the mask for cursor_x. ;;; - set Y reg to the byte offset for cursor_x. ;;; - returns with cursor_x in X reg, pixmask in A reg too. ;;; Called by plot, unplot, and locate. plotsetup: ldx cursor_y lda lineaddrs_l,x sta pixptr lda lineaddrs_h,x sta pixptr+1 ldx cursor_x ldy xoffsets,x lda xmasks,x sta pixmask rts ;;; Subroutine: plot ;;; plots a pixel at (cursor_x, cursor_y) plot: jsr plotsetup lda (pixptr),y ora pixmask sta (pixptr),y rts ;;; Subroutine: unplot ;;; erases a pixel at (cursor_x, cursor_y) unplot: jsr plotsetup lda pixmask eor #$ff sta pixmask lda (pixptr),y and pixmask sta (pixptr),y rts ;;; Subroutine: locate ;;; check the pixel at (cursor_x, cursor_y) ;;; if set, return with Z=0 ;;; otherwise, return with Z=1 ;;;; Inlined (keep for reference) ;locate: ; jsr plotsetup ; and (pixptr),y ; rts ;;; Subroutine: spawn ;;; Pick a random point on the edge of a circle ;;;; Inlined (keep for reference) ; spawn: ; ldy RANDOM ; lda (spawn_x),y ; sta part_x ; lda (spawn_y),y ; sta part_y ; rts ;;; Subroutine: drunkwalk ;;; Walk the point around randomly until it either is ;;; adjacent to a set pixel or goes out of bounds. ;;; Return with Z=0 if out of bounds, Z=1 if it hit a pixel. ;;; This is the innermost loop, so it should be as optimized as ;;; possible (we're not there yet). drunkwalk: ; using bit/bmi/bvc saves 6.25 cycles on average, compared to ; immediate cmp and bne. ; 4 code paths: up=14, down=15, left=15, right=13, avg=14.25 bit RANDOM ;4 ; use top 2 bits (probably more random, definitely faster) bmi lr ;2/3 bvc down ;2/3 dec part_y ;3 ; N=1 V=1 up bne checkbounds ;3 down: inc part_y ;3 ; N=1 V=0 down bne checkbounds ;3 lr: bvc right ;2/3 dec part_x ;3 ; N=0 V=1 left bne checkbounds ;3 right: inc part_x ;3 checkbounds: lda part_x cmp min_x beq oob cmp max_x beq oob sta cursor_x lda part_y cmp min_y beq oob cmp max_y beq oob sta cursor_y ldx #0 lda CONSOL cmp #6 bne dontplot jsr plot jsr unplot ldx #DMA_ON dontplot: ;stx SDMCTL ; nope, shadow updates are off... stx DMACTL ; check neighbors. used to be a subroutine, inlined it. ; also inlined plotsetup here. ; (-1,0) dec cursor_x ldx cursor_y lda lineaddrs_l,x sta pixptr lda lineaddrs_h,x sta pixptr+1 ldx cursor_x ldy xoffsets,x lda xmasks,x and (pixptr),y bne stick ; (1,0) inx stx cursor_x inx ldy xoffsets,x lda xmasks,x and (pixptr),y bne stick ; (0,-1) dec cursor_y ldx cursor_y lda lineaddrs_l,x sta pixptr lda lineaddrs_h,x sta pixptr+1 ldx cursor_x ldy xoffsets,x lda xmasks,x sta pixmask and (pixptr),y bne stick ; (0,1) tya ora #$40 ; add 64 tay lda (pixptr),y and pixmask bne stick jmp drunkwalk ; too far for a branch stick: oob: rts ;;; Subroutine: drawseed drawseed: ldx seedtype lda seeds_h,x pha lda seeds_l,x pha rts seed_point: ; initial point in center lda #$7f sta cursor_x lda #$5f sta cursor_y jmp plot seed_long: ; horizontal line, the width of the screen lda #$1 sta cursor_x lda #$5f sta cursor_y slnoop: jsr plot inc cursor_x lda cursor_x cmp #$ff bne slnoop rts seed_plus: lda #$7f sta cursor_x lda #$55 sta cursor_y sploop: jsr plot inc cursor_y lda cursor_y cmp #$69 bne sploop lda #$75 sta cursor_x lda #$5f sta cursor_y slloop: jsr plot inc cursor_x lda cursor_x cmp #$89 bne slloop rts seed_4pt: lda #$75 sta cursor_x lda #$55 sta cursor_y jsr plot lda #$68 sta cursor_y jsr plot lda #$88 sta cursor_x jsr plot lda #$55 sta cursor_y jmp plot ;;;;; end of executable code seeds_l: .byte <(seed_point-1),<(seed_plus-1),<(seed_4pt-1),<(seed_long-1) seeds_h: .byte >(seed_point-1),>(seed_plus-1),>(seed_4pt-1),>(seed_long-1) ; dlatbl.s is generated by perl script, mkdlatbl.pl .include "dlatbl.s" ; table of addresses, for each line on the screen. bloats the ; code by 384 bytes, but compared to calculating the address, is ; twice as fast! lineaddrs_l: laddr .set screen .repeat 192 .byte laddr laddr .set laddr + $20 .endrep ; tables to replace X coord => mask-and-offset calculations. xoffsets: xoffs .set 0 .repeat 32 .repeat 8 .byte xoffs .endrep xoffs .set xoffs + 1 .endrep xmasks: .repeat 32 .byte $80,$40,$20,$10,$08,$04,$02,$01 .endrep ;;; display list ; ANTIC opcodes blank8 = $70 gr8 = $0f gr0 = $02 lms = $40 jvb = $41 xex_org dlist .byte blank8, blank8, blank8 .byte gr8 | lms .word screen .repeat 127 .byte gr8 .endrep .byte gr8 | lms .word screen2 .repeat maxlines - 132 .byte gr8 .endrep .byte gr0 | lms .word textbuf .byte jvb .word dlist ;.out .sprintf("%d",* - dlist) xex_run loadaddr