Original written for DOS by Marek Matula of Taboo, then ported to ansi C by BigFoot/Breeze, and finally added 65816 support, DTV, illegal opcodes, optimizations, multi pass compile and a lot of features by Soci/Singular. Improved TASS compatibility, PETSCII codes by Groepaz.
Additional code: my_getopt command-line argument parser by Benjamin Sittler, avl tree code by Franck Bui-Huu, ternary tree code by Daniel Berlin.
Syntax is the same as the well known Turbo Assembler on c64, so you can port your sources easy by only replacing the CR at the end of each line.
Main developer and maintainer: soci at c64.rulez.org
This is a development version, features or syntax may change over time. Not everything is backwards compatible.
64tass is a command line compiler, the source can be written in any text editor. As a minimum the source filename must be given on command line.
64tass src.asm
There are also some useful parameters which are described later.
For comfortable compiling I use such Makefile
s (for make):
demo.prg: source.asm makros.asm pic.drp music.bin 64tass -C -a -B -i source.asm -o demo.tmp pucrunch -ffast -x 2048 demo.tmp >demo.prg
This way demo.prg
is recreated by compiling source.asm
whenever source.asm
, makros.asm
, pic.drp
or music.bin
had changed.
Of course it's not much harder to create something similar for win32 (make.bat), however this will always compile and compress:
64tass.exe -C -a -B -i source.asm -o demo.tmp pucrunch.exe -ffast -x 2048 demo.tmp >demo.prg
Here's a slightly more advanced Makefile example with default action as testing in VICE, clean target for removal of temporary files and compressing using an intermediate temporary file:
all: demo.prg x64 -autostartprgmode 1 -autostart-warp +truedrive +cart $< demo.prg: demo.tmp pucrunch -ffast -x 2048 $< >$@ demo.tmp: source.asm makros.asm pic.drp music.bin 64tass -C -a -B -i $< -o $@ .INTERMEDIATE: demo.tmp .PHONY: all clean clean: $(RM) demo.prg demo.tmp
Another useful thing is to add a basic header to your source files like the one below, so that the resulting file is directly runnable without additional compression:
*= $0801 .word (+), 2005 ;pointer, line number .null $9e, ^start;will be sys 4096 + .word 0 ;basic line end *= $1000 start rts
A frequently comming up question is, how to automatically allocate
memory, without hacks like *=*+1
? Sure
there's .byte
and friends for variables with initial values
but what about zero page, or RAM outside of program area? The solution
is to not use an initial value by using '?
' or not
giving a fill byte value to .fill
.
*= $02 p1 .word ? ;a zero page pointer temp .fill 10 ;a 10 byte temporary area
Space allocated this way is not saved in the output as there's no data to save at those addresses.
What about some code running on zero page for speed? It needs to be relocated, and the length must be known to copy it there. Here's an example:
ldx #size(zpcode)-1;calculate length - lda zpcode,x sta wrbyte,x dex ;install to zeropage bpl - jsr wrbyte rts ;code continues here but is compiled to run from $02 zpcode .logical $02 wrbyte sta $ffff ;quick byte writer at $02 inc wrbyte+1 bne + inc wrbyte+2 + rts .here
The assembler supports lists and tuples, which does not seems interesting at first as it sound like something which is only useful when heavy scripting is involved. But as normal arithmetic operations also apply on all their elements at once, this could spare quite some typing and repetition.
Let's take a simple example of a low/high byte jump table of return
addresses, this usually involves some unnecessary copy/pasting to create a pair
of tables with constructs like >(label-1)
.
jumpcmd lda hibytes,x ; selected routine in X register pha lda lobytes,x ; push address to stack pha rts ; jump, rts will increase pc by one! ; Build an anonymous list of jump addresses minus 1 - = (cmd_p, cmd_c, cmd_m, cmd_s, cmd_r, cmd_l, cmd_e)-1 lobytes .byte <(-) ; low bytes of jump addresses hibytes .byte >(-) ; high bytes
For writing short code there are some special pseudo instructions for always
taken branches. These are automatically compiled as relative branches when the
jump distance is short enough and as JMP
or BRL
when
longer. The names are derived from conditional branches and are:
GEQ
, GNE
, GCC
, GCS
,
GPL
, GMI
, GVC
, and GVS
.
There's one more called GRA
for CPUs supporting
BRA
, which is expanded to BRL
(if available) or
JMP
.
.0000 a9 03 lda #$03 in1 lda #3 .0002 d0 02 gne $0006 gne at ;branch always .0004 a9 02 lda #$02 in2 lda #2 .0006 4c 00 10 gne $1000 at gne $1000 ;branch further
If the branch would skip only one byte then the opposite condition is compiled and only the first byte is emitted. This is now a never executed jump, and the relative distance byte after the opcode is the jumped over byte.
If the branch would not skip anything at all then no code is generated.
.0009 geq $0009 geq in3 ;zero length "branch" .0009 18 clc in3 clc .000a b0 gcc $000c gcc at2 ;one byte skip, as bcs .000b 38 sec in4 sec ;sec is skipped! .000c 20 0f 00 jsr $000f at2 jsr func .000f func
Please note that expressions like Gxx *+2
or Gxx
*+3
are not allowed as the compiler can't figure out if it has to create
no code at all, the 1 byte variant or the 2 byte one. Therefore use normal or
anonymous labels defined after the jump instruction when jumping forward!
To avoid branch too long errors the assembler also supports long branches,
it can automatically convert conditional relative branches to it's opposite and
a JMP
or BRL
. This can be enabled on the command
line using the --long-branch
option.
.0000 ea nop nop
.0001 b0 03 4c 00 10 bcc $1000 bcc $1000 ;long branch
.0006 ea nop nop
Please note that forward jump expressions like Bxx *+130
,
Bxx *+131
and Bxx *+132
are not allowed as the
compiler can't decide between a short/long branch. Of course these destinations
can be used, but only with normal or anonymous labels defined after the jump
instruction.
There are some other tips below in the descriptions.
The default output filename is a.out
. This option changes it.
Strips the 2 or 3 byte starting address before the resulting binary. Useful for creating small ROM images.
Output the plain binary image from offset 0. The image size can be much larger than the processor address space. Useful for creating huge multi bank ROM files.
Generates non-linear output for linkers. Format: length, address, code, length, ...
If 16 MiB address space is used for a 65816, then the starting address of file will be 3 bytes long. This option makes it 2 bytes long.
Normally no conversion takes place, this is for backwards compatibility with a DOS based Turbo Assembler editor, which could create PETSCII files for 6502tass. (including control characters of course)
Using this option will change the default none
and screen
encodings to
map 'a'-'z' and 'A'-'Z' into the correct PETSCII range of $41-$5A and $C1-$DA,
which is more suitable for an ASCII editor. It also adds predefined petcat style
PETASCII literals to the default encodings.
For writing sources in utf8/utf16 encodings this option is required! The symbol names are still limited to ASCII, but custom string encodings can take advantage of the full unicode set.
BXX *+5 JMP xxx
Branch too long messages can be annoying sometimes, usually they'll result
in an BXX *+5 JMP xxx
rewrite. 64tass can do this automatically if this option is
used. But BRA
is not converted.
Labels are non case sensitive by default, this option changes that.
Defines a label to a value. Same syntax is allowed as in source files. Be careful with string quoting, the shell might eat some of the characters.
Disables warnings during compile.
Disables header and summary messages.
Switches the expression evaluator into compatibility mode. This
enables .
, :
and !
operators and disables 64tass specific extensions, disables precedence handling
and forces 16 bit unsigned evaluation (see differences to original Turbo Assembler
below)
If an included source or binary file can't be found in the directory of the source file then this path is tried. More than one directories can be specified by repeating this option. If multiple matches exist the first one is used.
These options will select the default architecture. It can be overridden by
using the .cpu
directive in the source.
Selects standard 6502. For writing compatible code, no extra codes. This is the default.
Selects 65c02. Enables extra opcodes and addressing modes specific to this CPU.
Selects 65ce02. Enables extra opcodes and addressing modes specific to this CPU.
Selects NMOS 6502. Enables extra illegal opcodes. Useful for demo coding for C64, disk drive code, etc.
Selects 65DTV02. Enables extra opcodes specific to DTV.
Selects 65816. Enables extra opcodes, and full 16 MiB address space.
Useful for SuperCPU projects. Don't forget to use --word-start
for small ones ;)
Selects 65EL02. Enables extra opcodes, useful RedPower CPU projects. Probably you'll need --nostart
as well.
Selects r65c02. Enables extra opcodes and addressing modes specific to this CPU.
Selects w65c02. Enables extra opcodes and addressing modes specific to this CPU.
List global labels to a file. Unused ones are marked with a comment.
Dumps source code and compiled code into file. Useful for debugging, it's much easier to identify the code in memory within the source files.
There won't be any monitor listing in the list file.
There won't be any source listing in the list file.
Prints help about command line options.
Prints short help about command line options.
Prints program version.
Integer constants can be entered as decimal ([0-9]+
),
hexadecimal ($[0-9a-f]*
) or binary (%[01]*
). Short
strings of few characters are converted to a numeric constant using the current
encoding at the place of use. The following operations are accepted:
x + y | add x to y | 2 + 2 is 4
| |||
x - y | substract y from x | 4 - 1 is 3
| |||
x * y | multiply x with y | 2 * 3 is 6
| |||
x / y | integer divide x by y | 7 / 2 is 3
| |||
x % y | integer modulo of x divided by y | 5 % 2 is 1
| |||
x ** y | x raised t power of y | 2 ** 4 is 16
| |||
-x | negated value | -2 is -2
| |||
+x | unchanged | +2 is 2
| |||
< | lower byte | <$1234 is $34
| |||
> | higher byte | >$1234 is $12
| |||
` | bank byte | `$123456 is $12
| |||
<> | lower word | <>$123456 is $3456
| |||
>` | higher word | <`$123456 is $1234
| |||
>< | lower byte swapped word | ><$123456 is $5634
| |||
x == y | x equals to y | 2 == 3 is <false>
| |||
x != y | x does not equal to y | 2 != 3 is <true>
| |||
x < y | x is less than y | 2 < 3 is <true>
| |||
x > y | x is more than y | 2 > 3 is <false>
| |||
x >= y | x is more than y or equals | 2 >= 3 is <false>
| |||
x <= y | x is less than y or equals | 2 <= 3 is <true>
| |||
x | y | bitwise or | 2 | 6 is 6
| |||
x ^ y | bitwise xor | 2 ^ 6 is 4
| |||
x & y | bitwise and | 2 & 6 is 2
| |||
x << y | logical shift left | 1 << 3 is 8
| |||
x >> y | arithmetic shift right | -8 >> 3 is -1
| |||
~x | invert bits | ~%101 is %010
| |||
.. | concatenate bits | $a..$b is $ab
| |||
x[n] | extract bit | $a[1] is 0
| |||
x[s] | slice bits | $1234[4:8] is $3
| |||
len(a) | length in bits |
|
An integer has a truth value of <true> if it's non-zero. The <true> value is the same as 1.
Length of a numeric constants are defined in bits and is calculated from the number of digits used for hexadecimal (4 each) and binary (1 each) definitions. It's also set when slicing, bit (1), byte (8) or word (16) extraction is used.
Integers are automatically promoted to float as necessary in expressions.
.byte 23 ; decimal .byte $33 ; hex .byte %00011111 ; binary lda #<label ldy #>label jsr $ab1e ldx #<>source ; word extraction ldy #<>dest lda #size(source)-1 mvn `source, `dest; bank extraction lda #((bitmap & $2000) >> 10) | ((screen & $3c00) >> 6) sta $d018 lda $d015 and #~%00100000 sta $d015
Floating point constants have a decimal mark in them and optionally an exponent. The following operations can be used on them:
x + y | add x to y | 2.2 + 2.2 is 4.4
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
x - y | substract y from x | 4.1 - 1.1 is 3.0
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
x * y | multiply x with y | 1.5 * 3 is 4.5
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
x / y | integer divide x by y | 7.0 / 2.0 is 3.5
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
x % y | integer modulo of x divided by y | 5.0 % 2.0 is 1.0
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
x ** y | x raised t power of y | 2.0 ** -1 is 0.5
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
~x | -(x+1) value | ~2.1 is -3.1
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
-x | negated value | -2.0 is -2.0
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+x | unchanged | +2.0 is 2.0
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
x == y | x equals to y | 2.0 == 3.0 is <false>
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
x != y | x does not equal to y | 2.0 != 3.0 is <true>
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
x < y | x is less than y | 2.0 < 3.0 is <true>
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
x > y | x is more than y | 2.0 > 3.0 is <false>
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
x >= y | x is more than y or equals | 2.0 >= 3.0 is <false>
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
x <= y | x is less than y or equals | 2.0 <= 3.0 is <true>
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
abs(a) | Absolute value | abs(-1.0) is 1.0
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
sign(a) | Sign value (-1, 0, 1) | sign(-4.0) is -1
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
floor(a) | Round down | floor(-4.8) is -5.0
| |||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
round(a) | Round to nearest away from zero | floor(4.8) is |
A floating point number has a truth value of <true> if it's non-zero.
As usual comparing floating point numbers for (non) equality is a bad idea due to rounding errors.
There are no predefined floating point constants, define them as necessary. Hint: pi is rad(180)
and e is exp(1)
.
Floating point numbers are automatically truncated to integer as necessary.
.byte 3.66e1 ; real, truncated to 36
Strings are enclosed in single or double quotes and can hold any unicode character. Operations like indexing or slicing are always done on the original representation. The current encoding is only applied when it's used in expressions as numeric constants or in context of text data directives. Doubling the quotes inside the strings escapes them.
.. | concatenate strings | "a".."b" is "ab"
|
x[i] | character from start | "abc"[1] is "b"
|
x[i] | character from end | "abc"[-1] is "c"
|
x[s] | no change | "abc"[:] is "abc"
|
x[s] | cut off start | "abc"[1:] is "bc"
|
x[s] | cut off end | "abc"[:-1] is "ab"
|
x[s] | reverse | "abc"[::-1] is "cba"
|
len(x) | number of characters | len("abc") is 3
|
A string has a truth value of <true> if it contains at least one character.
Strings are converted to numeric constants as necessary using the current
encoding and escape rules, for example when using a sane encoding "z" - "a"
is
25
.
Indexing characters with positive integers start with zero. Negative indexes are translated internally by adding the number of characters to them, therefore -1 can be used to access the last character.
Slicing is an operation when parts of string are extracted from a start position to an end position with a step value. These parameters are separated with colons enclosed in square brackets and are all optional. Their default values are [start:maximum:step=1]. Negative start and end characters are converted to positive internally by adding the length of string to them. Negative step operates in reverse direction, non single steps will jump over characters.
mystr = "oeU" ; text .text 'it''s' ; text: it's .word "ab"+1 ; character, results in "bb" usually .text "text"[:2] ; "te" .text "text"[2:] ; "xt" .text "text"[:-1] ; "tex" .text "reverse"[::-1]; "esrever"
Lists and tuples can hold a collection of values. Lists are defined from
values separated by comma between square brackets [1,2,3]
, an
empty list is []
. Tuples are similar but are enclosed in
parentheses instead. An empty tuple is ()
, a single element tuple
is (4,)
to differentiate from normal numeric expression
parentheses. When nested they function similar to an array. Currently both
types are immutable.
.. | concatenate lists | [1]..[2] is [1, 2]
|
x[i] | element from start | ("1", 2)[1] is 2
|
x[i] | element from end | ("1", 2, 3)[-1] is 3
|
x[s] | no change | (1, 2, 3)[:] is (1, 2, 3)
|
x[s] | cut off start | (1, 2, 3)[1:] is (2, 3)
|
x[s] | cut off end | (1, 2.0, 3)[:-1] is (1, 2.0)
|
x[s] | reverse | (1, 2, 3)[::-1] is (3, 2, 1)
|
len(x) | number of elements | len([1, 2, 3]) is 3
|
range(s,e,t) | create a list with values from a range | range(3) is [0,1,2]
|
A list or tuple has a truth value of <true> if it contains at least one element.
When arithmetic operations are applied they execute on the all elements
recursively, therefore [1, 2] + 1
is [2, 3]
, and abs([1, -1])
is [1, 1]
.
Indexing elements with positive integers start with zero. Negative indexes are transformed to positive by adding the number of elements to them, therefor -1 is the last element.
Slicing is an operation when parts of list or tuple are extracted from a start position to an end position with a step value. These parameters are separated with colons enclosed in square brackets and are all optional. Their default values are [start:maximum:step=1]. Negative start and end elements are converted to positive internally by adding the number of elements to them. Negative step operates in reverse direction, non single steps will jump over elements.
mylist = [1, 2, "whatever"] mytuple = (cmd_e, cmd_g) mylist = ("e", cmd_e, "g", cmd_g, "i", cmd_i) keys .text mylist[::2] ; keys ("e", "g", "i") call_l .byte <mylist[1::2]-1; routines (<cmd_e-1, <cmd_g-1, <cmd_i-1) call_h .byte >mylist[1::2]-1; routines (>cmd_e-1, >cmd_g-1, >cmd_i-1)
The range(start, end, step)
built in function can be used to
create lists of integers in a range with a given step value. At least the end
must be given, the start defaults to 0 and the step to 1. Sounds not very
useful, so here are a few examples:
;Bitmask table, 8 bits from left to right .byte %10000000 >> range(8) ;Classic 256 byte single period sinus table with values of 0-255. .byte 128.5+127*sin(range(256)*rad(360.0/256)) ;Screen row address tables - = $400+range(0, 1000, 40) scrlo .byte <(-) scrhi .byte >(-)
Normal labels can be defined at the start of each line. Each of them is uniq and can't be redefined. In arithmetic operations they represent the numeric addresses of a memory location. Additionally they also hold the compiled code and data definitions in binary format.
A label represents by default only the single line it is found on unless
block directives are used where it's extended till the end of block. The
content is not forward referencable, only the address of label. Usually the
size of a single element is a byte, but this can be more for data definitions.
Trying to overwrite
the same memory locations later does not affect the
content anymore.
. | member | label.locallabel
|
x[i] | element from start | label[1]
|
x[i] | element from end | label[-1]
|
x[s] | copy as tuple | label[:]
|
x[s] | cut off start, as tuple | label[1:]
|
x[s] | cut off end, as tuple | label[:-1]
|
x[s] | reverse, as tuple | label[::-1]
|
len(x) | number of elements | len(label)
|
size(a) | size in bytes | size(label)
|
A label has a truth value of <true> when it's address is non-zero.
mydata .word 1, 4, 3 mycode .block local lda #0 .bend ldx #size(mydata) ;6 bytes (3*2) ldx #len(mydata) ;3 elements ldx #mycode[0] ;lda instruction, $a9 ldx #mydata[1] ;2nd element, 4 jmp mycode.local ;address of local label
The assembler supports anonymous labels, also called as forward (+)
and backward (-) references. -
means one backward,
--
means two backward, etc. also the same for forward, but with
+
.
ldy #4 - ldx #0 - txa cmp #3 bcc + adc #44 + sta $400,x inx bne - dey bne --
Excessive nesting or long distance references create a poorly readable code. It's also very easy to insert a few new references in a way to break the old ones around by mistake.
These references are also useful in segments, but this can create a nice traps, as segments are copied into the code, with the internal references.
bne + #somemakro ;let's hope that this segment does + nop ;not contain forward references...
References can reference labels, results from expressions or other references.
Constant references can be created with the equal sign. These are not redefinable. Forward referencing to them is allowed as they retain the reference to constant objects over compilation passes.
border = $d020 ;a constant reference f .block g .block n nop ;jump here .bend .bend inc border ;inc $d020 jsr labelref.n labelref = f.g
Redefinable references can be created by the .var
directive.
As it's redefinable it can only be used in code after it's definition. Even
tricks like using constant references on them will not help with forward
referencing. They simply don't carry their last reference over from the
previous pass.
variabl .var 1 .rept 10 .byte variabl variabl .var variabl+1 .next
Boolean conditional operators give false (0) or true (1) or one of the operands as the result. True is defined as a non-zero number, a non-empty string/tuple/list, anything else is false.
x || y | if x is true then x otherwise y |
x ^^ y | if both false or true then false otherwise x || y |
x && y | if x is true then y otherwise x |
!x | if x is true then false otherwise true |
!!x | if x is true then true otherwise false |
;Silly example for 1=>"simple", 2=>"advanced", else "normal" .text MODE == 1 && "simple" || MODE == 2 && "advanced" || "normal"
The conditional operator gives the first (x) result if c is true or the second (y) if c is false.
c ? x : y | if c is true then x otherwise y |
;Silly example for 1=>"simple", 2=>"advanced", else "normal" .text MODE == 1 ? "simple" : MODE == 2 ? "advanced" : "normal"
Parenthesis (( )
) can be used to override operator precedence.
Don't forget that they also denote indirect addressing mode for certain
opcodes.
lda #(4+2)*3
Built in functions are identifiers followed by parentheses. They accept variable number of parameters separated by comma.
min(a, b, ...) | Minimum of values |
max(a, b, ...) | Maximum of values |
Special addressing mode forcing operators in front of an expression can be used to make sure the expected addressing mode is used.
@b | to force 8 bit address |
@w | to force 16 bit address |
@l | to force 24 bit address (65816) |
lda @w$0000
There are two address counters. One is used for placing the data in memory, the other one called logical address, and it's what the labels will be set or what the special star label gets when referenced.
.logical
.
*= $1000
.offs 100
.logical $300 drive lda #$80 sta $00 jmp drive ;jmp $300 rts .here
Here's an example how .logical
and *=
works together:
*= $0800 ;Compile: $0800, Logical: $0800 .logical $1000 ;Compile: $0800, Logical: $1000 *= $1200 ;Compile: $0a00, Logical: $1200 .here ;Compile: $0a00, Logical: $0a00
.align $100 irq inc $d019 ;this will be on a page boundary, after skipping bytes .align 4, $ea loop adc #1 ;padding with "nop" for DTV burst mode
.text "oeU" ; text, "" means $22 .text 'oeU' ; text, '' means $27 .text 23, $33 ; bytes .text %00011111 ; more bytes .text ^OEU ; the decimal value as string (^23 is $32,$33)
.text
, but the last byte will have the highest bit set.
Any character which already has the most significiant bit set will cause an error.
ldx #0 loop lda txt,x php and #$7f jsr $ffd2 inx plp bpl loop rts txt .shift "some text"
.text
, but all bytes are shifted to left, and the last
character gets the lowest bit set. Any character which already has the most significiant
bit set will cause an error as this would be cut off.
ldx #0 loop lda txt,x lsr sta $400,x inx bcc loop rts .enc screen txt .shiftl "some text" .enc none
.text
, but adds a null at the end, null in string is an error.
txt .text "lot of stuff" .null "to write" lda #<txt ldy #>txt jsr $ab1e
.text
, but prepend the
number of bytes in front of the string (pascal style string). Longer than 255 bytes are not allowed.
lda #<txt ldx #>txt jsr print rts print sta $fb stx $fc ldy #0 lda ($fb),y beq null tax - iny lda ($fb),y jsr $ffd2 dex bne - null rts txt .ptext "note"
.byte 255 ; $ff .byte ? ; reserve 1 byte of space
.char -33, 57
.word $2342, $4555 .word ? ; reserve 2 bytes of space
.int -533, 4433
lda #0 asl tax lda rets+1,x pha lda rets,x pha rts rets .rta $fce2
.long $123456 .long ? ; reserve 3 bytes of space
.dword $12345678 .dword ? ; reserve 4 bytes of space
.dint -533, 4433
.rept
!
.fill $100 ;no fill, just reserve $100 bytes .fill $4000, 0 ;16384 bytes of 0
noneand
screen(screen code), anything else is user defined. All user encodings start without any character or escape definitions, add some as required.
.enc screen ;screencode mode .text "text with screencodes" cmp #"u" ;compare screencode .enc none ;normal mode again cmp #"u" ;compare ascii
.enc petscii ;define an ascii->petscii encoding .cdef " @", 32 ;characters .cdef "AZ", $c1 .cdef "az", $41 .cdef "[[", $5b .cdef "££", $5c .cdef "]]", $5d .cdef "ππ", $5e .cdef $2190, $2190, $1f;left arrow .edef "\n", 13 ;escape sequences .edef "{clr}", 147 .text "{clr}Text in PETSCII\n"
Structures can be defined to organize sequential data definitions, which can be reused later many times. The offset of fields are available by using the definition's name as a base, and the fields themselves by using the instance name before the dot operator. The length of a struct is the sum of lengths of all items.
.struct ;anonymous struct x .byte 0 ;labels are visible y .byte 0 ;content compiled here .ends ;useful inside unions nn_s .struct ;named struct x .byte 0 ;labels are not visible y .byte 0 ;no content is compiled here .ends ;it's just a definition nn .dstruct nn_s ;struct instance, content here lda nn.x ;access internal fields ldy #nn_s.x ;get offset of field
Unions are similar to structs, except each line will start on the same address where the definition was done. The length of the union is the length of it's longest item. The offset of fields are available by using the definition's name as a base, and the fields themselves by using the instance name before the dot operator. These offsets and references mostly point to the start of the union, unless internal anonymous structs are used.
.union ;anonymous union x .byte 0 ;labels are visible y .word 0 ;content compiled here .endu nn_u .union ;named union x .byte 0 ;labels are not visible y .word 0 ;no content is compiled here .endu ;it's just a definition nn .dunion nn_u ;union instance here lda nn.x ;access internal fields ldy #nn_u.x ;get offset of field
The example below shown how to define structure to a binary include.
.union .binary "pic.drp",2 .struct color .fill 1024 screen .fill 1024 bitmap .fill 8000 backg .byte ? .ends .endu
Anonymous structs and unions in combination with sections are useful for
overlapping memory assignment. The example below shares zeropage allocations
for two separate parts of a bigger program. The common subroutine variables
are assigned after in the zp
section.
*= $02 .union ;spare some memory .struct .dsection zp1 ;declare zp1 section .send zp1 .ends .struct .dsection zp2 ;declare zp2 section .send zp2 .ends .endu .dsection zp ;declare zp section .send zp
fill .macro lp sta \1,x inx bne lp .endm name .segment sta $d020 sta $d021 .endm lda #1 #name ;call macro #fill $400 #fill $500
name .macro
lda #\1 ;first parameter
.endm
#name 23 ;call macro
name .macro jsr print .null "Hello @1!";first parameter .endm #name wth? ;call macro
.if oeu==1 nop .else lda #1 .fi
.if wait==2 ;2 cycles nop .elsif wait==3 ;3 cycles bit $ea .elsif wait==4 ;4 cycles bit $eaea .else ;else 5 cycles inc $2 .fi
ldx #0 lda #32 lp .for ue=0,ue<$400,ue=ue+$100 sta ue,x .next dex bne lp
.rept 100
nop
.next
.goto
i .var 100 loop .lbl nop i .var i - 1 .ifne i .goto loop ;generates 100 nops .fi
.include "macros.asm"
loading addressis ignored, and if not skipped then it's also loaded as data. By using offset and length it's possible to break out chunks of data from a file separately, like bitmap and colors for example. The filename can be a string expression.
.binary "stuffz.bin" ;simple include, all bytes .binary "stuffz.bin",2 ;skip start address .binary "stuffz.bin",2,1000 ;skip start address, 1000 bytes max *= $1000 ;load music to $1000 and .binary "music.dmc",2 ;strip load address
ize .proc nop cucc nop .pend jsr ize jmp ize.cuccIf
izeis not referenced then the code won't be compiled at all! All labels inside are local.
.block inc count + 1 count ldx #0 .bendAll labels inside a block are local.
.comment lda #1 ;this won't be compiled sta $d020 .endc
Sections are useful for linking sources, or to organize memory layout. With them it's easily possible to allocate addresses for variables at the place of actual use enclosed by the current scope. It can also be used to collect data or code to specific memory areas, or to ease the generation of code and data to multiple locations simultaniously in a single loop or macro.
All .section
-s scattered around in the sources are compiled
from the .dsection
declaration. Compilation happens as the code
appears, this directive only assigns enough space to hold all the stuff in the
sections. Where the .dsection
appears the section's private
address and logical address are initialized to the current values.
The space allocated is calculated by the difference of the initial private address and the private address after the last section was compiled. It is possible to adjust the address in sections in a non incremental way, but it must be done carefully otherwise the space allocation will be not right, in that case you must manually adjust the address and logical address after the section declaration.
Sections and section declarations can be nested, therefore it's possible to have the same names as long as it's inside a differently named section. Parent section names are visible for children, siblings can be reached through parents.
*= $02 .dsection zp ;declare zeropage section .send zp .cerror *>$30,"Too many zeropage variables" *= $334 .dsection bss ;declare uninitialized variable section .send bss .cerror *>$400,"Too many variables" *= $0801 .dsection code ;declare code section .word ss, 2005 .null $9e, ^start ss .word 0 .send code .cerror *>$1000,"Program too long!" *= $1000 .dsection data ;declare data section .send data .cerror *>$2000,"Data too long!" ;-------------------- .section code start sei .section zp ;declare some new zeropage variables p2 .word ? ;a pointer .send zp .section bss ;new variables buffer .fill 10 ;temporary area .send bss lda (p2),y lda #<label ldy #>label jsr print .section data ;some data label .null "message" .send data jmp error .section zp ;declare some more zeropage variables p3 .word ? ;a pointer .send zp .send code
The compiled code will look like:
>0801 0b 08 d5 07 .word ss, 2005 >0805 9e 32 30 36 31 00 .null $9e, ^start >080b 00 00 ss .word 0 *= $1000 .080d 78 start sei >0002 p2 .word ? ;a pointer .0334 buffer .fill 10 ;temporary area .080e b1 02 lda (p2),y .0810 a9 00 lda #<label .0812 a0 10 ldy #>label .0814 20 1e ab jsr print >1000 6d 65 73 73 61 67 65 00 label .null "message" .0817 4c e2 fc jmp error >0004 p2 .word ? ;a pointer
.al
lda #$4322
.xl
ldx #$1000
.databank $10 ;$10xxxx
.dpage $400
.page table .byte 0,1,2,3,4,5,6,7 .endp
.option allow_branch_across_page = 0 ldx #3 ;now this will execute in - dex ;16 cycles for sure bne - .option allow_branch_across_page = 1
.error "Unfinished here..." .cerror *>$1200, "Program too long by ", *-$1200, " bytes"
.warn "FIXME: handle negative values too!" .cwarn *>$1200, "This may not work!"
.cpu 6502 ;standard 65xx .cpu 65c02 ;CMOS 65C02 .cpu 65ce02 ;CSG 65CE02 .cpu 6502i ;NMOS 65xx .cpu 65816 ;W65C816 .cpu 65dtv02 ;65dtv02 .cpu 65el02 ;65el02 .cpu r65c02 ;R65C02 .cpu w65c02 ;W65C02 .cpu default ;cpu set on commandline
encryption.
.proff ;Don't put filler bytes into listing *= $8000 .fill $2000, $ff ;Pre-fill ROM area .pron *= $8000 .word reset, restore .text "CBM80" reset cld
TMPviewby Style to convert the sourcefile directly, or do the following:
64tass -C -T -a -W -i source.s -o outfile.prg
64tass is nearly 100% compatible with the original Turbo Assembler
, and supports
most of the features of the original Turbo Assembler Macro
.
The remaining notable differences are listed here:
The original turbo assembler uses case sensitive labels, use the -C, --case-sensitive option to enable this behaviour.
Another thing worth noting is that the original turbo assembler lets you create
an interesting ambiguous construct using a label called a
.
lsr a ; uses accu ! (or does it really?) a jmp a ; uses the label address .word a ; uses the label address
If you get a warning like warning: Possibly incorrectly used A "lsr a"
, then there
is such an ambiguous situation in your code and you should fix it (by renaming the label).
There are a few differences which can be worked around by the -T, --tasm-compatible option. These are:
The original expression parser has no operator precedence, but 64tass has. That
means that you will have to fix expressions using braces accordingly, for example
1+2*3
becomes (1+2)*3
.
The following operators used by the original Turbo Assembler are different:
The default expression evaluation is not limited to 16 bit unsigned numbers anymore.
aas label
The standard 6502 opcodes:
ADC $61, $65, $69, $6D, $71, $75, $79, $7D AND $21, $25, $29, $2D, $31, $35, $39, $3D ASL $06, $0A, $0E, $16, $1E BCC $90 BCS $B0 BEQ $F0 BIT $24, $2C BMI $30 BNE $D0 BPL $10 BRK $00 BVC $50 BVS $70 CLC $18 CLD $D8 CLI $58 CLV $B8 CMP $C1, $C5, $C9, $CD, $D1, $D5, $D9, $DD CPX $E0, $E4, $EC CPY $C0, $C4, $CC DEC $C6, $CE, $D6, $DE DEX $CA DEY $88 EOR $41, $45, $49, $4D, $51, $55, $59, $5D INC $E6, $EE, $F6, $FE INX $E8 INY $C8 JMP $4C, $6C JSR $20 LDA $A1, $A5, $A9, $AD, $B1, $B5, $B9, $BD LDX $A2, $A6, $AE, $B6, $BE LDY $A0, $A4, $AC, $B4, $BC LSR $46, $4A, $4E, $56, $5E NOP $EA ORA $01, $05, $09, $0D, $11, $15, $19, $1D PHA $48 PHP $08 PLA $68 PLP $28 ROL $26, $2A, $2E, $36, $3E ROR $66, $6A, $6E, $76, $7E RTI $40 RTS $60 SBC $E1, $E5, $E9, $ED, $F1, $F5, $F9, $FD SEC $38 SED $F8 SEI $78 STA $81, $85, $8D, $91, $95, $99, $9D STX $86, $8E, $96 STY $84, $8C, $94 TAX $AA TAY $A8 TSX $BA TXA $8A TXS $9A TYA $98
Aliases, pseudo instructions:
ASL $0A BGE $B0 BLT $90 GCC $4C, $90 GCS $4C, $B0 GEQ $4C, $F0 GGE $4C, $B0 GLT $4C, $90 GMI $30, $4C GNE $4C, $D0 GPL $10, $4C GVC $4C, $50 GVS $4C, $70 LSR $4A ROL $2A ROR $6A
The standard 6502 opcodes, plus additionally:
ANC $0B ANE $8B ARR $6B ASR $4B DCP $C3, $C7, $CF, $D3, $D7, $DB, $DF ISB $E3, $E7, $EF, $F3, $F7, $FB, $FF JAM $02 LAX $A3, $A7, $AB, $AF, $B3, $B7, $BF LDS $BB NOP $04, $0C, $14, $1C, $80 RLA $23, $27, $2F, $33, $37, $3B, $3F RRA $63, $67, $6F, $73, $77, $7B, $7F SAX $83, $87, $8F, $97 SBX $CB SHA $93, $9F SHS $9B SHX $9E SHY $9C SLO $03, $07, $0F, $13, $17, $1B, $1F SRE $43, $47, $4F, $53, $57, $5B, $5F
Additional aliases:
AHX $93, $9F ALR $4B AXS $CB DCM $C3, $C7, $CF, $D3, $D7, $DB, $DF INS $E3, $E7, $EF, $F3, $F7, $FB, $FF ISC $E3, $E7, $EF, $F3, $F7, $FB, $FF LAE $BB LAS $BB LXA $AB TAS $9B XAA $8B
Additionally to 6502 illegal opcodes:
BRA $12 SAC $32 SIR $42
Additional pseudo instruction:
GRA $12, $4C
These illegal opcodes are not valid:
ANC $0B JAM $02 LDS $BB NOP $04, $0C, $14, $1C, $80 SBX $CB SHA $93, $9F SHS $9B SHX $9E SHY $9C
These illegal aliases are not valid:
AHX $93, $9F AXS $CB LAE $BB LAS $BB TAS $9B
Additional opcodes to standard 6502:
ADC $72 AND $32 BIT $34, $3C, $89 BRA $80 CMP $D2 DEC $3A EOR $52 INC $1A JMP $7C LDA $B2 ORA $12 PHX $DA PHY $5A PLX $FA PLY $7A SBC $F2 STA $92 STZ $64, $74, $9C, $9E TRB $14, $1C TSB $04, $0C
Additional aliases and pseudo instructions:
DEA $3A GRA $4C, $80 INA $1A
Additional opcodes to standard 65C02:
BBR $0F, $1F, $2F, $3F, $4F, $5F, $6F, $7F BBS $8F, $9F, $AF, $BF, $CF, $DF, $EF, $FF RMB $07, $17, $27, $37, $47, $57, $67, $77 SMB $87, $97, $A7, $B7, $C7, $D7, $E7, $F7
Additional opcodes to R65C02:
STP $DB WAI $CB
Additional opcodes to standard 65C02:
ADC $63, $67, $6F, $73, $77, $7F AND $23, $27, $2F, $33, $37, $3F BRL $82 CMP $C3, $C7, $CF, $D3, $D7, $DF COP $02 EOR $43, $47, $4F, $53, $57, $5F JMP $5C, $DC JSL $22 JSR $FC LDA $A3, $A7, $AF, $B3, $B7, $BF MVN $54 MVP $44 ORA $03, $07, $0F, $13, $17, $1F PEA $F4 PEI $D4 PER $62 PHB $8B PHD $0B PHK $4B PLB $AB PLD $2B REP $C2 RTL $6B SBC $E3, $E7, $EF, $F3, $F7, $FF SEP $E2 STA $83, $87, $8F, $93, $97, $9F STP $DB SWA $EB TAD $5B TAS $1B TCD $5B TCS $1B TDA $7B TDC $7B TSA $3B TSC $3B TXY $9B TYX $BB XBA $EB XCE $FB WAI $CB
Additional aliases:
JML $5C, $DC
Additional opcodes to standard 65C02:
ADC $63, $67, $73, $77 AND $23, $27, $33, $37 CMP $C3, $C7, $D3, $D7 DIV $4F, $5F, $6F, $7F ENT $22 EOR $43, $47, $53, $57 JSR $FC LDA $A3, $A7, $B3, $B7 MMU $EF MUL $0F, $1F, $2F, $3F NXA $42 NXT $02 ORA $03, $07, $13, $17 PEA $F4 PEI $D4 PER $62 PHD $DF PLD $CF REA $44 REI $54 REP $C2 RER $82 RHA $4B RHI $0B RHX $1B RHY $5B RLA $6B RLI $2B RLX $3B RLY $7B SBC $E3, $E7, $F3, $F7 SEA $9F SEP $E2 STA $83, $87, $93, $97 STP $DB SWA $EB TAD $BF TDA $AF TIX $DC TRX $AB TXI $5C TXR $8B TXY $9B TYX $BB WAI $CB XBA $EB XCE $FB ZEA $8F
Additional opcodes to R65C02:
ASR $43, $44, $54 ASW $CB BCC $93 BCS $B3 BEQ $F3 BMI $33 BNE $D3 BPL $13 BRA $83 BSR $63 BVC $53 BVS $73 CLE $02 CPZ $C2, $D4, $DC DEW $C3 DEZ $3B INW $E3 INZ $1B JSR $22, $23 LDA $E2 LDZ $A3, $AB, $BB NEG $42 PHW $F4, $FC PHZ $DB PLZ $FB ROW $EB RTS $62 SEE $03 STA $82 STX $9B STY $8B TAB $5B TAZ $4B TSY $0B TYS $2B TZA $6B
Additional aliases to R65C02:
ASR $43 BGE $B3 BLT $93 NEG $42 RTN $62