flat assembler
Message board for the users of flat assembler.
Index
> Programming Language Design > [FASMG] MOS 6502 Assembler |
Author |
|
codestar 11 May 2015, 17:44
Standard syntax. Assembles most examples online.
Code: include 'assembler.inc' lda #$44 ; immediate lda $AA ; zero page lda $7F, x ; zero page, x lda $4FFF ; absolute lda $88BB, x ; absolute, x lda $24EE, y ; absolute, y lda ($AC, x) ; (indirect, x) lda ($DC), y ; (indirect), y ldx #$44 ; immediate ldx $80 ; zero page ldx $80, y ; zero page, y ldx $ABCD ; absolute ldx $ABCD, y ; absolute, y ldy #$44 ; immediate ldy $80 ; zero page ldy $80, x ; zero page, x ldy $ABCD ; absolute sta $AA ; zero page sta $7F, x ; zero page, x sta $4FFF ; absolute sta $88BB, x ; absolute, x sta $24EE, y ; absolute, y sta ($AC, x) ; (indirect, x) sta ($DC), y ; (indirect), y stx $80 ; zero page stx $80, y ; zero page, y stx $ABCD ; absolute sty $80 ; zero page sty $80, x ; zero page, x sty $ABCD ; absolute inc $80 ; zero page memory inc $80, x ; zero page, x inc $A000 ; absolute memory inc $8000, x ; absolute, x dec $80 ; zero page memory dec $80, x ; zero page, x dec $A000 ; absolute memory dec $8000, x ; absolute, x asl a ; accumulator asl $80 ; zero page asl $80, x ; zero page, x asl $A000 ; absolute asl $8000, x ; absolute, x rol a ; accumulator rol $80 ; zero page rol $80, x ; zero page, x rol $A000 ; absolute rol $8000, x ; absolute, x lsr a ; accumulator lsr $80 ; zero page lsr $80, x ; zero page, x lsr $A000 ; absolute lsr $8000, x ; absolute, x ror a ; accumulator ror $80 ; zero page ror $80, x ; zero page, x ror $A000 ; absolute ror $8000, x ; absolute, x adc #$44 ; immediate adc $AA ; zero page adc $7F, x ; zero page, x adc $4FFF ; absolute adc $88BB, x ; absolute, x adc $24EE, y ; absolute, y adc ($AC, x) ; (indirect, x) adc ($DC), y ; (indirect), y sbc #$44 ; immediate sbc $AA ; zero page sbc $7F, x ; zero page, x sbc $4FFF ; absolute sbc $88BB, x ; absolute, x sbc $24EE, y ; absolute, y sbc ($AC, x) ; (indirect, x) sbc ($DC), y ; (indirect), y cmp #$44 ; immediate cmp $AA ; zero page cmp $7F, x ; zero page, x cmp $4FFF ; absolute cmp $88BB, x ; absolute, x cmp $24EE, y ; absolute, y cmp ($AC, x) ; (indirect, x) cmp ($DC), y ; (indirect), y cpx #$88 ; immediate cpx $BB ; zero page cpx $3CCC ; absolute cpy #$88 ; immediate cpy $BB ; zero page cpy $3CCC ; absolute and #$44 ; immediate and $AA ; zero page and $7F, x ; zero page, x and $4FFF ; absolute and $88BB, x ; absolute, x and $24EE, y ; absolute, y and ($AC, x) ; (indirect, x) and ($DC), y ; (indirect), y ora #$44 ; immediate ora $AA ; zero page ora $7F, x ; zero page, x ora $4FFF ; absolute ora $88BB, x ; absolute, x ora $24EE, y ; absolute, y ora ($AC, x) ; (indirect, x) ora ($DC), y ; (indirect), y eor #$44 ; immediate eor $AA ; zero page eor $7F, x ; zero page, x eor $4FFF ; absolute eor $88BB, x ; absolute, x eor $24EE, y ; absolute, y eor ($AC, x) ; (indirect, x) eor ($DC), y ; (indirect), y bit $50 ; zero page bit $4000 ; absolute beq .a bne .a bcc .a bcs .a bvc .a bvs .a bmi .a bpl .a .a: brk clc cld cli clv dex dey inx iny nop pha php pla plp rti rts sec sed sei tax tay tsx txa txs tya Code: ;;;;;;;;;;;;;; ONE-BYTE INSTRUCTIONS ;;;;;;;;;;;;; irp <name,o>, brk,$00,\ clc,$18, cld,$D8, cli,$58, clv,$B8,\ dex,$CA, dey,$88, inx,$E8, iny,$C8,\ nop,$EA, pha,$48, php,$08, pla,$68,\ plp,$28, rti,$40, rts,$60, sec,$38,\ sed,$F8, sei,$78, tax,$AA, tay,$A8,\ tsx,$BA, txa,$8A, txs,$9A, tya,$98 macro name db o end macro end irp ;;;;;;;;;;;;;;;;;;;;; BRANCH ;;;;;;;;;;;;;;;;;;;;; macro jmp a match (x), a ; indirect db $6C dw x else match x, a ; absolute db $4C dw x end match end macro irp <name,o>,\ beq,$F0, bne,$D0, bcc,$90, bcs,$B0,\ bvc,$50, bvs,$70, bmi,$30, bpl,$10 macro name a db o, (255-($-a)) and $FF end macro end irp macro jsr a ; call subroutine db $20 dw a ; absolute end macro ;;;;;;;;;;;;;;;;;;;; INC, DEC ;;;;;;;;;;;;;;;;;;;; ; opc $80 ; zero page ; opc $80, x ; zero page, x ; opc $A000 ; absolute ; opc $8000, x ; absolute, x macro mos_id name, aaa, p local i, mode, size i=0 mode=0 size=0 match a=,b, p ; n, x expect b, x i=a if i>=0 & i<=$FF size=1 mode=101b else size=2 mode=111b end if else match a, p ; n i=a if i>=0 & i<=$FF size=1 mode=001b else size=2 mode=011b end if else err 'Error' end match verify_u16 i db (aaa shl 5) or \ (mode shl 2) or 2 if size=1 ; zero page db i else ; absolute dw i end if end macro macro inc p& mos_id inc, 111b, <p> end macro macro dec p& mos_id dec, 110b, <p> end macro ;;;;;;;;;;;;;;; ASL, LSR, ROL, ROR ;;;;;;;;;;;;;;; ; shift, rotate ; opc ; accumulator ; opc $80 ; zero page ; opc $80, x ; zero page, x ; opc $A000 ; absolute ; opc $8000, x ; absolute, x macro mos_s name, aaa, p local i, mode, size i=0 mode=0 size=0 match a=,b, p ; n, x expect b, x i=a if i>=0 & i<=$FF size=1 mode=101b else size=2 mode=111b end if else match _a, p ; x match =a, _a ; accumulator size=1 mode=010b else i=_a if i>=0 & i<=$FF size=1 mode=001b else size=2 mode=011b end if end match else ; accumulator size=1 mode=010b end match db (aaa shl 5) or \ (mode shl 2) or 2 if mode<>010b ; not accumulator? verify_u16 i if size=1 ; zero page db i else ; absolute dw i end if end if end macro irp <name,o>,\ asl,000b, rol,001b, lsr,010b, ror,011b macro name p& mos_s name, o, <p> end macro end irp ;;;;;;;; LDA, STA, ADC, SBC, ORA, CMP, ETC ;;;;;;; ; basic arithmetic ; opc #$44 ; immediate ; opc $AA ; zero page ; opc $7F, x ; zero page, x ; opc $4FFF ; absolute ; opc $88BB, x ; absolute, x ; opc $24EE, y ; absolute, y ; opc ($AC, x) ; (indirect, x) ; opc ($DC), y ; (indirect), y macro mos_a name, aaa, p local i, mode, size i=0 mode=0 size=0 match #a, p ; immediate i=a mode=010b size=1 match =sta, name err 'Invalid' end match else match (a=,b), p ; (indirect, x) expect b, x i=a mode=000b size=1 else match (a)=,b, p ; (indirect), y expect b, y i=a mode=100b size=1 else match a=,b, p ; ?, ? i=a verify_u16 i ; i, ? match =x, b ; i, x if i>=0 & i<=$FF ; zero page, x mode=101b size=1 else ; absolute, x mode=111b size=2 end if else match =y, b ; absolute, y mode=110b size=2 else err 'Error' end match else match a, p i=a verify_u16 i if i>=0 & i<=$FF ; zero page mode=001b size=1 else ; absolute mode=011b size=2 end if else err 'Error' end match db (aaa shl 5) or \ (mode shl 2) or 1 if size=1 db i else dw i end if end macro irp <name,o>,\ ora,000b, and,001b, eor,010b, adc,011b,\ sta,100b, lda,101b, cmp,110b, sbc,111b macro name p& mos_a name, o, <p> end macro end irp ;;;;;;;;;;;;;;;;;;;; STX, LDX ;;;;;;;;;;;;;;;;;;;; ; load/store x ; opc #$44 ; immediate ; opc $80 ; zero page ; opc $80, y ; zero page, y ; opc $AAAA ; absolute ; opc $AAAA, y ; absolute, y macro mos_lsx name, aaa, p local i, mode, size i=0 mode=0 size=0 match #a, p ; immediate i=a mode=000b size=1 match =stx, name err 'Error' end match else match a=,b, p ; ?, ? i=a verify_u16 i ; i, ? match =y, b ; i, y if i>=0 & i<=$FF ; zero page, y mode=101b size=1 else ; absolute, y mode=111b size=2 match =stx, name err 'Error' end match end if else err 'Error' end match else match a, p i=a verify_u16 i if i>=0 & i<=$FF ; zero page mode=001b size=1 else mode=011b ; absolute size=2 end if else err 'Error' end match db (aaa shl 5) or \ (mode shl 2) or 2 if size=1 db i else dw i end if end macro macro stx p& mos_lsx stx, 100b, <p> end macro macro ldx p& mos_lsx ldx, 101b, <p> end macro ;;;;;;;;;;;;;;;;;;;; STY, LDY ;;;;;;;;;;;;;;;;;;;; ; opc #$44 ; immediate ; opc $AA ; zero page ; opc $7F, x ; zero page, x ; opc $4FFF ; absolute ; opc $88BB, x ; absolute, x macro mos_lsy name, aaa, p local i, mode, size i=0 mode=0 size=0 match #a, p ; immediate i=a mode=000b size=1 match =sty, name err 'Error' end match else match a=,b, p ; ?, ? i=a verify_u16 i ; i, ? match =x, b ; i, x if i>=0 \ & i<=$FF ; zero page, x mode=101b size=1 else ; absolute, x mode=111b size=2 end if else err 'Error' end match else match a, p i=a verify_u16 i if i>=0 & i<=$FF ; zero page mode=001b size=1 else ; absolute mode=011b size=2 end if else err 'Error' end match db (aaa shl 5) or \ (mode shl 2) if size=1 db i else dw i end if end macro macro sty p& mos_lsy sty, 100b, <p> end macro macro ldy p& mos_lsy ldy, 101b, <p> end macro ;;;;;;;;;;;;;;;;;;;; CPX, CPY ;;;;;;;;;;;;;;;;;;;; ; compare x/y ; opc #$44 ; immediate ; opc $AA ; zero page ; opc $4FFF ; absolute macro mos_c name, aaa, p local i, mode, size i=0 mode=0 size=0 match #a, p ; immediate verify_u8 a i=a mode=000b size=1 else match a, p ; x i=a verify_u16 i if i>=0 \ & i<=$FF ; zero page mode=001b size=1 else ; absolute mode=011b size=2 end if else err 'Error' end match db (aaa shl 5) \ or (mode shl 2) if size=1 db i else dw i end if end macro macro cpx p& mos_c cpx, 111b, <p> end macro macro cpy p& mos_c cpy, 110b, <p> end macro ;;;;;;;;;;;;;;;;;;;;;;; BIT ;;;;;;;;;;;;;;;;;;;;;; macro bit i verify_u16 i if i>=0 & i<=$FF ; zero page db $24, i else ; absolute db $2C dw i end if end macro
|
|||||||||||
11 May 2015, 17:44 |
|
shoorick 16 Jul 2015, 19:57
is it case sensitive?
|
|||
16 Jul 2015, 19:57 |
|
ProMiNick 18 Jun 2017, 15:26
I tryed to play with this opcode set (example got from Internet some decoration of expressions as operands added). nice. codestar, your macros allow to make code as readable as posible & it almost not needed in commenting (all logic can be placed in operands).
examle/6502/snake/snake.asm (I prefixed absolute opcodes by + to allow expression in them and unify them, but i didn`t used expression for absolutes, so preciding + can be removed from example) Code: ;rename binary as 'SNAKE.BIN' ; ___ _ __ ___ __ ___ ; / __|_ _ __ _| |_____ / /| __|/ \_ ) ; \__ \ ' \/ _` | / / -_) _ \__ \ () / / ; |___/_||_\__,_|_\_\___\___/___/\__/___| ; Change direction: W A S D include '6502/6502.inc' include 'snake.inc' ;uninitialized data: virtual at 0 apple screen_coord snakeDirection db ? snakeLength db ? align $10 snakeHead screen_coord snakeBody screen_coord end virtual ;code: org $0600 jsr init jsr loop init: jsr initSnake jsr generateApplePosition rts initSnake: lda #movingRight sta +snakeDirection lda #2*sizeof screen_coord sta +snakeLength lda #(screen.pixel_17_16) lobyte ;lo:sreen_coord 17,16 sta +snakeHead.lo lda #(screen.pixel_16_16) lobyte ;lo:sreen_coord 16,16 sta +snakeBody.lo+0*sizeof screen_coord lda #(screen.pixel_15_16) lobyte ;lo:sreen_coord 15,16 sta +snakeBody.lo+1*sizeof screen_coord lda #(screen.pixel_ANY_16) hibyte ;hi:sreen_coord any,16 hi the same for any x of 16th row sta +snakeHead.hi sta +snakeBody.hi+0*sizeof screen_coord sta +snakeBody.hi+1*sizeof screen_coord rts generateApplePosition: lda +sysRandom ;lo:screen random,random sta +apple.lo lda +sysRandom and #(screen.size-1) hibyte clc adc #screen hibyte ;hi:screen random,random sta +apple.hi rts loop: jsr readKeys jsr checkCollision jsr updateSnake jsr drawApple jsr drawSnake jsr spinWheels jmp loop rts readKeys: lda +sysLastKey cmp #ASCII_W beq upKey cmp #ASCII_D beq rightKey cmp #ASCII_S beq downKey cmp #ASCII_A beq leftKey rts upKey: lda #movingDown bit +snakeDirection bne illegalMove lda #movingUp sta +snakeDirection rts rightKey: lda #movingLeft bit +snakeDirection bne illegalMove lda #movingRight sta +snakeDirection rts downKey: lda #movingUp bit +snakeDirection bne illegalMove lda #movingDown sta +snakeDirection rts leftKey: lda #movingRight bit +snakeDirection bne illegalMove lda #movingLeft sta +snakeDirection rts illegalMove: rts checkCollision: jsr checkAppleCollision jsr checkSnakeCollision rts checkAppleCollision: lda +apple.lo cmp +snakeHead.lo bne .CheckingOut lda +apple.hi cmp +snakeHead.hi bne .CheckingOut .eat_apple: repeat sizeof screen_coord inc +snakeLength end repeat jsr generateApplePosition .CheckingOut: rts checkSnakeCollision: ldx #sizeof screen_coord .snakeCollisionLoop: lda +snakeHead.lo,x cmp +snakeHead.lo bne .continueCollisionLoop .maybeCollided: lda +snakeHead.hi,x cmp +snakeHead.hi bne .continueCollisionLoop .continueCollisionLoop: repeat sizeof screen_coord inx end repeat cpx +snakeLength beq .didntCollide jmp .snakeCollisionLoop .didCollide: jmp gameOver .didntCollide: rts updateSnake: ldx +snakeLength dex txa .updateLoop: lda +snakeHead.lo,x sta +snakeBody.lo,x dex bpl .updateLoop lda +snakeDirection lsr bcs .up lsr bcs .right lsr bcs .down lsr bcs .left .up: lda +snakeHead.lo sec sbc #1*screen_line_length sta snakeHead.lo bcc .upup rts .upup: dec +snakeHead.hi lda #(screen-1) hibyte ; out of screen: before top row cmp +snakeHead.hi beq .collision rts .right: inc +snakeHead.lo lda #(screen.line_length-1) bit +snakeHead.lo beq .collision rts .down: lda +snakeHead.lo clc adc #1*screen.line_length sta +snakeHead.lo bcs .downdown rts .downdown: inc +snakeHead.hi lda #(screen+screen.size) hibyte ; out of screen: after last row cmp +snakeHead.hi beq .collision rts .left: dec +snakeHead.lo lda +snakeHead.lo and #(screen.line_length-1) cmp #(screen.line_length-1) beq .collision rts .collision: jmp gameOver drawApple: ldy #0 lda +sysRandom sta +apple.lo,y rts drawSnake: ldx +snakeLength lda #Black sta (snakeHead.lo,x) ; erase end of tail ldx #0 lda #White sta (snakeHead.lo,x) ; paint head rts spinWheels: ;time size=$402 cycles ldx #0 .spinloop: ;time size=255 times of 4 cycles of CPU nop nop dex bne .spinloop rts gameOver: examle/6502/snake/snake.inc Code: movingUp = 1 movingRight = 2 movingDown = 4 movingLeft = 8 include\6502\6502.inc (Your macros codestar) Code: ... ;;;;;;;;;;;;;;;;;;;; VERIFY ;;;;;;;;;;;;;;;;;;;;;; include 'equates.inc' ;added only this four lines include 'system.inc' include 'screen.inc' include 'macro.inc' macro verify_n n, min, max ... include\6502\equates.inc Code: ;fundamentals false? = 0 true? = 1 page? = $100 lobyte equ and $FF hibyte equ shr 8 ;sysKey codes ASCII_W = $77 ASCII_A = $61 ASCII_S = $73 ASCII_D = $64 ; Colors Black = $0 White = $1 Red = $2 Cian = $3 Purple = $4 Green = $5 Blue = $6 Yellow = $7 Orange = $8 Brown = $9 Light_Red = $A Dark_Grey = $B Grey = $C Light_Green = $D Light_Blue = $E Light_Grey = $F include\6502\system.inc Code: virtual at $FE
sysRandom db ?
sysLastKey db ?
end virtual include\6502\screen.inc Code: screen_line_length = 32 virtual at $0200 screen: .line_length = 32 repeat screen.line_length, y:0 repeat screen.line_length, x:0 if used .pixel_#x#_#y label .pixel_#x#_#y end if db ? end repeat if ($-32) hibyte = ($-1) hibyte label .pixel_ANY_#y at $-1 end if end repeat .size = $ - screen end virtual virtual at 0 screen_coord dw ? ; define (sizeof screen_coord) = 2 end virtual struc screen_coord X:0,Y:0 assert X = X and (screen.line_length-1) assert Y = Y and (screen.line_length-1) label .lo at $ label .hi at $+1 dw screen+X+Y shl 5 end struc include\6502\macro.inc Code: macro align? boundary,value:? db (boundary-1)-(($ scale 0)+boundary-1) mod boundary dup value end macro macro label_EoP_fix ; Label that located on both pages is unreachable, protect against it if $ and $FF = $FF nop end if end macro |
|||
18 Jun 2017, 15:26 |
|
< Last Thread | Next Thread > |
Forum Rules:
|
Copyright © 1999-2025, Tomasz Grysztar. Also on GitHub, YouTube.
Website powered by rwasa.