Next Previous Contents

6. Control commands

Here's a list of all control commands and a description, what they do:

6.1 .A16

Valid only in 65816 mode. Switch the accumulator to 16 bit.

Note: This command will not emit any code, it will tell the assembler to create 16 bit operands for immediate accumulator adressing mode.

See also: .SMART

6.2 .A8

Valid only in 65816 mode. Switch the accumulator to 8 bit.

Note: This command will not emit any code, it will tell the assembler to create 8 bit operands for immediate accu adressing mode.

See also: .SMART

6.3 .ADDR

Define word sized data. In 6502 mode, this is an alias for .WORD and may be used for better readability if the data words are address values. In 65816 mode, the address is forced to be 16 bit wide to fit into the current segment. See also .FARADDR. The command must be followed by a sequence of (not necessarily constant) expressions.

Example:

        .addr   $0D00, $AF13, _Clear
  

See: .FARADDR

6.4 .ALIGN

Align data to a given boundary. The command expects a constant integer argument that must be a power of two, plus an optional second argument in byte range. If there is a second argument, it is used as fill value, otherwise the value defined in the linker configuration file is used (the default for this value is zero).

Since alignment depends on the base address of the module, you must give the same (or a greater) alignment for the segment when linking. The linker will give you a warning, if you don't do that.

Example:

        .align  256
  

6.5 .ASCIIZ

Define a string with a trailing zero.

Example:

        Msg:    .asciiz "Hello world"
  

This will put the string "Hello world" followed by a binary zero into the current segment. There may be more strings separated by commas, but the binary zero is only appended once (after the last one).

6.6 .AUTOIMPORT

Is followd by a plus or a minus character. When switched on (using a +), undefined symbols are automatically marked as import instead of giving errors. When switched off (which is the default so this does not make much sense), this does not happen and an error message is displayed. The state of the autoimport flag is evaluated when the complete source was translated, before outputing actual code, so it is not possible to switch this feature on or off for separate sections of code. The last setting is used for all symbols.

You should probably not use this switch because it delays error messages about undefined symbols until the link stage. The cc65 compiler (which is supposed to produce correct assembler code in all circumstances, something which is not true for most assembler programmers) will insert this command to avoid importing each and every routine from the runtime library.

Example:

        .autoimport     +       ; Switch on auto import
  

6.7 .BLANK

Builtin function. The function evaluates its argument in braces and yields "false" if the argument is non blank (there is an argument), and "true" if there is no argument. As an example, the .IFBLANK statement may be replaced by

        .if     .blank(arg)
  

6.8 .BSS

Switch to the BSS segment. The name of the BSS segment is always "BSS", so this is a shortcut for

        .segment  "BSS"
  

See also the .SEGMENT command.

6.9 .BYTE

Define byte sized data. Must be followed by a sequence of (byte ranged) expressions or strings.

Example:

        .byte   "Hello world", $0D, $00
  

6.10 .CASE

Switch on or off case sensitivity on identifiers. The default is off (that is, identifiers are case sensitive), but may be changed by the -i switch on the command line. The command must be followed by a '+' or '-' character to switch the option on or off respectively.

Example:

        .case   -               ; Identifiers are not case sensitive
  

6.11 .CODE

Switch to the CODE segment. The name of the CODE segment is always "CODE", so this is a shortcut for

        .segment  "CODE"
  

See also the .SEGMENT command.

6.12 .CONDES

Export a symbol and mark it in a special way. The linker is able to build tables of all such symbols. This may be used to automatically create a list of functions needed to initialize linked library modules.

Note: The linker has a feature to build a table of marked routines, but it is your code that must call these routines, so just declaring a symbol with .CONDES does nothing by itself.

All symbols are exported as an absolute (16 bit) symbol. You don't need to use an additional .EXPORT statement, this is implied by .CONDES.

.CONDES is followed by the type, which may be constructor, destructor or a numeric value between 0 and 6 (where 0 is the same as specifiying constructor and 1 is equal to specifying destructor). The .CONSTRUCTOR and .DESTRUCTOR commands are actually shortcuts for .CONDES with a type of constructor resp. destructor.

After the type, an optional priority may be specified. If no priority is given, the default priority of 7 is used. Be careful when assigning priorities to your own module constructors so they won't interfere with the ones in the cc65 library.

Example:

        .condes         ModuleInit, constructor
        .condes         ModInit, 0, 16
  

See the .CONSTRUCTOR and .DESTRUCTOR commands and the separate section Module constructors/destructors explaining the feature in more detail.

6.13 .CONCAT

Builtin function. The function allows to concatenate a list of string constants separated by commas. The result is a string constant that is the concatentation of all arguments. This function is most useful in macros and when used together with the .STRING builtin function. The function may be used in any case where a string constant is expected.

Example:

        .include        .concat ("myheader", ".", "inc)
  

This is the same as the command

        .include        "myheader.inc"
  

6.14 .CONST

Builtin function. The function evaluates its argument in braces and yields "true" if the argument is a constant expression (that is, an expression that yields a constant value at assembly time) and "false" otherwise. As an example, the .IFCONST statement may be replaced by

        .if     .const(a + 3)
  

6.15 .CONSTRUCTOR

Export a symbol and mark it as a module constructor. This may be used together with the linker to build a table of constructor subroutines that are called by the startup code.

Note: The linker has a feature to build a table of marked routines, but it is your code that must call these routines, so just declaring a symbol as constructor does nothing by itself.

A constructor is always exported as an absolute (16 bit) symbol. You don't need to use an additional .export statement, this is implied by .constructor. It may have an optional priority that is separated by a comma. If no priority is given, the default priority of 7 is used. Be careful when assigning priorities to your own module constructors so they won't interfere with the ones in the cc65 library.

Example:

        .constructor    ModuleInit
        .constructor    ModInit, 16
  

See the .CONDES and .DESTRUCTOR commands and the separate section Module constructors/destructors explaining the feature in more detail.

6.16 .CPU

Reading this pseudo variable will give a constant integer value that tells which instruction set is currently enabled. Possible values are:

        0 -->   6502
        1 -->   65SC02
        2 -->   65SC816
        3 -->   SunPlus SPC
  

It may be used to replace the .IFPxx pseudo instructions or to construct even more complex expressions.

Example:

        .if     (.cpu = 0) .or (.cpu = 1)
                txa
                pha
                tya
                pha
        .else
                phx
                phy
        .endif
  

6.17 .DATA

Switch to the DATA segment. The name of the DATA segment is always "DATA", so this is a shortcut for

        .segment  "DATA"
  

See also the .SEGMENT command.

6.18 .DBYT

Define word sized data with the hi and lo bytes swapped (use .WORD to create word sized data in native 65XX format). Must be followed by a sequence of (word ranged) expressions.

Example:

        .dbyt   $1234, $4512
  

This will emit the bytes

        $12 $34 $45 $12
  

into the current segment in that order.

6.19 .DEBUGINFO

Switch on or off debug info generation. The default is off (that is, the object file will not contain debug infos), but may be changed by the -g switch on the command line. The command must be followed by a '+' or '-' character to switch the option on or off respectively.

Example:

        .debuginfo      +       ; Generate debug info
  

6.20 .DEFINE

Start a define style macro definition. The command is followed by an identifier (the macro name) and optionally by a list of formal arguments in braces. See section Macros.

6.21 .DEF, .DEFINED

Builtin function. The function expects an identifier as argument in braces. The argument is evaluated, and the function yields "true" if the identifier is a symbol that is already defined somewhere in the source file up to the current position. Otherwise the function yields false. As an example, the .IFDEF statement may be replaced by

        .if     .defined(a)
  

6.22 .DESTRUCTOR

Export a symbol and mark it as a module destructor. This may be used together with the linker to build a table of destructor subroutines that are called by the startup code.

Note: The linker has a feature to build a table of marked routines, but it is your code that must call these routines, so just declaring a symbol as constructor does nothing by itself.

A destructor is always exported as an absolute (16 bit) symbol. You don't need to use an additional .export statement, this is implied by .destructor. It may have an optional priority that is separated by a comma. If no priority is given, the default priority of 7 is used. Be careful when assigning priorities to your own module destructors so they won't interfere with the ones in the cc65 library.

Example:

        .destructor     ModuleDone
        .destructor     ModDone, 16
  

See the .CONDES and .CONSTRUCTOR commands and the separate section Module constructors/destructors explaining the feature in more detail.

6.23 .DWORD

Define dword sized data (4 bytes) Must be followed by a sequence of expressions.

Example:

        .dword  $12344512, $12FA489
  

6.24 .ELSE

Conditional assembly: Reverse the current condition.

6.25 .ELSEIF

Conditional assembly: Reverse current condition and test a new one.

6.26 .END

Forced end of assembly. Assembly stops at this point, even if the command is read from an include file.

6.27 .ENDIF

Conditional assembly: Close a .IF... or .ELSE branch.

6.28 .ENDMAC, .ENDMACRO

End of macro definition (see section Macros).

6.29 .ENDPROC

End of local lexical level (see .PROC).

6.30 .ENDREP, .ENDREPEAT

End a .REPEAT block.

6.31 .ERROR

Force an assembly error. The assembler will output an error message preceeded by "User error" and will not produce an object file.

This command may be used to check for initial conditions that must be set before assembling a source file.

Example:

        .if     foo = 1
        ...
        .elseif bar = 1
        ...
        .else
        .error  "Must define foo or bar!"
        .endif
  

See also the .WARNING and .OUT directives.

6.32 .EXITMAC, .EXITMACRO

Abort a macro expansion immidiately. This command is often useful in recursive macros. See separate section Macros.

6.33 .EXPORT

Make symbols accessible from other modules. Must be followed by a comma separated list of symbols to export.

Example:

        .export foo, bar
  

See: .EXPORTZP

6.34 .EXPORTZP

Make symbols accessible from other modules. Must be followed by a comma separated list of symbols to export. The exported symbols are explicitly marked as zero page symols.

Example:

        .exportzp  foo, bar
  

See: .EXPORT

6.35 .FARADDR

Define far (24 bit) address data. The command must be followed by a sequence of (not necessarily constant) expressions.

Example:

        .faraddr        DrawCircle, DrawRectangle, DrawHexagon
  

See: .ADDR

6.36 .FEATURE

This directive may be used to enable one or more compatibility features of the assembler. While the use of .FEATURE should be avoided when possible, it may be useful when porting sources written for other assemblers. There is no way to switch a feature off, once you have enabled it, so using

        .FEATURE        xxx
  

will enable the feature until end of assembly is reached.

The following features are available:

dollar_is_pc

The dollar sign may be used as an alias for the star (`*'), which gives the value of the current PC in expressions. Note: Assignment to the pseudo variable is not allowed.

labels_without_colons

Allow labels without a trailing colon. These labels are only accepted, if they start at the beginning of a line (no leading white space).

loose_string_term

Accept single quotes as well as double quotes as terminators for string constants.

loose_char_term

Accept single quotes as well as double quotes as terminators for char constants.

at_in_identifiers

Accept the at character (`@') as a valid character in identifiers. The at character is not allowed to start an identifier, even with this feature enabled.

dollar_in_identifiers

Accept the dollar sign (`$') as a valid character in identifiers. The at character is not allowed to start an identifier, even with this feature enabled.

pc_assignment

Allow assignments to the PC symbol (`*' or `$' if dollar_is_pc is enabled). Such an assignment is handled identical to the .ORG command (which is usually not needed, so just removing the lines with the assignments may also be an option when porting code written for older assemblers).

It is also possible to specify features on the command line using the --feature command line option. This is useful when translating sources written for older assemblers, when you don't want to change the source code.

As an example, to translate sources written for Andre Fachats xa65 assembler, the features

        labels_without_colons, pc_assignment, loose_char_term
  

may be helpful. They do not make ca65 completely compatible, so you may not be able to translate the sources without changes, even when enabling these features. However, I have found several sources that translate without problems when enabling these features on the command line.

6.37 .FILEOPT, .FOPT

Insert an option string into the object file. There are two forms of this command, one specifies the option by a keyword, the second specifies it as a number. Since usage of the second one needs knowledge of the internal encoding, its use is not recommended and I will only describe the first form here.

The command is followed by one of the keywords

        author
        comment
        compiler
  

a comma and a string. The option is written into the object file together with the string value. This is currently unidirectional and there is no way to actually use these options once they are in the object file.

Examples:

        .fileopt        comment, "Code stolen from my brother"
        .fileopt        compiler, "BASIC 2.0"
        .fopt           author, "J. R. User"
  

6.38 .GLOBAL

Declare symbols as global. Must be followed by a comma separated list of symbols to declare. Symbols from the list, that are defined somewhere in the source, are exported, all others are imported. Additional .IMPORT or .EXPORT commands for the same symbol are allowed.

Example:

        .global foo, bar
  

6.39 .GLOBALZP

Declare symbols as global. Must be followed by a comma separated list of symbols to declare. Symbols from the list, that are defined somewhere in the source, are exported, all others are imported. Additional .IMPORTZP or .EXPORTZP commands for the same symbol are allowed. The symbols in the list are explicitly marked as zero page symols.

Example:

        .globalzp foo, bar
  

6.40 .I16

Valid only in 65816 mode. Switch the index registers to 16 bit.

Note: This command will not emit any code, it will tell the assembler to create 16 bit operands for immediate operands.

See also the .I8 and .SMART commands.

6.41 .I8

Valid only in 65816 mode. Switch the index registers to 8 bit.

Note: This command will not emit any code, it will tell the assembler to create 8 bit operands for immediate operands.

See also the .I16 and .SMART commands.

6.42 .IF

Conditional assembly: Evalute an expression and switch assembler output on or off depending on the expression. The expression must be a constant expression, that is, all operands must be defined.

A expression value of zero evaluates to FALSE, any other value evaluates to TRUE.

6.43 .IFBLANK

Conditional assembly: Check if there are any remaining tokens in this line, and evaluate to FALSE if this is the case, and to TRUE otherwise. If the condition is not true, further lines are not assembled until an .ESLE, .ELSEIF or .ENDIF directive.

This command is often used to check if a macro parameter was given. Since an empty macro parameter will evaluate to nothing, the condition will evaluate to FALSE if an empty parameter was given.

Example:

        .macro     arg1, arg2
        .ifblank   arg2
                   lda     #arg1
        .else
                   lda     #arg2
        .endif
        .endmacro
  

See also: .BLANK

6.44 .IFCONST

Conditional assembly: Evaluate an expression and switch assembler output on or off depending on the constness of the expression.

A const expression evaluates to to TRUE, a non const expression (one containing an imported or currently undefined symbol) evaluates to FALSE.

See also: .CONST

6.45 .IFDEF

Conditional assembly: Check if a symbol is defined. Must be followed by a symbol name. The condition is true if the the given symbol is already defined, and false otherwise.

See also: .DEFINED

6.46 .IFNBLANK

Conditional assembly: Check if there are any remaining tokens in this line, and evaluate to TRUE if this is the case, and to FALSE otherwise. If the condition is not true, further lines are not assembled until an .ELSE, .ELSEIF or .ENDIF directive.

This command is often used to check if a macro parameter was given. Since an empty macro parameter will evaluate to nothing, the condition will evaluate to FALSE if an empty parameter was given.

Example:

        .macro     arg1, arg2
                   lda     #arg1
        .ifnblank  arg2
                   lda     #arg2
        .endif
        .endmacro
  

See also: .BLANK

6.47 .IFNDEF

Conditional assembly: Check if a symbol is defined. Must be followed by a symbol name. The condition is true if the the given symbol is not defined, and false otherwise.

See also: .DEFINED

6.48 .IFNREF

Conditional assembly: Check if a symbol is referenced. Must be followed by a symbol name. The condition is true if if the the given symbol was not referenced before, and false otherwise.

See also: .REFERENCED

6.49 .IFP02

Conditional assembly: Check if the assembler is currently in 6502 mode (see .P02 command).

6.50 .IFP816

Conditional assembly: Check if the assembler is currently in 65816 mode (see .P816 command).

6.51 .IFPC02

Conditional assembly: Check if the assembler is currently in 65C02 mode (see .PC02 command).

6.52 .IFREF

Conditional assembly: Check if a symbol is referenced. Must be followed by a symbol name. The condition is true if if the the given symbol was referenced before, and false otherwise.

This command may be used to build subroutine libraries in include files (you may use separate object modules for this purpose too).

Example:

        .ifref  ToHex                   ; If someone used this subroutine
        ToHex:  tay                     ; Define subroutine
                lda     HexTab,y
                rts
        .endif
  

See also: .REFERENCED

6.53 .IMPORT

Import a symbol from another module. The command is followed by a comma separated list of symbols to import.

Example:

        .import foo, bar
  

See: .IMPORTZP

6.54 .IMPORTZP

Import a symbol from another module. The command is followed by a comma separated list of symbols to import. The symbols are explicitly imported as zero page symbols (that is, symbols with values in byte range).

Example:

        .includezp  foo, bar
  

See: .IMPORT

6.55 .INCBIN

Include a file as binary data. The command expects a string argument that is the name of a file to include literally in the current segment.

Example:

        .incbin         "sprites.dat"
  

6.56 .INCLUDE

Include another file. Include files may be nested up to a depth of 16.

Example:

        .include        "subs.inc"
  

6.57 .LEFT

Builtin function. Extracts the left part of a given token list.

Syntax:

        .LEFT (<int expr>, <token list>)
  

The first integer expression gives the number of tokens to extract from the token list. The second argument is the token list itself.

Example:

To check in a macro if the given argument has a '#' as first token (immidiate addressing mode), use something like this:

        .macro  ldax    arg
                ...
                .if (.match (.left (1, arg), #))

                ; ldax called with immidiate operand
                ...

                .endif
                ...
        .endmacro
  

See also the .MID and .RIGHT builtin functions.

6.58 .LINECONT

Switch on or off line continuations using the backslash character before a newline. The option is off by default. Note: Line continuations do not work in a comment. A backslash at the end of a comment is treated as part of the comment and does not trigger line continuation. The command must be followed by a '+' or '-' character to switch the option on or off respectively.

Example:

        .linecont       +               ; Allow line continuations

        lda     \
                #$20                    ; This is legal now
  

6.59 .LIST

Enable output to the listing. The command must be followed by a boolean switch ("on", "off", "+" or "-") and will enable or disable listing output. The option has no effect if the listing is not enabled by the command line switch -l. If -l is used, an internal counter is set to 1. Lines are output to the listing file, if the counter is greater than zero, and suppressed if the counter is zero. Each use of .LIST will increment or decrement the counter.

Example:

        .list   on              ; Enable listing output
  

6.60 .LISTBYTES

Set, how many bytes are shown in the listing for one source line. The default is 12, so the listing will show only the first 12 bytes for any source line that generates more than 12 bytes of code or data. The directive needs an argument, which is either "unlimited", or an integer constant in the range 4..255.

Examples:

        .listbytes      unlimited       ; List all bytes
        .listbytes      12              ; List the first 12 bytes
        .incbin         "data.bin"      ; Include large binary file
  

6.61 .LOCAL

This command may only be used inside a macro definition. It declares a list of identifiers as local to the macro expansion.

A problem when using macros are labels: Since they don't change their name, you get a "duplicate symbol" error if the macro is expanded the second time. Labels declared with .LOCAL have their name mapped to an internal unique name (___ABCD__) with each macro invocation.

Some other assemblers start a new lexical block inside a macro expansion. This has some drawbacks however, since that will not allow any symbol to be visible outside a macro, a feature that is sometimes useful. The .LOCAL command is in my eyes a better way to address the problem.

You get an error when using .LOCAL outside a macro.

6.62 .LOCALCHAR

Defines the character that start "cheap" local labels. You may use one of '@' and '?' as start character. The default is '@'.

Cheap local labels are labels that are visible only between two non cheap labels. This way you can reuse identifiers like "loop" without using explicit lexical nesting.

Example:

        .localchar      '?'

        Clear:  lda     #$00            ; Global label
        ?Loop:  sta     Mem,y           ; Local label
                dey
                bne     ?Loop           ; Ok
                rts
        Sub:    ...                     ; New global label
                bne     ?Loop           ; ERROR: Unknown identifier!
  

6.63 .MACPACK

Insert a predefined macro package. The command is followed by an identifier specifying the macro package to insert. Available macro packages are:

        generic         Defines generic macros like add and sub.
        longbranch      Defines conditional long jump macros.
  

Including a macro package twice, or including a macro package that redefines already existing macros will lead to an error.

Example:

        .macpack        longbranch      ; Include macro package

                cmp     #$20            ; Set condition codes
                jne     Label           ; Jump long on condition
  

Macro packages are explained in more detail in section Macro packages).

6.64 .MAC, .MACRO

Start a classic macro definition. The command is followed by an identifier (the macro name) and optionally by a comma separated list of identifiers that are macro parameters.

See section Macros).

6.65 .MATCH

Builtin function. Matches two token lists against each other. This is most useful within macros, since macros are not stored as strings, but as lists of tokens.

The syntax is

        .MATCH(<token list #1>, <token list #2>)
  

Both token list may contain arbitrary tokens with the exception of the terminator token (comma resp. right parenthesis) and

Often a macro parameter is used for any of the token lists.

Please note that the function does only compare tokens, not token attributes. So any number is equal to any other number, regardless of the actual value. The same is true for strings. If you need to compare tokens and token attributes, use the .XMATCH function.

Example:

Assume the macro ASR, that will shift right the accumulator by one, while honoring the sign bit. The builtin processor instructions will allow an optional "A" for accu addressing for instructions like ROL and ROR. We will use the .MATCH function to check for this and print and error for invalid calls.

        .macro  asr     arg

                .if (.not .blank(arg)) .and (.not .match (arg, a))
                .error "Syntax error"
                .endif

                cmp     #$80            ; Bit 7 into carry
                lsr     a               ; Shit carry into bit 7

        .endmacro
  

The macro will only accept no arguments, or one argument that must be the reserved keyword "A".

See: .XMATCH

6.66 .MID

Builtin function. Takes a starting index, a count and a token list as arguments. Will return part of the token list.

Syntax:

        .MID (<int expr>, <int expr>, <token list>)
  

The first integer expression gives the starting token in the list (the first token has index 0). The second integer expression gives the number of tokens to extract from the token list. The third argument is the token list itself.

Example:

To check in a macro if the given argument has a '#' as first token (immidiate addressing mode), use something like this:

        .macro  ldax    arg
                ...
                .if (.match (.mid (0, 1, arg), #))

                ; ldax called with immidiate operand
                ...

                .endif
                ...
        .endmacro
  

See also the .LEFT and .RIGHT builtin functions.

6.67 .ORG

Start a section of absolute code. The command is followed by a constant expression that gives the new PC counter location for which the code is assembled. Use .RELOC to switch back to relocatable code.

Please note that you do not need this command in most cases. Placing code at a specific address is the job of the linker, not the assembler, so there is usually no reason to assemble code to a specific address.

You may not switch segments while inside a section of absolute code.

Example:

        .org    $7FF            ; Emit code starting at $7FF
  

6.68 .OUT

Output a string to the console without producing an error. This command is similiar to .ERROR, however, it does not force an assembler error that prevents the creation of an object file.

Example:

        .out    "This code was written by the codebuster(tm)"
  

See also the .WARNING and .ERROR directives.

6.69 .P02

Enable the 6502 instruction set, disable 65C02 and 65816 instructions. This is the default if not overridden by the --cpu command line option.

See: .PC02 and .P816

6.70 .P816

Enable the 65816 instruction set. This is a superset of the 65C02 and 6502 instruction sets.

See: .P02 and .PC02

6.71 .PAGELEN, .PAGELENGTH

Set the page length for the listing. Must be followed by an integer constant. The value may be "unlimited", or in the range 32 to 127. The statement has no effect if no listing is generated. The default value is -1 (unlimited) but may be overridden by the --pagelength command line option. Beware: Since ca65 is a one pass assembler, the listing is generated after assembly is complete, you cannot use multiple line lengths with one source. Instead, the value set with the last .PAGELENGTH is used.

Examples:

        .pagelength     66              ; Use 66 lines per listing page

        .pagelength     unlimited       ; Unlimited page length
  

6.72 .PARAMCOUNT

This builtin pseudo variable is only available in macros. It is replaced by the actual number of parameters that were given in the macro invocation.

Example:

        .macro  foo     arg1, arg2, arg3
        .if     .paramcount <> 3
        .error  "Too few parameters for macro foo"
        .endif
        ...
        .endmacro
  

See section Macros.

6.73 .PC02

Enable the 65C02 instructions set. This instruction set includes all 6502 instructions.

See: .P02 and .P816

6.74 .PROC

Start a nested lexical level. All new symbols from now on are in the local lexical level and are not accessible from outside. Symbols defined outside this local level may be accessed as long as their names are not used for new symbols inside the level. Symbols names in other lexical levels do not clash, so you may use the same names for identifiers. The lexical level ends when the .ENDPROC command is read. Lexical levels may be nested up to a depth of 16.

The command may be followed by an identifier, in this case the identifier is declared in the outer level as a label having the value of the program counter at the start of the lexical level.

Note: Macro names are always in the global level and in a separate name space. There is no special reason for this, it's just that I've never had any need for local macro definitions.

Example:

        .proc   Clear           ; Define Clear subroutine, start new level
                lda     #$00
        L1:     sta     Mem,y   ; L1 is local and does not cause a
                                ; duplicate symbol error if used in other
                                ; places
                dey
                bne     L1      ; Reference local symbol
                rts
        .endproc                ; Leave lexical level
  

See: .ENDPROC

6.75 .REF, .REFERENCED

Builtin function. The function expects an identifier as argument in braces. The argument is evaluated, and the function yields "true" if the identifier is a symbol that has already been referenced somewhere in the source file up to the current position. Otherwise the function yields false. As an example, the .IFREF statement may be replaced by

        .if     .referenced(a)
  

See: .DEFINED

6.76 .REPEAT

Repeat all commands between .REPEAT and .ENDREPEAT constant number of times. The command is followed by a constant expression that tells how many times the commands in the body should get repeated. Optionally, a comma and an identifier may be specified. If this identifier is found in the body of the repeat statement, it is replaced by the current repeat count (starting with zero for the first time the body is repeated).

.REPEAT statements may be nested. If you use the same repeat count identifier for a nested .REPEAT statement, the one from the inner level will be used, not the one from the outer level.

Example:

The following macro will emit a string that is "encrypted" in that all characters of the string are XORed by the value $55.

        .macro  Crypt   Arg
                .repeat .strlen(Arg), I
                .byte   .strat(Arg, I) .xor $55
                .endrep
        .endmacro
  

See: .ENDREPEAT

6.77 .RELOC

Switch back to relocatable mode. See the .ORG command.

6.78 .RES

Reserve storage. The command is followed by one or two constant expressions. The first one is mandatory and defines, how many bytes of storage should be defined. The second, optional expression must by a constant byte value that will be used as value of the data. If there is no fill value given, the linker will use the value defined in the linker configuration file (default: zero).

Example:

        ; Reserve 12 bytes of memory with value $AA
        .res    12, $AA
  

6.79 .RIGHT

Builtin function. Extracts the right part of a given token list.

Syntax:

        .RIGHT (<int expr>, <token list>)
  

The first integer expression gives the number of tokens to extract from the token list. The second argument is the token list itself.

See also the .LEFT and .MID builtin functions.

6.80 .RODATA

Switch to the RODATA segment. The name of the RODATA segment is always "RODATA", so this is a shortcut for

        .segment  "RODATA"
  

The RODATA segment is a segment that is used by the compiler for readonly data like string constants.

See also the .SEGMENT command.

6.81 .SEGMENT

Switch to another segment. Code and data is always emitted into a segment, that is, a named section of data. The default segment is "CODE". There may be up to 254 different segments per object file (and up to 65534 per executable). There are shortcut commands for the most common segments ("CODE", "DATA" and "BSS").

The command is followed by a string containing the segment name (there are some constraints for the name - as a rule of thumb use only those segment names that would also be valid identifiers). There may also be an optional attribute separated by a comma. Valid attributes are "zeropage" and "absolute".

When specifying a segment for the first time, "absolute" is the default. For all other uses, the attribute specified the first time is the default.

"absolute" means that this is a segment with absolute addressing. That is, the segment will reside somewhere in core memory outside the zero page. "zeropage" means the opposite: The segment will be placed in the zero page and direct (short) addressing is possible for data in this segment.

Beware: Only labels in a segment with the zeropage attribute are marked as reachable by short addressing. The `*' (PC counter) operator will work as in other segments and will create absolute variable values.

Example:

        .segment "ROM2"                 ; Switch to ROM2 segment
        .segment "ZP2", zeropage        ; New direct segment
        .segment "ZP2"                  ; Ok, will use last attribute
        .segment "ZP2", absolute        ; Error, redecl mismatch
  

See: .BSS, .CODE, .DATA and .RODATA

6.82 .SMART

Switch on or off smart mode. The command must be followed by a '+' or '-' character to switch the option on or off respectively. The default is off (that is, the assembler doesn't try to be smart), but this default may be changed by the -s switch on the command line.

In smart mode the assembler will track usage of the REP and SEP instructions in 65816 mode and update the operand sizes accordingly. If the operand of such an instruction cannot be evaluated by the assembler (for example, because the operand is an imported symbol), a warning is issued. Beware: Since the assembler cannot trace the execution flow this may lead to false results in some cases. If in doubt, use the .Inn and .Ann instructions to tell the assembler about the current settings.

Example:

        .smart                          ; Be smart
        .smart  -                       ; Stop being smart
  

6.83 .STRAT

Builtin function. The function accepts a string and an index as arguments and returns the value of the character at the given position as an integer value. The index is zero based.

Example:

        .macro  M       Arg
                ; Check if the argument string starts with '#'
                .if (.strat (Arg, 0) = '#')
                ...
                .endif
        .endmacro
  

6.84 .STRING

Builtin function. The function accepts an argument in braces and converts this argument into a string constant. The argument may be an identifier, or a constant numeric value.

Since you can use a string in the first place, the use of the function may not be obvious. However, it is useful in macros, or more complex setups.

Example:

        ; Emulate other assemblers:
        .macro  section name
                .segment        .string(name)
        .endmacro
  

6.85 .STRLEN

Builtin function. The function accepts a string argument in braces and eveluates to the length of the string.

Example:

The following macro encodes a string as a pascal style string with a leading length byte.

        .macro  PString Arg
                .byte   .strlen(Arg), Arg
        .endmacro
  

6.86 .TCOUNT

Builtin function. The function accepts a token list in braces. The function result is the number of tokens given as argument.

Example:

The ldax macro accepts the '#' token to denote immidiate addressing (as with the normal 6502 instructions). To translate it into two separate 8 bit load instructions, the '#' token has to get stripped from the argument:

        .macro  ldax    arg
                .if (.match (.mid (0, 1, arg), #))
                ; ldax called with immidiate operand
                lda     #<(.right (.tcount (arg)-1, arg))
                ldx     #>(.right (.tcount (arg)-1, arg))
                .else
                ...
                .endif
        .endmacro
  

6.87 .WARNING

Force an assembly warning. The assembler will output a warning message preceeded by "User warning". This warning will always be output, even if other warnings are disabled with the -W0 command line option.

This command may be used to output possible problems when assembling the source file.

Example:

        .macro  jne     target
                .local L1
                .ifndef target
                .warning "Forward jump in jne, cannot optimize!"
                beq     L1
                jmp     target
        L1:
                .else
                ...
                .endif
        .endmacro
  

See also the .ERROR and .OUT directives.

6.88 .WORD

Define word sized data. Must be followed by a sequence of (word ranged, but not necessarily constant) expressions.

Example:

        .word   $0D00, $AF13, _Clear
  

6.89 .XMATCH

Builtin function. Matches two token lists against each other. This is most useful within macros, since macros are not stored as strings, but as lists of tokens.

The syntax is

        .XMATCH(<token list #1>, <token list #2>)
  

Both token list may contain arbitrary tokens with the exception of the terminator token (comma resp. right parenthesis) and

Often a macro parameter is used for any of the token lists.

The function compares tokens and token values. If you need a function that just compares the type of tokens, have a look at the .MATCH function.

See: .MATCH

6.90 .ZEROPAGE

Switch to the ZEROPAGE segment and mark it as direct (zeropage) segment. The name of the ZEROPAGE segment is always "ZEROPAGE", so this is a shortcut for

        .segment  "ZEROPAGE", zeropage
  

Because of the "zeropage" attribute, labels declared in this segment are addressed using direct addressing mode if possible. You must instruct the linker to place this segment somewhere in the address range 0..$FF otherwise you will get errors.

See: .SEGMENT


Next Previous Contents