processor 6502 VSYNC = $00 VBLANK = $01 WSYNC = $02 RSYNC = $03 NUSIZ0 = $04 NUSIZ1 = $05 COLUP0 = $06 COLUP1 = $07 COLUPF = $08 COLUBK = $09 CTRLPF = $0A REFP0 = $0B REFP1 = $0C PF0 = $0D PF1 = $0E PF2 = $0F RESP0 = $10 POSH2 = $11 RESP1 = $11 RESM0 = $12 RESM1 = $13 RESBL = $14 AUDC0 = $15 AUDC1 = $16 AUDF0 = $17 AUDF1 = $18 AUDV0 = $19 AUDV1 = $1A GRP0 = $1B GRP1 = $1C ENAM0 = $1D ENAM1 = $1E ENABL = $1F HMP0 = $20 HMP1 = $21 HMM0 = $22 HMM1 = $23 HMBL = $24 VDELP0 = $25 VDELP1 = $26 VDELBL = $27 RESMP0 = $28 RESMP1 = $29 HMOVE = $2A HMCLR = $2B CXCLR = $2C CXM0P = $30 CXM1P = $31 CXP0FB = $32 CXP1FB = $33 CXM0FB = $34 CXM1FB = $35 CXBLPF = $36 CXPPMM = $37 INPT0 = $38 INPT1 = $39 INPT2 = $3A INPT3 = $3B INPT4 = $3C INPT5 = $3D SWCHA = $280 SWACNT = $281 SWCHB = $282 SWBCNT = $283 INTIM = $284 TIM1T = $294 TIM8T = $295 TIM64T = $296 T1024T = $297 SCANLINE = $81 KEYDELAY = $87 COLUMN = $88 GRHEIGHT = $E8 VALUE = $82 REPS = $83 org $f800 cld clc jsr score lda #$0 sta KEYDELAY ; Reset KEYDELAY to zero lda #$c sta COLUMN ; Reset column Start LDA #$00 ; get contents of memory STA PF0 STA PF1 STA PF2 ; save into a pattern control register LDA #$00 STA CTRLPF ; set background control register LDA #$47 STA COLUP1 ; set right side color sta COLUP0 lda #$57 LDY #$00 DEY STA WSYNC ; wait for horizontal sync STA VBLANK ; start vertical blanking STA VSYNC ; start vertical retrace LDA #$2A STA TIM8T ; set timer for appropriate length Loop4 LDY INTIM BNE Loop4 ; waste time STY WSYNC ; wait for horizontal sync STY VSYNC ; end vertical retrace period LDA #$24 STA TIM64T ; set timer for next wait Loop3 LDY INTIM BNE Loop3 ; waste time STY WSYNC ; wait for horizontal sync ldy #$04 STY VBLANK ; end vertical blanking sty WSYNC lda #$e4 ; set number of scanlines sta SCANLINE sta WSYNC lda #$00 ; clear background sta PF0 sta PF1 sta PF2 sta REFP0 sta HMP1 ; move player 1 right 7 pixels loop6 stx WSYNC ldx SCANLINE cpx #$b0 ; if at scanline #$b0 draw the code bne b1 lda #$9 sta GRHEIGHT jsr code jsr drawit lda COLUMN ; divide column by two and move cursor clc ; two columns at a time ror tax ldy #$1 jsr movit jsr cursor b1 cpx #$a6 ; turn cursor off bne b2 lda #$0 sta GRP0 sta GRP1 b2 cpx #$80 ; if column is #$12, draw START bne b3 lda COLUMN cmp #$12 bne b3 lda #$8 sta GRHEIGHT jsr play jsr drawit b3 cpx #$50 ; draw Bob Colbert bne b4 sta WSYNC lda #$8 sta GRHEIGHT jsr name jsr drawit b4 dec SCANLINE bne loop6 lda SWCHA ; read joystick and #$f0 tay bne j0 sta KEYDELAY ; if nothing pressed, reset keydelay jmp b6 j0 inc KEYDELAY lda KEYDELAY cmp #$08 bne b6 lda #$0 ; if keydelay = #$8, check direction sta KEYDELAY tya asl bcs j2 ldy COLUMN ; move cursor right iny cpy #$13 bne j1 ldy #$c j1 sty COLUMN j2 asl bcs j4 ldy COLUMN ; move cursor left dey cpy #$b bne j3 ldy #$12 j3 sty COLUMN j4 asl bcs j5 lda COLUMN ; decrease digit value clc sbc #$0b tax lda $90,x clc adc #$f0 sta $90,x jmp b6 j5 asl bcs b6 goup lda COLUMN ; increase digit value clc sbc #$0b tax lda #$10 clc adc $90,x sta $90,x b6 lda INPT4 ; check for fire button and #$80 bne b9 ldy COLUMN cpy #$12 bne b7 ldx #$18 ; if in START jump to game m1 lda gocode,x sta $a0,x dex bpl m1 jmp $a0 b7 lda $90 ; get high byte of address to modify clc ; from first digit in code (far left) ror ror ror ror ora #$f0 sta $8f ; put in zeropage variable lda $92 ; get low nibble of address's low byte clc ror ; rotate it 4 times to put it in the right place ror ror ror ora $91 ; join it with the high nibble sta $8e ; put in zeropage variable lda $94 ; get low nibble of value's low byte clc ror ; rotate it 4 times to put it in the right place ror ror ror ora $93 ; join it with the high nibble sta VALUE ; put in zeropage variable lda $95 ; get low nibble of REPS low byte clc ror ; rotate it 4 times to put it in the right place ror ror ror sta REPS ; put in zeropage variable ldx #$20 b8 lda bscode,x ; loop to copy code that makes modification to game sta $a0,x dex bpl b8 jsr $a0 ; jump to the code that modifies the game lda #$c ; reset the cursor (will probably reset the code too) sta COLUMN b9 JMP Start ; do next screen (every 1/60th second) drawit lda #$03 ; set both players to 3 copies sta NUSIZ0 sta NUSIZ1 lda #$01 ; set vertical delay on for both players sta VDELP0 sta VDELP1 ldx #$6 ; move players 12 columns over ldy #$0 jsr movit lda #$f0 ; set player 0 to move left 1 pixel sta HMP0 sta WSYNC sta HMOVE ; move player 0 sec lda SCANLINE ; adjust scanline count sbc GRHEIGHT sta SCANLINE loop2 ldy GRHEIGHT lda ($AA),y ; get player0 copy1 data sta GRP0 sta WSYNC lda ($AC),y ; get player1 copy1 data sta GRP1 lda ($AE),y ; get player0 copy2 data sta GRP0 lda ($B0),y ; get player1 copy2 data sta $E9 lda ($B2),y ; get player0 copy3 data tax lda ($B4),y ; get player1 copy3 data tay lda $E9 sta GRP1 stx GRP0 sty GRP1 sta GRP0 dec GRHEIGHT bpl loop2 ; loop until done lda #$00 ; clear player graphics sta GRP1 sta GRP0 rts movit sta WSYNC ; wait for scanline loop1 dex ; wait for column (15 bit wide) x bpl loop1 nop ; additional delay sta RESP0 ; reset player 0 sta RESP1 ; reset player 1 cpy #$0 ; if y then compensate column beq mvexit tax lda table3,x ; get compensation value from table3 sta HMP0 sta WSYNC sta HMOVE mvexit rts cursor lda COLUMN ; if odd column, must user HMOVE and #$01 beq c3 lda #$80 c3 sta HMP0 sta WSYNC sta HMOVE lda COLUMN cmp #$12 ; if column 12, turn off cursor bne c4 ; START will be turned on instead lda #$0 beq c5 c4 lda #$ff c5 sta GRP0 lda #$0 sta NUSIZ0 ; set to 1 copy of player0 sta GRP1 rts code ; puts necessary addresses in zero-page locations ldx #$0d ; for drawing the 6-digit code ldy #$6 ; each digit is spaced $10 bytes apart code1 ; to allow for easy display (e.g. 2 is at $FE20 and A at $FEA0) lda #$fe sta $aa,x lda $90,y sta $a9,x dex dex dey bpl code1 rts score ; only for testing purposes - initializes code ldx #$06 ; code will be initialized to zero in final release loop5 lda table1,x sta $90,x dex bpl loop5 rts name ; copies addresses to zero-page for "Bob Colbert" ldx #$0b ; will be "Cheetah" or something in final release loop7 lda table2,x sta $aa,x dex bpl loop7 rts play ; copies addresses to zero-page for drawing "START" ldx #$0b loop8 lda table4,x sta $aa,x dex bpl loop8 clc lda SCANLINE sbc #$6 sta SCANLINE rts ; initial code - for testing only table1 .byte $f0,$a0,$f0,$e0,$f0,$f0 ;bit-mapped graphics of digits org $fe00 d0 .byte $00,$00,$38,$44,$44,$44,$44,$44,$44,$38,$0,$0,$0,$0,$0,$0 d1 .byte $00,$00,$10,$10,$10,$10,$10,$10,$30,$10,$0,$0,$0,$0,$0,$0 d2 .byte $00,$00,$7c,$40,$40,$30,$08,$04,$44,$38,$0,$0,$0,$0,$0,$0 d3 .byte $00,$00,$38,$44,$44,$04,$18,$04,$44,$38,$0,$0,$0,$0,$0,$0 d4 .byte $00,$00,$04,$04,$7e,$44,$24,$14,$0c,$04,$0,$0,$0,$0,$0,$0 d5 .byte $00,$00,$38,$44,$44,$04,$78,$40,$40,$7c,$0,$0,$0,$0,$0,$0 d6 .byte $00,$00,$38,$44,$44,$78,$40,$40,$44,$38,$0,$0,$0,$0,$0,$0 d7 .byte $00,$00,$20,$20,$10,$10,$08,$08,$04,$78,$0,$0,$0,$0,$0,$0 d8 .byte $00,$00,$38,$44,$44,$44,$38,$44,$44,$38,$0,$0,$0,$0,$0,$0 d9 .byte $00,$00,$38,$44,$04,$3c,$44,$44,$44,$38,$0,$0,$0,$0,$0,$0 da .byte $00,$82,$82,$82,$7c,$44,$44,$28,$28,$10,$0,$0,$0,$0,$0,$0 db .byte $00,$f8,$84,$84,$84,$f8,$84,$84,$84,$f8,$0,$0,$0,$0,$0,$0 dc .byte $00,$3c,$42,$80,$80,$80,$80,$80,$42,$3c,$0,$0,$0,$0,$0,$0 dd .byte $00,$f8,$84,$82,$82,$82,$82,$82,$84,$f8,$0,$0,$0,$0,$0,$0 de .byte $00,$fc,$80,$80,$80,$fc,$80,$80,$80,$fc,$0,$0,$0,$0,$0,$0 df .byte $00,$80,$80,$80,$80,$f8,$80,$80,$80,$fc,$0,$0,$0,$0,$0,$0 org $ff00 ;bob colbert .byte $00,$f1,$8a,$8a,$f1,$f0,$88,$90,$e0 .byte $00,$9c,$52,$52,$9c,$10,$10,$10,$10 .byte $00,$18,$25,$41,$40,$40,$40,$24,$18 .byte $00,$cb,$2a,$2a,$cb,$0a,$0a,$0a,$0a .byte $00,$8c,$58,$56,$8c,$00,$00,$00,$00 .byte $00,$82,$82,$82,$82,$d2,$a7,$02,$00 ;start .byte $00,$03,$04,$00,$00,$03,$04,$04,$03 .byte $00,$81,$41,$41,$41,$81,$01,$41,$87 .byte $00,$08,$08,$04,$07,$04,$02,$02,$c1 .byte $00,$24,$24,$44,$c4,$47,$84,$84,$07 .byte $00,$41,$41,$41,$41,$81,$41,$41,$87 .byte $00,$00,$00,$00,$00,$00,$00,$00,$c0 ; lookup table for Bob Colbert table2 .byte $00,$ff,$09,$ff,$12,$ff,$1b,$ff,$24,$ff,$2d,$ff ; horizontal adjustment for cursor table3 .byte $00,$00,$00,$00,$00,$00,$00,$f0,$e0 ; lookup table for START table4 .byte $36,$ff,$3f,$ff,$48,$ff,$51,$ff,$5a,$ff,$63,$ff ; #$22 bytes ; Code that gets copied to zero-page to modify game bscode lda $f01e ; Set banks up so game is in $f000 - $ffff nop sta $fff8 ldx VALUE ; Get value entered in code ldy REPS ; Get # of times to repeat value bs1 lda $f000,x ; Tells Supercharger what value to store lda ($8e),y ; Stores value at memory location in ($8e) dey bpl bs1 ; Loop until all REPS done ldx #$08 ; Switch Cheetah back into SC at $f800 lda $f000,x sta $fff8 rts ; #$0e bytes gocode ldx #$1d ; Sets banks up so game is in $f000 - $ffff and turns ROM power off lda $f000,x ; This also activates the Supercharger Modification that disables sta $fff8 ; all further bankswitching. lda $fffc ; get lobyte of address - will be modified later for 2k games sta $e0 lda $fffd ; get hibyte of address sta $e1 jmp ($e0) ; start game org $fffc .byte $00,$F8,$00,$F8