Assembler (As65)

The assembler (As65) produces a relocatable object modules by compiling lines of source code held in local files. The format of each source line must follow the pattern shown below. The 'square' brackets enclose optional components within the line (like the label) whilst the  '(X|Y)' pattern indicates a choice between types delimited by '|' characters. 

[[label[:]] [(opcode|directive|macro) [arguments]]] [; comment]

Opcodes and directives names are case insensitive in source code but labels and macro names are case sensitive. Given this syntax all of the following examples are valid.

; A comment line
a_label_by_itself
        NOP             ; Opcode with no argument followed by a comment
        nop             ; Same as above
        LDA #1
        .6502		; Generate code for 6502 processor
        MYMACRO 1,2,3   ; Generate a parameterised macro

Labels

Labels can  be placed before all opcodes or on lines by themselves. A global label is comprised of a letter or underscore ('_') followed by a series of alphanumeric and/or underscore characters. A label may optionally be followed by a colon (':').

A local label has the same grammatical construction as a global label but begins with a period ('.'). Whilst a global label may only be used once with a module a local label may be defined several times provided it appears each time within the scope of a different global label.

SomeGlobalLabel:
.ALocalLabel:

Most directives do not allow labels. Those that do give them special meaning (e.g. macro name, symbol name in .EQU and .SET, etc.)

Expressions

The arguments provided to most opcodes and directives are expression comprised of absolute (e.g. constant literals), relative (e.g. the address of some relocatable instruction or piece of data) and external values (e.g. values defined in other source modules).

The expression parser evaluates operations on absolute values during processing to produce constant values but expressions involving relative and external terms are left for the linker to resolve. The following table shows all the supported operators in decreasing order or precedence.  

Operator Description
$
*
.
@
The current instruction origin
( sub-expression )
number
symbol
'character literal'
Unary values
+
-
~
!
LO
HI
BANK
Unary plus (ignored)
Negation
Complement
Logical Not
Bits 7 to 0
Bits 15 to 8
Bits 31 to 16
*
/
%
Multiply
Divide
Remainder
+
-
Addition
Subtraction
<<
>>
Right Shift
Left Shift
<
<=
>
>=
Less Than
Less Than Or Equal
Greater Than
Greater Than Or Equal
==
!=
Equal
Not Equal
&
|
^
Binary AND
Binary OR
Binary XOR
&&
||
Logical AND
Logical OR

Expressions may only contain numeric values. There are no string functions.

Literals

Literal numeric values can be expressed in binary, decimal, octal, decimal and as character values. Literal values may be up to 32-bits in size and all expressions are evaluated at this precision. Values are masked to 8- and 16- bits when generating code.

        LDA #%10101100    ; Load a binary constant
        LDX #@177         ; Load an octal constant
        LDA 127           ; Load from a location specified in decimal
        STA $FFC1         ; Store at a location specified in hexadecimal
        lda #'X'          ; Load ASCII for 'X' into the accumlator
        .LONG 'ABCD'      ; A 32-bit character constant

Directives

This section descibes commands which control the assembler and the generation of code.

.6501

This directive places the assembler in 6501 processor mode. The 6501 processor supports all normal 6502 instructions as well as the extended BBR, BBS, SMB and RMB instructions.

.6502

This directive places the assembler in 6502 processor mode. Only the traditional 6502 instructions and addressing modes are supported.

.65C02

This directive places the assembler in 65C02 processor mode.  The 65C02 processor supports all normal 6502 instructions plus new addressing modes and extra some instructions including the BBR, BBS, SMB and RMB instructions, 

.65SC02

This directive places the assembler in 65SC02 processor mode.  The 65SC02 processor supports the same instructions as the 65C02 BUT does not have then extended BBR, BBS, SMB and RMB instructions, 

.65816

This directive places the assembler into 65816 processor mode.

.65832

This directive places the assembler into 65832 processor mode.

(The 65832 was designed by WDC but never actually made it into production. It is very similar to the 65816 but supports 32-bit accumulator and index registers. This feature is experimental).

.EQU <expr>

Creates a symbol having the value indicated by the expression, for example the following creates a symbol for the ASII carriage return character. An error will be generated if the symbol is already defined.

CR      .EQU  $0D

As65 accepts '= <expr>' as an alternative syntax when defining equates for compatibility with other assemblers.

.SET <expr>

Creates a symbol having the value indicated by the expression. Unlink .EQU the .SET directive will not complain if the same symbol is assigned a value multiple times. This can be useful when defining counters or calculating intermediate results within macros.

COUNT   .SET COUNT+1

.CODE

The .CODE directive tells the assembler to place any code generated by instructution or data directives into the object files code section.

.DATA

The .DATA directive tells the assembler to place any code generated by instructution or data directives into the object files initialised data section.

.BSS

The .BSS directive tells the assembler to place any code generated by instructution or data directives into the object files uninitialised data section.

.PAGE0

The .PAGE0 directive tells the assembler to place any code generated by instructution or data directives into a specially marked section that will be located on page 0 ($0000-$00FF on 8-bit CPUs or $000000-$00FFFF on 16-bit CPUs) .

.ORG <constant expr>

The .ORG directive sets the absolute target address for the current section. For compatibility with other assemblers As65 will also accept  '*= <expr>'.

.DPAGE <constant expr> (65816/65832 only)

The .DPAGE directive informs the assembler of the assumed value of the direct page register for the following sequence of instructions so that direct-page addressing can be used instead of absolute where possible.

.DBREG <constant expr> (65816/65832 only)

The .DBREG directive informs the assembler of the assumed value of the data bank register for the following sequence of instructions so that absolute address can be used instead of long absolute where possible.

.LONGA (ON|OFF) (65816/65832 only)

When compiling for the 65816 processor this directive controls the size of immediate values loaded into the accumulator. If a .LONGA ON directive has been processed then 16 bit literals will be generated otherwise they will be 8 bits.

.LONGI (ON|OFF) (65816/65832 only)

When compiling for the 65816 processor this directive controls the size of immediate values loaded into the X and Y registers. If a .LONGI ON directive has been processed then 16 bit literals will be generated otherwise they will be 8 bits.

.WIDEA (ON|OFF) (65832 only)

When compiling for the 65832 processor this directive controls the size of immediate values loaded into the accumulator. If a .WIDEA ON directive has been processed then 32 bit literals will be generated otherwise they will be 8 bits.

.WIDEI (ON|OFF) (65832 only)

When compiling for the 65832 processor this directive controls the size of immediate values loaded into the X and Y registers. If a .WIDEI ON directive has been processed then 32 bit literals will be generated otherwise they will be 8 bits.

.IF <constant expr>

Assembles the following source code up to the matching .ELSE or .ENDIF if the constant expression evaluates to a non-zero value.

        JSR DoSomething
        .IF DEBUGGING
        JSR DumpRegisters
        .ENDIF
        JSR DoTheNextBit

.IFABS <expr>

Assembles the following source code up to the matching .ELSE or .ENDIF if the expression evaluates to a absolute (i.e. constant) value.

This directive is useful in macros to test the type of the parameter value.

.IFNABS <expr>

Assembles the following source code up to the matching .ELSE or .ENDIF if the expression does not evaluate to a absolute (i.e. constant) value.

This directive is useful in macros to test the type of the parameter value.

.IFREL <expr>

Assembles the following source code up to the matching .ELSE or .ENDIF if the expression evaluates to a relocatable value.

This directive is useful in macros to test the type of the parameter value.

.IFNREL <expr>

Assembles the following source code up to the matching .ELSE or .ENDIF if the expression does not evaluate to a relocatable value.

This directive is useful in macros to test the type of the parameter value.

.ELSE

Assembles the folloing source code up the matching .ENDIF if the condition for the preceding matching .IF, .IFABS, .IFNABS, .IFREL, .IFNREL directive was not met. 

.ENDIF

The .ENDIF directive marks the end of condition code section.

.INCLUDE "filename"

Causes the contents of the indicated file to be read and processed before the remainder of the current file.

.APPEND "filename"

The current source file is close and processing continues at the first line of the indicated file.

        NOP

        .APPEND "AnotherFile.asm"

        NOP             ; This line will not be processed.

.END

The .END directive marks the end of the source code.

        NOP

        .END

        NOP             ; This line will not be processed.

.INSERT "filename"

The .INSERT directive reads the binary contents of the indicated file and inserts it directly into the generated object code.

A typically use is to insert pre-compiled data such as graphics images, encryption keys or lookup tables into the code.

.REPEAT <constant expr>

Causes the source lines up to the matching .ENDR directive to repeated the number of times indicated by the constant expression

        .REPEAT 8       ; Generate 8 NOPs
        NOP
        .ENDR

.ENDR

Marks the end of .REPEAT section.

.MACRO [<arg>[,<arg>]*]

The .MACRO directive indicates that the following source lines upto the matching .ENDM should be used to define a macro. The name of the macro is taken from the label preceding the .MACRO command.

_NOT16 .MACRO VLA,RES
        LDA VLA+0
        EOR #$FF
        STA RES+0
        LDA VLA+1
        EOR #$FF
        STA RES+1
        .ENDM

Macro arguments can be accessed by defining symbolic names for them or by positional references (using \0 thru \9). The sequence \? can be used with a macro to obtain the macro expansion count, for example to generate unique labels for branches within the macro.

.ENDM

Marks the end of a .MACRO definition

.EXITM

When used within a macro it causes an immediate termination of the expansion process.

.GLOBAL <symbol>[,<symbol>]*

The .GLOBAL directive lists one or more symbols defined in the current module that can be referenced by code in other modules.

.EXTERN <symbol>[,<symbol>]*

The .EXTERN directive lists one or more symbols defined in other modules so that they can be used in expressions within the current module (e.g. subroutine addresses, key data areas, etc.).

.BYTE  (<expr>|<string>)[,(<expr>|<string>)]*

The .BYTE directive deposits a series of 8-bit values into the object code for the current module. The values can be defined as the result of an expression (this includes simple numeric values) or as strings delimited by quotes.

        .BYTE "Hello World",$0D,$0A,0

.DBYTE <expr>[,<expr>]*

The .DBYTE directive deposits a series of 16-bit values defined by a series of expressions into the object code for the current module. The values are defined most significant byte first.

        .DBYTE 1,$2,3+5

.WORD <expr>[,<expr>]*

The .WORD directive deposits a series of 16-bit values defined by a series of expressions into the object code for the current module. The values are defined least significant byte first.

        .WORD 1,$2,3+5

.ADDR <expr>,[<expr>]*

The .ADDR directive deposits a series of 24-bit values defined by a series of expressions into the object code for the current module.

        .ADDR Function1,Function2

The .ADDR directive is primarily intended for creating function jump tables for the 65816 processor.

.LONG <expr>[,<expr>]*

The .LONG directive deposits a series of 32-bit values defined by a series of expressions into the object code for the current module.

        .LONG 1,$2,3+5

.SPACE <constant expr>

The .SPACE directive reserves the specified number of zero valued bytes in the object code.

PTRA    .SPACE 2

.LIST

The .LIST directive enables the output of lines to the listing file.

.NOLIST

The .NOLIST directive suspends the generation of a listing.

.TITLE

The .TITLE directive sets the string shown as the title at the top of the listing page.

.PAGE

The .PAGE directive forces the listing to restart at the top of the next page.

Opcodes

The assembler recognizes all the opcodes for the 6501, 6502, 65C02, 65SC02 and 65816 processors but will only generate code for currently selected processor type. Using an inappropriate opcode will generate an error.

Opcode 6501 6502 65C02 65SC02 65816
ADC Y Y Y Y Y
AND Y Y Y Y Y
ASL Y Y Y Y Y
BBR0
BBR1
BBR2
BBR3
BBR4
BBR5
BBR6
BBR7
Y   Y    
BBS0
BBS1
BBS2
BBS3
BBS4
BBS5
BBS6
BBS7
Y   Y    
BCC Y Y Y Y Y
BCS Y Y Y Y Y
BEQ Y Y Y Y Y
BIT Y Y Y Y Y
BMI Y Y Y Y Y
BNE Y Y Y Y Y
BPL Y Y Y Y Y
BRA     Y Y Y
BRK Y Y Y Y Y
BRL         Y
BVC Y Y Y Y Y
BVS Y Y Y Y Y
CLC Y Y Y Y Y
CLD Y Y Y Y Y
CLI Y Y Y Y Y
CLV Y Y Y Y Y
CMP Y Y Y Y Y
COP         Y
CPX Y Y Y Y Y
CPY Y Y Y Y Y
DEC Y Y Y Y Y
DEX Y Y Y Y Y
DEY Y Y Y Y Y
EOR Y Y Y Y Y
INC Y Y Y Y Y
INX Y Y Y Y Y
INY Y Y Y Y Y
JML         Y
JSL         Y
LDA Y Y Y Y Y
LDX Y Y Y Y Y
LDY Y Y Y Y Y
LSR Y Y Y Y Y
MVN         Y
MVP         Y
NOP Y Y Y Y Y
ORA Y Y Y Y Y
PEA         Y
PEI         Y
PER         Y
PHA Y Y Y Y Y
PHB         Y
PHD         Y
PHK         Y
PHX     Y Y Y
PHY     Y Y Y
PLA Y Y Y Y Y
PLB         Y
PLD         Y
PLP Y Y Y Y Y
PLX     Y Y Y
PLY     Y Y Y
REP          
RMB0
RMB1
RMB2
RMB3
RMB4
RMB5
RMB6
RMB7
Y   Y    
ROL Y Y Y Y Y
ROR Y Y Y Y Y
RTI Y Y Y Y Y
RTL         Y
RTS Y Y Y Y Y
SBC Y Y Y Y Y
SEC Y Y Y Y Y
SED Y Y Y Y Y
SEI Y Y Y Y Y
SEP         Y
SMB0
SMB1
SMB2
SMB3
SMB4
SMB5
SMB6
SMB7
Y   Y    
STA Y Y Y Y Y
STP     Y Y Y
STX Y Y Y Y Y
STY Y Y Y Y Y
STZ     Y Y Y
TAX Y Y Y Y Y
TAY Y Y Y Y Y
TCD         Y
TCS         Y
TDC         Y
TRB     Y Y Y
TSB     Y Y Y
TSX Y Y Y Y Y
TXA Y Y Y Y Y
TXS Y Y Y Y Y
TXY         Y
TYA Y Y Y Y Y
TYX         Y
WAI     Y Y Y
WDM         Y
XBA         Y
XCE         Y

 

Addressing Modes

The 65xx family of processors support a number of different addressing modes which can be used with each instruction.

Syntax Description
Implied
A Accumulator
#expr Immediate
#<expr Immediate (lo byte)
#>expr Immediate (hi byte)
#^expr Immediate (bank byte)
<expr Direct
<expr,X Direct Indexed by X 
<expr,Y Direct Indexed by Y
>expr Absolute Long (65816 only)
>expr,X Absolute Long Indexed by X (65816 only)
[expr] Long Indirect (65816 only)
[expr],Y Long Indirect Indexed (65816 only)
(expr,X) Indexed Indirect
(expr),Y Indirect Indexed
(expr,S),Y Stack Relative Indirect Indexed (65816 only)
(expr) Indirect
|expr Absolute
|expr,X Absolute Indexed by X
|expr,Y Absolute Indexed by Y
expr Absolute or Direct
expr,X Absolute or Direct Indexed by X
expr,Y Absolute or Direct Indexed by Y 
expr,S Stack Relative (65816 only)

If the absolute address of the target memory location is known the assembler will attempt to generate the smallest instruction (e.g. direct page instead of absolute). The explicit direct (< expr) and absolute (| expr or !expr) allow the programmer to specify an exact addressing mode for expressions which are not absolute, for example those referencing external symbols.

The assembler allows the implied addressing mode to be used with shift and rotate instructions and treats it as if the accumulator mode had been specified.

BRK & COP

The BRK and COP instructions are usually documented as implied although they both expect the opcode to be followed by a data byte and the PC is incremented by two.

The assembler allows these instructions to be used either in the normal implied way or with the immediate addressing mode to specify the data byte. For example the following results in the same code.

         BRK             ; Normal usage
        .BYTE $7E

        BRK #$7E        ; Generate opcode and data byte together

Code Sections

The assembler can generate code into four different sections (e.g. CODE, DATA, BSS and PAGE0). At the start of each pass the sections are defined as relative. Using the .ORG directive any section can be forced to place code or data at a specific absolute memory address.

         .CODE
        NOP             ; A relocatable NOP

        .ORG $F000      ; Make the section absolute
        NOP             ; Place a NOP at $F000

        .DATA           ; Switch to the (relative) DATA section
        .BYTE 1,2,3


        .CODE           ; Switch back to the absolute code section
        NOP             ; Place a NOP at $F001

You can switch between the sections throughout your code. Any code or data generated will be added where the section was left when it was previously used.

Once a section has been made absolute it can not be made relative again. The .ORG directive can be used multiple times within the same section, for example to reserve memory in different RAM areas.

Structured Assembly

The assembler supports a simple from of structured programming (e.g. IF..ELSE..ENDIF, REPEAT..UNTIL, etc.) based on the flag bits in the condition register. The assembler will generate the branches needed to implement these control structures without you having to define any labels. It also tries to generate the smallest amount of code using relative branches (e.g. BRA, BEQ, BPL, etc.) when it can, only resorting to JMP when it has to.

Structured code may not be as efficient as normal hand coded routines (due to the extra branches) but this is often outweighed by the enhanced readability and reduction in labels.

IF..ELSE..ENDIF

An IF command starts a block of code that will only be executed if the indicated condition (e.g. EQ, NE, CC, CS, PL, MI, VC or VS) exists . For example a simple 16-bit increment can be coded as follows

        INC VAL+0
        IF EQ
         INC VAL+1
        ENDIF

The ELSE command can be used to defined an alternate block of code to be executed if the condition was not true.

        AND #$01
        IF EQ
         ; A contained an even number
        ELSE
         ; A contained an odd number
        ENDIF

REPEAT..UNTIL|FOREVER

The REPEAT and UNTIL commands can be used to defined a piece of code that repeats (at least once) until some condition is true. For example the following code counts the bits in A by arithmetically shifting it left until result of the shift is zero.

        LDX #0
        REPEAT
         ASL A
         PHP
         IF CS
          INX
         ENDIF
         PLP
        UNTIL EQ

If you want a loop that repeats endlessly then use the FOREVER keyword at the end instead of UNTIL.

WHILE..ENDW

The WHILE and ENDW commands produce a block of code that will repeat while some condition is true.

        WHILE EQ
        ENDW 

BREAK & CONTINUE

Both the REPEAT and WHILE loops can contain the loop modifiers BREAK and CONTINUE.

The BREAK command generates a branch to the next instruction immediately after the matching UNTIL, FOREVER or ENDW.

        LDX #0
        REPEAT
         CPX #7
         IF EQ
          BREAK
         ENDIF
         INX
        FOREVER

Similarly the CONTINUE generates a branch back to the start of REPEAT or WHILE loop to force the start of the next iteration.

Both BREAK and CONTINUE allow an optional condition code argument that makes the branch conditional. For example the last example could be written more efficiently as follows.

        LDX #0
        REPEAT
         CPX #7
         BREAK EQ
         INX
        FOREVER

 

 << Back
Home
Contents Next >>

This page was last updated on 9th March 2018