MAD-ASSEMBLER 1.9.5

Tebe/Madteam (01.01.2013)

translated poorly to English by Phaeron using Google Translate (01.26.2013)



INTRODUCTION

Preface

Mad-Assembler (MADS) is a 32 bit application, written in Delphi. Most applications are written in C, so to be different I used Delphi 7.0 ;).

MADS is oriented toward users of QA, XASM, and FA. The syntax is borrowed from QA, some macro commands and syntax come from XASM, and SpartaDOS X (SDX) syntax is inherited from FA. Additional characters are allowed in label names. Also added are support for the 65816 CPU, macros, procedures, splitting across virtual memory banks, and nested label names.

The number of labels and macros are limited only by the memory in your PC. Specifically, you can have 2147483647 (INTEGER) table entries. I'm sure this amount is sufficient. :)

Arithmetic operations are done with values of type INT64 (signed 64 bit), with the result represented with a value of type CARDINAL (unsigned 32 bit).

A line can be up to 65535 bytes, which is also the length limit of a label name. However, I have not had the opportunity to check labels as long as poems. :)

With the free compiler Free Pascal Compiler, it is possible to compile MADS for other platforms, such as Linux, Mac, OS/2, etc. For more information on how to build, see the chapter on Compilation.

If your system can run a version of Free Pascal, you can use MADS.

  • XASM home page: http://atariarea.krap.pl/x-asm/


    Compilation

    To compile MADS source, you can use the Delphi compiler, if Delphi 7.0 or later is installed.

    Another, more multi-platform way is to use the compiler package from the Free Pascal Compiler (FPC), which can be downloaded from: http://www.freepascal.org/

    Run the installer, and select the folder in which you installed FP. It is important not to use a directory name which contains '!' or other special characters, or else you will not be able to compile any files, and it should probably not be a standard path name. The command-line to start compilation could look like this (the case in the parameter names is important):
    fpc -Mdelphi -v mads.pas
    
    
  • -Mdelphi compile in Delphi mode
  • -v show all errors and warnings
  • -O3 enable code optimization
  • Compared to the Delphi compiler, FPC generates bigger code, but the speed of the compiled MADS is much faster, even by a few seconds. The included MADS.EXE is compiled using FPC.


    DIFFERENCES AND SIMILARITIES BETWEEN MADS AND XASM

    Similarities

  • the same syntax
  • the same exit codes
  • the same macro commands


    Differences and new behaviors

  • small additions to ORG, e.g.. 'ORG [[expression]]adres[,adres2]'
  • XASM does not like whitespace, MADS tolerates and accepts it in logical/arithmetic expressions and static/variable definitions
  • MADS allows expressions to be grouped with (), [], XASM only within []
  • MADS provides static and variable definitions of local, global, and temporary scope, XASM only global
  • MADS does not accept ORG a:adres or ORG f:adres
  • MADS encodes real numbers using the directive .FL .FL real, XASM by pseudo-command DTA R DTA R(real)
  • MADS has expanded support in the pseudo-command INS
  • MADS does not accept the addressing form 'lda (203),0'
  • MADS allows writing programs for SpartaDOS X
  • MADS permits writing relocatable code in a custom format
  • when encoding the value of a character, i.e.
      lda #' '
      lda #" "
    

    MADS distinguishes between single quotes (ATASCII coding) and double quotes (INTERNAL coding), whereas XASM treats both forms the same (ATASCII coding). Of course, the quote types are treated the same in DTA by MADS.

  • in indexed modes, a '+' or '-' sign increments or decrements the index register, e.g.
     lda $2000,x+    ->    lda $2000,x
                           inx
    
  • but if the '+' or '-' sign is used with a value, it change the value of the main operand instead (this only works with absolute indexed addressing):
     lda $2000,x+2   ->    lda $2002,x
    

    USAGE

    Assembler switches

    Syntax: mads source [switches]
    
    -b:address      Generate binary file at specific address
    -c              Label case sensitivity
    -d:label=value  Define a label
    -f              CPU command at first column
    -hc[:filename]  Header file for CC65
    -hm[:filename]  Header file for MADS
    -i:path         Additional include directories
    -l[:filename]   Generate listing
    -m:filename     File with macro definition
    -o:filename     Set object file name
    -p              Print fully qualified file names in listing and error messages
    -s              Silent mode
    -t[:filename]   List label table
    -x              Exclude unreferenced procedures
    -vu             Verify code inside unreferenced procedures
    -u              Warn of unused labels
    

    The default filenames are:

  • source.lst
  • source.obx
  • source.lab
  • source.h
  • source.hea
  • source.mac

    If no extension is specified for the source file, MADS will default to the extension .ASM.

    Switches can be given in any order, preceded by '/' or '-', and case does not matter. Also, switches can be combined:
    mads -lptd:label=value -d:label2=value source.asm
    mads -l  -p  -t  source
    mads source.asm  -lpt
    mads.exe "%1" -ltpi:"d:\!atari\macro\"
    mads -i:"c:\atari\macros\" -c source.asm  -lpt
    
    By default, after assembly MADS will save the output with the extension '.OBX', which can be changed with a batch file:
    mads "%1" -o:%~n1.xex
    
    More can be learned about the operators by doing "CALL /?" in Microsoft DOS.
  • -b:address
    Using the -b allows specification of a target address for a file that does not specify an address itself (the ORG psuedo-command specifies an assembly address).

    -c
    The -c switch causes label, variable, and constant names to be treated as case-sensitive. Assembler directives and 6502/65816 CPU instructions are always recognized regardless of case.

    -d:label=value
    Use the -d switch to define a new label in MADS memory from the command-line. This switch can be used multiple times in a single invocation of MADS, which is useful when assembling from a batch file (BAT).

    -f
    Use -f to allow CPU instructions to be recognized in the first column instead of just labels.

    -hc[:filename]
    The switch -hc saves a header file for the CC65 compiler. It also lets you specify a new name for the file. The default extension for the CC65 header file is *.H.

    -hm[:filename]
    The switch -hm saves a header file for MADS. It also lets you specify a new name for the file. The default extension for the MADS is *.HEA. Such a file contains information about the banks and values assigned to labels. Additionally, the labels are grouped by their types: CONSTANTS, VARIABLES, PROCEDURES.

    -i:path
    The -i switch is used to set the search path for ICL and INS. This switch can be use multiple times in the same command line to MADS, i.e.:
     -i:"c:\program files" -i:c:\temp -i:"d:\atari project"
    

    -l:filename
    The -l switch enables writing of a listing file. It also lets you specify a new name for the file.

    -m:filename
    The -m switch specifies a file with macro definitions, which MADS assembles before the main .ASM file.

    -o:filename
    The -o switch specifies a new name for the Atari DOS or SpartaDOS X executable file, which is created at the end of assembly.

    -p
    The -p switch is useful in conjunction with Code Genie. When an error occurs during assembly, MADS generated error messages will appear in the Output Bar of Code Genie:
    D:\!Delphi\Masm\test.asm (29) ERROR: Missing .PROC
    
    Now just double-click the message line, and the cursor in the editor will move to the line with the error.

    -s
    Use the -s switch to activate the so-called 'Silent mode', where no messages will be displayed, only errors (ERROR) and warnings (WARNING).

    -t[:filename]
    The -t switch writes a file with referenced label definitions. It also lets you specify an alternate name for the file.

    -x
    -x skips assembly of unreferenced procedures defined with the .PROC directive.

    -vu
    -vu enables verification of code inside procedures even if they are not emitted, usually used in conjunction with -x.

    -u
    -u lists unreferenced labels in the program.


    Exit codes

    3 = bad parameters, assembling not started
    2 = error occured
    0 = no errors
    
    Warnings do not change the value of the exit code.


    .LST file format

    The listing format is the same as XASM, except that the virtual memory bank is added before the address (if the bank is <>0). For more on virtual banks, see Memory banks.

         3
         4 = 01,9033		picture equ $9033
         5 = 01,00A0		scr1 equ $a0
         6
         7
         8 01,2000 EA		main nop
    

    .LAB file format

    As with XASM, the *.LAB file stores information about labels in the program.

    There are three columns:

  • The first column is the virtual bank number assigned to the label (if <>0).
  • The second column is the label value.
  • The third column is the label name.

    Virtual bank numbers with values >= $FFF9 have special meanings:
     $FFF9   label for parameter in procedure defined by .PROC
     $FFFA   label for array defined by .ARRAY
     $FFFB   label for structured data defined by the pseudo-command DTA STRUCT_LABEL
     $FFFC   label for SpartaDOS X symbol - SMB
     $FFFD   label for macro defined by .MACRO directive
     $FFFE   label for structure defined by .STRUCT directive
     $FFFF   label for procedure defined by .PROC directive
    

    Characters with special meanings in label names:

  • label defined in a macro (with two colons) ::
  • a dot ('.') separates the name of a scope (.MACRO, .PROC, .LOCAL, .STRUCT) from the field name in the scope

    The numeric value after :: is the number of the macro call.

    Mad-Assembler v1.4.2beta by TeBe/Madteam
    Label table:
    00	0400	@STACK_ADDRESS
    00	00FF	@STACK_POINTER
    00	2000	MAIN
    00	2019	LOOP
    00	201C	LOOP::1
    00	201C	LHEX
    00	0080	LHEX.HLP
    00	204C	LHEX.THEX
    00	205C	HEX
    00	205C	HEX.@GETPAR0.LOOP
    00	2079	HEX.@GETPAR1.LOOP
    

    .H file format

    I'm not sure if the file is OK, but Eru wanted something so here it is. :) It is useful for linking together ASM and CC65, or C ported to the Atari. Its contents can look like this (example file TEST.ASM):

    #ifndef _TEST_ASM_H_
    #define _TEST_ASM_H_
    
    #define TEST_CPU65816 0x200F
    #define TEST_CPU6502 0x2017
    #define TEST_TEXT6502 0x201F
    #define TEST_TEXT65816 0x2024
    
    #endif
    

    MACRO COMMANDS

     REQ, RNE, RPL, RMI, RCC, RCS, RVC, RVS
    
     SEQ, SNE, SPL, SMI, SCC, SCS, SVC, SVS
    
     JEQ, JNE, JPL, JMI, JCC, JCS, JVC, JVS
    
     ADD, SUB
    
     ADB, SBB
    
     ADW, SBW
    
     PHR, PLR
    
     INW, INL, IND, DEW, DEL, DED
    
     MVA, MVX, MVY
    
     MWA, MWX, MWY
    
     CPB, CPW, CPL, CPD
    
    The purpose of macro commands is to save time when writing programs and to shorten listings. Macro commands replace commonly used groups of instructions.

    REQ, RNE, RPL, RMI, RCC, RCS, RVC, RVS

    These macro commands are similar to the 6502 branch instructions BEQ, BNE, BPL, BMI, BCC, BCS, BVC, BVS, but branch to the previously assembled instruction ("repeat"):

       lda:cmp:req 20           ->      lda 20
                                -> wait cmp 20
                                ->      beq wait
    
       ldx #0                   ->      ldx #0 
       mva:rne $500,x $600,x+   -> loop lda $500,x
                                ->      sta $600,x
                                ->      inx
                                ->      bne loop
    

    SEQ, SNE, SPL, SMI, SCC, SCS, SVC, SVS

    These macro commands are similar to the 6502 branch instructions BEQ, BNE, BPL, BMI, BCC, BCS, BVC, BVS, but branch over the next assembled instruction ("skip"):

       lda #40         ->       lda #40
       add:sta  $80    ->       clc
       scc:inc  $81    ->       adc $80
                       ->       sta $80
                       ->       bcc skip
                       ->       inc $81
                       ->  skip
    

    JEQ, JNE, JPL, JMI, JCC, JCS, JVC, JVS

    These macro commands are similar to the 6502 branch instructions BEQ, BNE, BPL, BMI, BCC, BCS, BVC, BVS, but can target the entire 64KB address space ("jump"):

     jne dest   ->  beq *+4
                ->  jmp dest
    
    If the distance is short (in the range -128 ... +127), MADS uses a regular BEQ, BNE, BPL, BMI, BCC, BCS, BVC, or BVS branch instruction.

    ADD, SUB

    These macro commands add or subtract from the accumulator without including the carry flag.

      ADD -> CLC         SUB -> SEC
          -> ADC ...         -> SBC ...
    


    ADB, SBB

    These macro commands add or subtract a value from a byte location in memory and store it either back or to another location.

      ADB SRC #$40 -> LDA SRC       ADB A B C  -> LDA A
                   -> CLC                      -> CLC
                   -> ADC #$40                 -> ADC B
                   -> STA SRC                  -> STA C
    
      SBB SRC #$80 -> LDA SRC       SBB A B C  -> LDA A
                   -> SEC                      -> SEC
                   -> SBC #$80                 -> SBC B
                   -> STA SRC                  -> STA C
    


    ADW, SBW

    These macro commands add or subtract a value from a word location in memory and store it either back or to another location.

      ADW SRC #$40 -> CLC             ADW A B C  -> CLC
                   -> LDA SRC                    -> LDA A
                   -> ADC #$40                   -> ADC B
                   -> STA SRC                    -> STA C
                   -> SCC                        -> LDA A+1
                   -> INC SRC+1                  -> ADC B+1
                                                 -> STA C+1
    
      ADW SRC #$40 SRC -> CLC
                       -> LDA SRC
                       -> ADC #$40
                       -> STA SRC
                       -> LDA SRC+1
                       -> ADC #$00
                       -> STA SRC+1
                                                 
      SBW SRC #$4080 -> SEC           SBW A B C  -> SEC
                     -> LDA SRC                  -> LDA A
                     -> SBC <$4080               -> SBC B
                     -> STA SRC                  -> STA C
                     -> LDA SRC+1                -> LDA A+1
                     -> SBC >$4080               -> SBC B+1
                     -> STA SRC+1                -> STA C+1 
    


    PHR, PLR

    These macros are similar to the 6502 mnemonics PHA and PLA, but push or pop the A, X, and Y registers to and from the stack.

      PHR  -> PHA         PLR  -> PLA
           -> TXA              -> TAY
           -> PHA              -> PLA
           -> TYA              -> TAX
           -> PHA              -> PLA
    


    INW, INL, IND, DEW, DEL, DED

    The macro commands INW, INL, and IND increment 16-bit (word), 24-bit (long), and 32-bit (dword) memory locations.

    The macro commands DEW, DEL, and DED decrement 16-bit (word), 24-bit (long), and 32-bit (dword) memory locations. The accumulator is also changed after the decrement macro commands.
        inw dest  ->       inc dest    ->   inc dest
                  ->       bne skip    ->   sne
                  ->       inc dest+1  ->   inc dest+1
                  ->  skip             ->
    
        dew dest  ->       lda dest    ->   lda dest
                  ->       bne skip    ->   sne
                  ->       dec dest+1  ->   dec dest+1
                  ->  skip dec dest    ->   dec dest   
    


    MVA, MVX, MVY

    The macro commands MVA, MVX, MVY transfer bytes using the A, X, or Y registers, respectively. OPT R+ can potentially reduce the code size from these macros by removing redundant instructions.

        lda src    ->  mva src dst
        sta dst    ->
    
        ldy $10,x  ->  mvy $10,x $a0,x
        sty $a0,x  ->
    
        ldx #$10   ->  mvx #$10 dst
        stx dst    ->
    


    MWA, MWX, MWY

    The macro commands MWA, MWX, MWY transfer words using the A, X, or Y registers, respectively. OPT R+ can potentially reduce the code size from these macros by removing redundant instructions.

        ldx <adr    ->  mwx #adr dst
        stx dst     ->
        ldx >adr    ->
        stx dst+1   ->
    
        mwa #0 $80  ->  lda #0           mwy #$3040 $80  ->  ldy <$3040
                    ->  sta $80                          ->  sty $80
                    ->  sta $81                          ->  ldy >$3040
                                                         ->  sty $81
    
        mwa ($80),y $a000,x  ->  lda ($80),y
                             ->  sta $a000,x
                             ->  iny
                             ->  lda ($80),y
                             ->  sta $a001,x
    


    CPB, CPW, CPL, CPD

    The macro commands CPB, CPW, CPL, and CPD perform comparison of byte, word (16-bit), long (24-bit), and dword (32-bit) values, respectively.

     cpw temp #$4080
     bcc skip
    
     cpd v0 v1
     beq skip
    


    PSEUDOCOMMANDS

     IFT [.IF] expression
     ELS [.ELSE]
     ELI [.ELSEIF] expression
     EIF [.ENDIF]
     
     ERT ERT 'string'["string"] | ERT expression
    
     label EQU expression
     label  =  expression
    
     label SET expression
     
     label EXT type
    
     OPT [bcfhlmorst][+-]
     ORG [[expression]]address[,address2]
     INS 'filename'["filename"][*][+-value][,+-ofset[,length]]
     ICL 'filename'["filename"]
     DTA [abfghltv](value1,value2...)[(value1,value2...)]
     DTA [cd]'string'["string"]
     RUN expression
     INI expression
     END [.EN]
    
     SIN (centre,amp,size[,first,last])
     RND (min,max,length)
    
     :repeat
    
     BLK N[one] X
     BLK D[os] X
     BLK S[parta] X
     BLK R[eloc] M[ain]|E[xtended]
     BLK E[mpty] X M[ain]|E[xtended]
     BLK U[pdate] S[ymbols]
     BLK U[pdate] E[xternal]
     BLK U[pdate] A[dress]
     BLK U[pdate] N[ew] X 'string'
    
     label SMB 'string'
    
     NMB
     RMB
     LMB #expression
    

    These are mostly the same, although there are some differences with quoted strings. Both ' ' and " " are treated the same except in operands, where '' gives the ATASCII code of a character, and "" gives the INTERNAL code.


    BLK

     BLK N[one] X                    - set program counter to X without adding a header block
    
     BLK D[os] X                     - DOS block with header $FFFF or without header when
                                       the program counter is already set to X
    
     BLK S[parta] X                  - fixed address block with header $FFFA, set program counter to X
    
     BLK R[eloc] M[ain]|E[xtended]   - relocatable block in MAIN or EXTENDED memory
    
     BLK E[mpty] X M[ain]|E[xtended] - relocatable block reserving MAIN or EXTENDED memory
                                       NOTE: the program counter is immediately raised by X bytes
    
     BLK U[pdate] S[ymbols]          - update block for updating previous SPARTA or RELOC blocks with the
                                       addresses of SDX symbols
    
     BLK U[pdate] E[xternal]         - update block for updating addresses of external labels ($FFEE header)
                                       NOTE: does not apply to SpartaDOS X, as this is a MADS extension
    
     BLK U[pdate] A[dress]           - update block for addresses in RELOC blocks
    
     BLK U[pdate] N[ew] X 'string'   - block declaring a new symbol 'string' in a RELOC block
                                       with address X. If the symbol name is prefixed with @,
                                       the address is in main memory and can be invoked by
                                       command.com
    
    For more information on SpartaDOS X blocks, see
    SpartaDOS X file format and Programming SpartaDOS X.


    label SET expression

    The pseudo-command SET redefines a label, with similar effect as temporary labels that begin with '?':

    temp set 12
    
         lda #temp
    
    temp set 23
    
         lda #temp
    

    label SMB 'string'

    Declares a label as a SDX symbol. The symbol name can have a maximum of 8 characters. BLK UPDATE SYMBOLS will direct the assembler to generate the correct update block for symbols. Example:

           pf  smb 'PRINTF'
               jsr pf
               ...
    
    will make the SDX system insert the correct address into the JSR instruction.

    Note: This statement is not transitive, so the following example will cause errors at compile time:
           cm  smb 'COMTAB'
           wp  equ cm-1       (błąd !)
    
               sta wp
    
    Use this instead:
           cm  smb 'COMTAB'
    
               sta cm-1       (ok !)
    

    Note: use labels for all symbols and declare before usage for correct operation!


    :repeat

    Example: 
               :4 asl @
               :2 dta a(*)
               :256 dta #/8
    
    ladr :4 dta l(line:1)
    hadr :4 dta h(line:1)           
    
    A ':' specifies the number of times to repeat the line (in the case of a macro, this specifies a macro parameter by number if it is in decimal). The repeat count should be in the range <0..2147483647>. When repeating a line with ':repeat', it is possible to use the loop counter in the repeated line using a hash sign ('#') or the parameter :1.

    When attempting to use the character ':' to repeat lines in a macro:
    .macro test
     :2 lsr @
    .endm
    
    The ':' prefixed number in this case is interpreted as the second macro parameter. To prevent this interpretation by MADS, add something after the ':' that does nothing, such as the plus sign ('+').
    .macro test
     :+2 lsr @
    .endm
    

    Now, the ':' is correctly interpreted as :repeat.


    OPT

    The OPT pseudo-command allows options to be enabled or disabled during assembly.
     b+  enable bank sensitivity
     b-  disable bank sensitivity                                         (default)
     c+  use 65816 instruction set (16bit)
     c-  use 6502 instruction set (8bit)                                  (default)
     f+  emit file as a single block (useful for cartridges)
     f-  emit file as multiple blocks                                     (default)
     h+  write DOS executable file headers                                (default)
     h-  omit DOS executable file headers
     l+  enable writing to listing file (LST)
     l-  disable writing to listing file (LST)                            (default)
     m+  expand macros in listing
     m-  include only macro invocation in listing                         (default)
     o+  enable writing to object file (OBX)                              (default)
     o-  disable writing to object file (OBX)
     r+  enable optimization for MVA, MVX, MVY, MWA, MWX, MWY
     r-  disable optimization for MVA, MVX, MVY, MWA, MWX, MWY            (default)
     s+  print listing to screen
     s-  do not print listing to screen                                   (default)
     t+  enable SEP/REP tracking (65816 CPU)
     t-  disable SEP/REP tracking (65816 CPU)                             (default)
     ?+  labels beginning with '?' are local (MAE style)
     ?-  labels beginning with '?' are temporary                          (default)
    
    Example:
     
     OPT c+ c  - l  + s +
     OPT h-
     OPT o +
    

    All options controlled by OPT can be used anywhere in the listing, e.g. if it is turned on at line 12 and off at line 20 then the listing will only contain lines 12 through 20.

    OPT C+ is required to use 65816 addressing modes.

    If you use CodeGenie and 'OPT S+', the listing file is unnecessary as the listing is printed in the lower pane (Output Bar).


    ORG

    The ORG pseudo-command sets a new assembly address and therefore a new position for data in RAM.
     adr                 assembles to ADR, setting the address in the header to ADR
     adr,adr2            assembles to ADR, setting the address in the header to ADR2
     [b($ff,$fe)]        write $FFFE header (will generate 2 bytes)
     [$ff,$fe],adr       write $FFFE header, setting the address in the header to ADR
     [$d0,$fe],adr,adr2  write $D0FE header, assemble at address ADR, set the address in the header to ADR2
     [a($FFFA)],adr      write SpartaDOS $FAFF header, set address in the header to ADR
    
    Example:
    
     opt h-
     ORG [a($ffff),d'atari',c'ble',20,30,40],adr,adr2
    

    Brackets [ ] are used to write a new header, which can be any length. Other values following closing ']', separated by a comma, are the assembly address and the address in the header.

    Here is an example of a file with a single header, assembled at address $2000, with valid block start and end addresses in the header.
    Example:
    
     opt h-f+
     ORG [a(start), a(over-1)],$2000
    
    start
     nop
     .ds 128
     nop
    over
    

    INS 'filename'["filename"][*][+-value][,+-ofset[,length]]

    The INS pseudo-command allows inclusion of an external binary file. The included file does not have to be in the same directory as the main file being assembled. Search paths for the file can be configurated using the /i switch (see assembly switches).

    Additionally, you can perform the following operations on the binary data:
    *          invert bytes
    +-VALUE    increase or decrease each byte by the value of the expression VALUE
    
    +OFSET     skip OFSET bytes at the beginning of the file     (seek to OFSET)
    -OFSET     read OFSET bytes at the end of the file           (seek to FileLength-OFSET)
    
    LENGTH     read LENGTH bytes from the file
    
    If the LENGTH value is not specified, the default behavior is to read to the end.


    ICL 'filename'["filename"]

    The pseudo-command ICL includes an additional source file in the assembly process. The attached file does not have to be in the same directory as the main assembly file. Additional paths are added to the MADS search path using the /i switch (see assembly switches).


    DTA

    The pseudo-command DTA defines typed data. If the type is not specified, byte data is assumed (b).
       b   byte data (8-bit)
       a   word data (16-bit)
       v   relocatable WORD data (16-bit)
       l   byte data (8-bit)
       h   byte data (8-bit)
       t   long data (24-bit)
       e   long data (24-bit)
       f   doubleword data (32-bit)
       g   doubleword data (32-bit) in reversed byte order (big-endian)
       c   ATASCII string, delimited by '' or ""; * at the end encodes inverse
           video, e.g. dta c'abecadlo'*
       d   INTERNAL string, delimited by '' or ""; * at the end encodes inverse
           video, e.g. dta d'abecadlo'*
    
    Example:
    
      dta 1 , 2, 4
      dta a ($2320 ,$4444)
      dta d'sasasa', 4,a ( 200 ), h($4000)
      dta  c  'file' , $9b
      dta c'invers'*
    


    SIN(centre,amp,size[,first,last])

    where: 
    
    centre     is a number which is added to every sine value 
    amp        is the sine amplitude 
    size       is the sine period 
    first,last define range of values in the table. They are optional.
               Default are 0,size-1. 
    
    Example: dta a(sin(0,1000,256,0,63))
             defines table of 64 words representing a quarter of sine with
             amplitude of 1000.
    

    RND(min,max,length)

    This pseudo-command generates LENGTH pseudorandom values in the range <MIN..MAX>.
    Example: dta b(rnd(0,33,256))
    

    IFT, ELS, ELI, EIF

     IFT [.IF] expression
     ELS [.ELSE]
     ELI [.ELSEIF] expression
     EIF [.ENDIF]
    

    These pseudo-commands and directives conditionally include lines based on the value of an expression.


    DIRECTIVES

     .ALIGN N[,fill]
     
     .ARRAY label index type [= default_value]
     .ENDA, [.AEND]
    
     .DEF label [= expression]
    
     .ENUM label
     .ENDE, [.EEND]
    
     .ERROR [ERT] 'string'["string"] lub .ERROR [ERT] expression
    
     .EXTRN label [,label2,...] type
    
     .IF [IFT] expression
     .ELSE [ELS]
     .ELSEIF [ELI] expression
     .ENDIF [EIF]
    
     .IFDEF label
     .IFNDEF label
    
     .LOCAL label
     .ENDL, [.LEND]
    
     .LINK 'filename'
     
     .MACRO label
     .ENDM, [.MEND]
     :[%%]parameter
     .EXITM [.EXIT]
    
     .NOWARN
    
     .PRINT [.ECHO] 'string1','string2'...,value1,value2,...
    
     .PAGES [expression]
     .ENDPG, [.PGEND] 
    
     .PUBLIC, [.GLOBAL], [.GLOBL] label [,label2,...]
    
     .PROC label
     .ENDP, [.PEND]
     .REG, .VAR
    
     .REPT expression [,parameter1, parameter2, ...]
     .ENDR, [.REND]
     .R
    
     .RELOC [.BYTE|.WORD]
    
     .STRUCT label
     .ENDS, [.SEND]
    
     .SYMBOL label
     
     .SEGDEF label address length [bank]
     .SEGMENT label
     .ENDSEG
     
     .USING, [.USE] proc_name, local_name
    
     .VAR var1[=value],var2[=value]... (.BYTE|.WORD|.LONG|.DWORD)
     .ZPVAR var1, var2... (.BYTE|.WORD|.LONG|.DWORD)
    
     .END
    
     .EN
    
     .BYTE
     .WORD
     .LONG
     .DWORD
    
     .OR
     .AND
     .XOR
     .NOT
    
     .LO (expression)
     .HI (expression)
    
     .DB
     .DW
     .DS expression
    
     .BY [+byte] bytes and/or ASCII
     .WO words
     .HE hex bytes
     .SB [+byte] bytes and/or ASCII
     .CB [+byte] bytes and/or ASCII
     .FL floating point numbers
    
     .ADR label
     .LEN label
    
     .GET [index] 'filename'["filename"][*][+-value][,+-ofset[,length]]
     .PUT [index] = value
     .SAV [index] ['filename',] length
    

    .SYMBOL label

    The directive .SYMBOL is equivalent to the pseudo-command SMB except that the symbol name does not need to be specified, as it is implied to be label. A .SYMBOL directive can be placed anywhere within a relocatable SDX block (BLK RELOC), unlike SMB.

    Whenever there is a .SYMBOL directive, the following block update will be generated:

    BLK UPDATE NEW LABEL 'LABEL'
    
    More on the declaration of SDX symbols is found in the section
    Defining symbols with SMB.


    .ALIGN N [,fill]

    The directive .ALIGN aligns the assembly address to the value N, using FILL as the memory preset value for any needed fill. It is possible to align relocatable code provided that the FILL value is given.

    The defaults are: N=$0100, FILL=0.

    Example:
    
     .align
    
     .align $400
     
     .align $100,$ff
    

    .REPT expression [,parameter1, parameter2, ...]

    The directive REPT is the same as the
    :repeat syntax, except that a block is repeated instead of a single line. The beginning of the block is defined with the .REPT directive, which is followed by a repeat count in the range <0..2147483647> and then optional parameters. Unlike macro parameters, the parameters to .REPT are always calculated first and the result is substituted immediately (this feature can be used to define new labels). The parameters specified in the .REPT block are used like parameters to a .MACRO block. A .REPT block is ended using the .ENDR directive, before which there should be no label.

    Additionally, within a .REPT....ENDR block, the hash sign '#' (or directive .R) gives the current value of the loop counter (like for :repeat).
    Example:
    
     .rept 12, #*2, #*3        ; a .REPT block can be combined with :rept
     :+4 dta :1                ; :+4 to distinguish from repeat block parameter :4
     :+4 dta :2
     .endr
    
     .rept 9, #                ; define 9 labels label0..label8
    label:1 mva #0 $d012+#
     .endr
    

    .PAGES [expression]

    The directive .PAGES specifies that a piece of code delimited by a <.PAGES .. .ENDPG> block should fit within a number of memory pages (the default is 1). If the program code exceeds the given number of memory pages, the error Page error at ???? is generated.

    These directives can help when we want part of the program to be within one memory page, or when we write a program stored in an additional memory bank (64 pages of memory), such as:
    Example:
    
     org $4000
     
     .pages $40
      ...
      ...
     .endpg
    

    .SEGDEF label address length [attrib] [bank]
    .SEGMENT label
    .ENDSEG

    The directive .SEGDEF defines a new segment LABEL at address ADDRESS and with length LENGTH. Read/write attributes can be assigned to the segment (R-read, W-write, RW-read/write), as well as a virtual bank number BANK (default=0).

    The .SEGMENT directive begins writing of code and data to the code segment LABEL. Exceeding the preset length of the segment produces error message Segment LABEL error at ADDRESS.

    The directive .ENDSEG ends writing to the current segment and returns to the main program block.

    Example:
    
    	.segdef sdata adr0 $100
    	.segdef test  adr1 $40
    
    	org $2000
    
    	nop
    
    	.cb 'ALA'
    
    	.segment sdata
    
    	nop
    	
    	.endseg
    
    	lda #0
    
    	.segment test
    	ldx #0
    	clc
    
    	dta c'ATARI'
    
    	.endseg
    
    adr0	.ds $100
    adr1	.ds $40 
    

    .END

    The directive .END can be used interchangeably with the directives .ENDP, .ENDM, .ENDS, .ENDA, .ENDL, .ENDR, .ENDPG, .ENDW, and .ENDT.


    .VAR var1[=value1],var2[=value2]... (.BYTE|.WORD|.LONG|.DWORD) [=address]

    The directive .VAR is used to declare and initialize variables in the main program block and in .PROC and .LOCAL blocks. MADS does not use the information in these variables in further operations involving pseudo and macro commands. Acceptable types of variables are .BYTE, .WORD, .LONG, and .DWORD, multiples of those types, and types declared by .STRUCT and .ENUM.
    Example:
    
     .var a,b , c,d   .word          ; 4 variables of type .WORD
     .var a,b,f  :256 .byte          ; 3 variables each with a size of 256 bytes
     .var c=5,d=2,f=$123344 .dword   ; 3 .DWORD variables with values 5, 2, and $123344
    
     .var .byte i=1, j=3             ; 2 variables of type .BYTE with values 1, 3
    
     .var a,b,c,d .byte = $a000      ; 4 variables of type .BYTE with addresses $A000, $A001, $A002, $A003
     
     .var .byte a,b,c,d = $a0        ; 4 variables of type byte, with the last variable 'D' having address $A0
                                     ; !!! in this form it is not possible to determine the address of variables
    
      .proc name
      .var .word p1,p2,p3            ; declare three variable of type .WORD
      .endp
    
     .local
      .var a,b,c .byte
      lda a
      ldx b
      ldy c
     .endl
    
     .struct Point                   ; new structure of type POINT
     x .byte
     y .byte
     .ends
    
      .var a,b Point                 ; declare structured variables
      .var Point c,d                 ; equivalent to syntax 'label DTA POINT'
    
    Declared variables are physically allocated at the end of the block, as determined by the directives .ENDP, .ENDL, or .END. The exception is that in a .PROC block, variables declared with .VAR are always allocated in front of the .ENDP directive even if the .VAR statements are within nested .LOCAL blocks.


    .ZPVAR var1, var2... (.BYTE|.WORD|.LONG|.DWORD) [=address]

    The directive .ZPVAR is used to declare zero page variables in the main program block and in .PROC and .LOCAL blocks. Attempting to assign to or initialize a variable of this type will generate the warning message Uninitialized variable. MADS does not use the information in these variables in further operations involving pseudo and macro commands. Acceptable variable types are .BYTE, .WORD., .LONG, .DWORD, multiples of those types, and types declared by .STRUCT and .ENUM:
    Example:
    
     .zpvar a b c d  .word = $80    ; 4 variables of type .WORD starting at address $0080
     .zpvar i j .byte               ; two more byte variables starting at address $0080+8
    
     .zpvar .word a,b               ; 2 variables of type .WORD
                                    ; !!! in this form it is not possible to determine the addresses of the variables
    
     .struct Point                  ; declare new structure POINT
     x .byte
     y .byte
     .ends
    
      .zpvar a,b Point              ; declare structured variables
      .zpvar Point c,d              ; equivalent to syntax 'label DTA POINT'                                
    
    The zero-page variable will be assigned addresses only at the end of the block in which it was declared, at .ENDP, .ENDL, or .END. The exception is a .PROC block where variables declared with .ZPVAR are assigned at the .ENDP directive even if variables are declared within nested .LOCAL blocks.

    Using .ZPVAR with only an address will specify the first address to assign to the next variable (the default address is $0080).

    Example:
    
     .zpvar = $40                       
    

    The address is automatically incremented by MADS and the warning message Access violations at address $xxxx is generated if addresses are repeated. In the case of a zero page overflow, the error Value out of range is generated.


    .PRINT [.ECHO]

    Prints on screen parameter values or string expressions delimited by ' ' or " " quotes:

    Example:
    
     .print "End: ",*,'..',$8000-*
     .echo "End: ",*,'..',$8000-*
    

    (Editor's note: Values are printed out as hexadecimal with a $ prefix.)


    .ERROR [ERT] 'string'["string"] | .ERROR [ERT] expression

    The directive .ERROR and pseudo-command ERT are equivalent and stop assembly, displaying a message given as a parameter delimited by ' ' or " ". If the parameter is a boolean expression, then assembly will stop when the expression is true (with User error):
    Example:
    
     ert "halt"            ; ERROR: halt
     .error "halt"
    
     ert *>$7fff           ; ERROR: User error
     .error *>$7fff
    

    .BYTE, .WORD, .LONG, .DWORD

    These directives are used to determine the allowable types for parameters in a procedure declaration. They can also be used in place of the pseudo command DTA for data definition.
    Example:
    
    .proc test (.word tmp,a,b .byte value)
    
     .byte "atari",5,22
     .word 12,$FFFF
     .long $34518F
     .dword $11223344
    

    .DB

    Define data of type BYTE. Equivalent to the pseudo command DTA B or the .BYTE directive.


    .DW

    Define data of type WORD. Equivalent to the pseudo command DTA A or the .WORD directive.


    .DS expression

    This directive has been adapted from MAC'65 and reserves uninitialized memory. This is equivalent to the pseudo command ORG *+expression. The .DS directive cannot be used in relocatable code like ORG can.

    purpose: reserves space for data without initializing then space to any particular value(s).
    
    usage: [label] .DS expression
    
    Using ".DS expression" is exactly equivalent of using "ORG *+expression". That is, the label
    (if it is given) is set equal to the current value of the location counter. Then then value
    of the expression is added to then location counter.
    
    Example: BUFFERLEN .DS 1 ;reserve a single byte
             BUFFER   .DS 256  ;reserve 256 bytes
    

    .BY [+byte] bytes and/or ASCII

    Store byte values in memory. ASCII strings can be specified by enclosing the string in either single or double quotes.

    If the first character of the operand field is a '+', then the following byte will be used as a constant and added to all remaining bytes of the instruction.
    Example:
          .BY +$80 1 10 $10 'Hello' $9B
    
    will generate:
            81 8A 90 C8 E5 EC EC EF 1B
    
    Values in .BY statements may also be separated with commas for compatibility with other assemblers. Spaces are allowed since they are easier to type.


    .WO words

    Stores words in memory. Multiple words can be entered.

    Values in .WO statements may also be separated with commas for compatibility with other assemblers. Spaces are allowed since they are easier to type.


    .HE hex bytes

    Store hex bytes in memory. This is a convenient method to enter strings of hex bytes, since it does not require the use of the '$' character. The bytes are still separated by spaces however, which I feel makes a much more readable layout than the 'all run together' form of hex statement that some other assemblers use.

    Example: .HE 0 55 AA FF

    Values in .HE statements may also be separated with commas for compatibility with other assemblers. Spaces are allowed since they are easier to type.


    .SB [+byte] bytes and/or ASCII

    This is in the same format as the .BY pseudo-op, except that it will convert all bytes into ATASCII screen codes before storing them. The ATASCII conversion is done before any constant is added with the '+' modifier.

    Values in .SB statements may also be separated with commas for compatibility with other assemblers. Spaces are allowed since they are easier to type.


    .CB [+byte] bytes and/or ASCII

    This is in the same format as the .BY pseudo-op, except that the last character on the line will be EOR'ed with $80.

    Values in .CB statements may also be separated with commas for compatibility with other assemblers. Spaces are allowed since they are easier to type.


    .FL floating point numbers

    Stores 6-byte BCD floating point numbers for use with the OS FP ROM routines.

    Values in .FL statements may also be separated with commas for compatibility with other assemblers. Spaces are allowed since they are easier to type.


    .EN

    The directive .EN is equivalent to the pseudo command END and ends assembly.

    This is an optional pseudo-op to mark the end of assembly. It can be placed before the end of your source file to prevent a portion of it from being assembled.


    .ADR label

    The directive .ADR returns the address of LABEL before the assembly address is changed (you can put LABEL between parentheses or square brackets). For example:
     org $2000
    
    .proc tb,$1000
    tmp lda #0
    .endp
    
     lda .adr tb.tmp  ; = $2000
     lda tb.tmp       ; = $1000
    


    .LEN label

    The directive .LEN returns the length in bytes of a block declared with .PROC, .ARRAY, .LOCAL, or .STRUCT. The label is the name of the .PROC, .ARRAY, .LOCAL, or .STRUCT block (the label name can be within parentheses or square brackets):
    label .array [255] .dword
          .enda
    
          dta a(.len label)   ; = $400
    
    .proc wait
     lda:cmp:req 20
     rts
    .endp
    
     dta .len wait    ; = 7
    

    .DEF label [= expression]

    The directive .DEF is used to check for the presence of the LABEL definition or to define it. If the label is defined it returns 1 or TRUE, otherwise it returns 0 or FALSE. It is possible to put the name LABEL between parentheses or square brackets:
     ift .not(.def label)
     .def label
     eif
    
    This unary operator tests whether the following label has been defined yet, returning TRUE or FALSE as appropriate.

    CAUTION: Defining a label AFTER the use of a .DEF which references it can be dangerous, particularly if the .DEF is used in a .IF directive.


    .IFDEF label

    The directive .IFDEF is equivalent to .IF .DEF LABEL.
    Example:
    
    .ifdef label
           jsr proc1
    .else
           jsr proc2
    .endif
    

    .IFNDEF label

    The directive .IFNDEF is equivalent to .IF .NOT .DEF LABEL.
    Example:
    
    .ifndef label
          clc
    .else
          sec
    .endif
    
    In the following example, the .IFNDEF (.IF) block will be processed and the label defined only when the block is first encountered. If there are any errors associated with their definition, this will only be reported when a reference to one of them is attempted, resulting in the error Undeclared label LABEL_NAME.
     .ifndef label
     .def label
     lda #0               ; this will only be generated once and not be reassembled
     temp = 100           ; label TEMP is defined only once during assembly
     .endif
    

    .NOWARN

    The directive .NOWARN disables warning messages for the current line being assembled.
    Example:
    
    .nowarn .proc temp       ; warning not generated: 'Unreferenced procedure TEMP'
            .endp
    

    .USING, [.USE]

    The directive .USING (.USE) allows an additional scope to be specified for label lookup. .USING (.USE) is valid in the current namespace.
    Example:
    
    .local move
    
    tmp    lda #0
    hlp    sta $a000
    
    .local move2
    
    tmp2   ldx #0
    hlp2   stx $b000
    
    .endl
    
    .endl
    
    .local main
    
    .use move.move2
    
           lda tmp2
     
    .use move
    
           lda tmp
    
    .endl
    

    .GET [index] 'filename'... [.BYTE, .WORD, .LONG, .DWORD]

    This is equivalent to the pseudo command INS (similar syntax), except that the file is loaded into memory instead of included in assembly. This directive allows the specified file to be loaded into memory and for its bytes to be referred to as a one-dimensional array.

    Example:
    
     .get 'file'                    ; load the file into a MADS array
     .get [5] 'file'                ; load the file into an array starting at index 5
    
     .get 'file',0,3                ; load the file into an array of size 3
    
     lda #.get[7]                   ; load the value of element 7 of the file array
     adres = .get[2]+.get[3]<<8     ; use bytes 2 and 3 of the file array as an address
    
    With the help of the directives .GET, .PUT a module for Theta Music Composer (TMC) can be read and relocated. The MADS makro in the directory ../EXAMPLES/MSX/TMC_PLAYER/tmc_relocator.mac accomplishes this.

    The permitted range of values is INDEX = <0..65535>. The values read by .GET are of type BYTE.


    .PUT [index] = value

    The directive .PUT stores a value of type BYTE into a one-dimensional array in MADS memory. This is the same array in which the directive .GET reads a file.

    The permitted range of values is INDEX = <0..65535>.

    Example:
    
     .put [5] = 12       ; store the value 12 into MADS memory at element 5
    

    .SAV [index] ['filename',] length

    The directive .SAV saves the buffer used by the directives .GET and .PUT to an external file or inserts it into the current assembly output.
    Example:
    
     .sav ?length            ; add elements [0..?length-1] to current assembly output
     .sav [200] 256          ; add elements  [200..200+256-1] to current assembly output
     .sav [6] 'filename',32  ; save elements [6..6+32-1] to file FILENAME
    
    The permitted range of values for INDEX = <0..65535>.


    .OR, .AND, .XOR, .NOT

    These directives are equivalent to the logical operators || (.OR), && (.AND), ^ (.XOR), ! (.NOT).


    .LO (expression), .HI (expression)

    These directives are equivalent to '<' (low byte) and '>' (high byte), respectively.


    .IF, .ELSE, .ELSEIF, .ENDIF

     .IF     [IFT] expression
     .ELSE   [ELS]
     .ELSEIF [ELI] expression
     .ENDIF  [EIF]
    

    These directives and pseudo commands can be used interchangeably to conditionally assemble portions of code:

    Example:
    
     .IF .NOT .DEF label_name
       label_name = 1
     .ENDIF
    
     .IF [.NOT .DEF label_name] .AND [.NOT .DEF label_name2]
       label_name = 1
       label_name2 = 2
     .ENDIF
    

    In these examples the parentheses or square brackets are required as otherwise the parameter to the first .DEF directive would be the label label_name.AND.NOT.DEFlabel_name2 (spaces are ignored and periods are allowed in label names).


    6502 CODE GENERATION DIRECTIVES

     #IF type expression [.OR type expression] [.AND type expression]
     #ELSE
     #END
    
     #WHILE type expression [.OR type expression] [.AND type expression]
     #END
    
     #CYCLE #N
     

    #IF type expression [.OR type expression] [.AND type expression]

    The #IF directive is somewhat equivalent to the IF statement of higher-level languages (C, Pascal).

    The #IF, #ELSE, and #END directives produce 6502 machine code for an IF conditional statement around the designated program block and can be nested. All types are acceptable (.BYTE, .WORD, .LONG, and .DWORD). It is possible to combine terms using the .AND and .OR directives, but it is impossible to control the order of evaluation with parentheses.

    The implementation of the #IF directive begins with the calculation of the value that is a simple expression consisting of two operands and one operator (expression can be combined using the .OR or .AND directives).

    If the expression is non-zero (TRUE), the program block within the #IF is executed, terminated by a JMP instruction to the next instruction after #END if there is an #ELSE block.

    If the expression is zero (FALSE), the code following #ELSE is executed. If there is no #ELSE directive, then control is transferred to the next instruction after the #END directive. Example:
    #if .byte label>#10 .or .byte label<#5
    #end
    
    #if .byte label>#100
    
    #else
    
     #if .byte label<#200
     #end
     
    #end
    
    #if .byte label>#100 .and .byte label<#200 .or .word lab=temp
    #end
    
    #if .byte @
    #end
    

    #WHILE type expression [.OR type expression] [.AND type expression]

    The #WHILE directive is equivalent to the WHILE statement in higher-level languages (C, Pascal).

    The directives #WHILE and #END allow generation of 6502 machine code for a loop around the given program block and can be nested. All types .BYTE, .WORD, .LONG, and .DWORD are acceptable. Multiple terms can be connected with the .OR and .AND directives, but order of evaluation cannot be controlled by parentheses.

    The sequence of operations in the expansion of the #WHILE statement is as follows:

    • 1. Calculate the value of the expression and check if it is equal to zero (FALSE).
      • if so, skip step 2;
      • if not (TRUE), go to step 2.
    • 2. Execute the code block bounded by the #WHILE and #END directives, then go to step 1.

    If the first evaluation of the expression produces zero, the program block will never be executed and control passes to the next statement after #END.

    #while .byte label>#10 .or .byte label<#5
    #end
    
    #while .byte label>#100
     #while .byte label2<#200
     #end
    #end
    
    #while .byte label>#100 .and .byte label<#200 .or .word lab=temp
    #end
    

    #CYCLE #N

    The directive #CYCLE generates code to take a given number of cycles. The generated code does not modify any memory or any general purpose register.

    #cycle #17  ; pha      3 cycle
                ; pla      4 cycle
                ; pha      3 cycle
                ; pla      4 cycle
                ; cmp $00  3 cycle
                          ---------
                          17 cycle
    

    Assembling into zero page

    Unlike two-pass assemblers like QA and XASM, MADS is a multi-pass assembler. Why?

    Take this example:
     org $00
     
     lda tmp+1
     
    tmp lda #$00
    
    A two-pass assembler does not know the value of the TMP label and will assume that it is 16-bit (WORD type) and generate LDA abs.

    However, MADS nicely generates LDA zp. This is the simplest benefit of multiple passes.

    Now, suppose referring to zero page with LDA abs is required. No problem, just extend the mnemonic:
     org $00
     
     lda.w tmp+1
     
    tmp lda #$00
    
    Three mnemonic extensions are allowed:
     .b[.z]
     .w[.a][.q]
     .l[.t]
    
    meaning BYTE, WORD, and LONG (TRIPLE). The last one generates a 24-bit value for 65816 long addressing (seldom used). For more information 6502 and 65816 CPU mnemonics, see
    Mnemonics.

    Another way to force zero page addressing is to use curly braces { }:

     dta {lda $00},$80    ; lda $80
    
    Either will work with MADS, but the last pass will do the trick for us. :) The next problem is putting this code on your computer. Loading directly into page zero will probably work if the target area is within $80..$FF, but below that the OS is unlikely to survive.

    Therefore, MADS allows the following:

     org $20,$3080
     
     lda tmp+1
     
    tmp lda #$00
    
    This assembles at address $0020, but with a load address of $3080. Of course, moving the code to the correct address ($0020 in our example) is now the responsibility of the programmer.

    In summary:

     org adres1,adres2
    

    Assembles at adres1, but loads to address adres2. The ORG will always create a new block in the file, which adds an additional four bytes for the header of the new block.

    If it is OK for the new address of the data in memory to be the current address, then the property of .LOCAL and .PROC blocks can be used to avoid writing a new header:
         1
         2 					org $2000
         3
         4 FFFF> 2000-200D> A9 00		lda #0
         5 2002 EA				nop
         6
         7 0060			.local	temp, $60
         8
         9 0060 BD FF FF			lda $ffff,x
        10 0063 BE FF FF			ldx $ffff,y
        11
        12 				.endl
        13
        14 2009 A5 60			lda temp
        15 200B AD 03 20			lda .adr temp
        16
    
    In this example the block TEMP will assemble with the new address = $60 and be placed in memory at address $2003. After the block end directive (.ENDL, .ENDP, .END), assembly will resume at the previous assembly address plus the length of the block, which in this case is $2009.

    The directives .ADR and .LEN can then be used to copy the block to the correct address:

          ldy #0
    copy  mva .adr(temp),y temp,y+
          cpy #.len temp
          bne copy
    
    For more information on the directives, see .ADR and .LEN.


    TYPES

    MADS allows the declaration of two types of data: structured (.STRUCT), and enumerated (.ENUM).

    STRUCTURED TYPES, STRUCTURES

    If you have programmed in C, you have probably already encountered structures. Overall, a MADS structure defines an array of virtual, one-dimensional fields of varying .BYTE, .WORD, .LONG, or .DWORD types or multiples thereof. They are virtual because they exist only in memory during assembly.

    The fields of the structure contain information about offsets from the beginning of the structure.


    Declaring structures (.STRUCT)

    Structure declaration directives:

    name .STRUCT
         .STRUCT name
         .ENDS [.SEND] [.END]
    

    name .STRUCT

    Declares a structure with the name name preceding the .STRUCT directive. The name of the structure is required and an error is generated if it is missing. Structures cannot be named with mnemonic or psuedo-instruction names. If the name is reserved, a Reserved word error is reported.

    Example of structure declaration:
    .STRUCT name
    
      x .word      ; lda #name.x = 0
      y .word      ; lda #name.y = 2
      z .long      ; lda #name.z = 4
      v .dword     ; lda #name.v = 7
    
      q :3 .byte   ; lda #name.q = 11
    
    .ENDS          ; lda #name   = 14 (length)
    
    Each line defines a field by name and type (.BYTE, .WORD, .LONG, or .DWORD). The field name may be preceded by whitespace. Between the .STRUCT and .ENDS directives, CPU mnemonics may not be used. Attempting to do so or having other invalid characters will result in a Improper syntax or Illegal instruction error.

    In summary, the label name contains information about the total length of the structure (in bytes). The other labels describing the fields contain information about the offsets to each field from the beginning of the structure.

    Structure declarations cannot be nested, but previously declared structures can be nested in other ones (declaration order does not matter). For example:
    .STRUCT temp
    
    x .word
    y .word
    v .byte
    z .word
    
    .ENDS
    
    
    .STRUCT test
    
    tmp  temp
    
    .ENDS
    
     lda #temp.v
     lda #test.tmp.x
     lda #test.tmp.z
    
    What are structures useful for?

    Suppose you have a table of different types, where you can read each table field with a predetermined offset value. If a field is added to the table, or the table is modified in any other way, the program code will have to be updated to use new field offsets. Defining the table using a structure means that offsets can be determined by the structure definition, which are then automatically updated even if the structure of the table is changed.

    Another example of structure usage can be found in the section on External symbols, Using external symbols with structures (.STRUCT).


    Defining structured data, references

    Structured data can be defined by assigning a new label with the pseudo-command DTA and a specific structure name, or just with the structure name without the pseudo-command. The result is that the virtual structure definition is turned into actual reserved memory.

    label DTA struct_name [count] (data1,data2,data3...) (data1,data2,data3...) ...
    
    label struct_name
    

    COUNT specifies a number in the range <0..COUNT>, which defines the maximum element index in a one-dimensional array and thus the amount of memory reserved.

    Examples of structure and structured data declarations:
    ;-----------------------;
    ; structure declaration ;
    ;-----------------------;
    .STRUCT temp
    
    x .word
    y .word
    v .byte
    z .word
    
    .ENDS
    
    ;---------------;
    ; defining data ;
    ;---------------;
    
    data dta temp [12] (1,20,200,32000) (19,2,122,42700)
    
    data2 dta temp [0]
    
    data3 temp          // shorter equivalent to DATA2
    
    The value in square brackets must be a value between <..2147483647>, which defines the maximum value of a one-dimensional array index and thus the amount of memory reserved for the structured data.

    After the square brackets an optional list of initializer values (in parentheses) may follow. Otherwise, the field values default to zero. However, if the initializer list is shorter than the number of declared fields, the remaining fields are initialized to the previous value given for those fields:

    data dta temp [12] (1,20,200,32000)
    
    Such a declaration will result in all fields being initialized to the values 1,20,200,32000, not just the first element data[0].

    If the list of initializers is longer than the number of elements, the error Constant expression violates subrange bounds will result.

    To refer to fields in the structured data, use its name, followed by an index in square brackets and the field name after a dot:
     lda data[4].y
     ldx #data[0].v
    

    Forgetting the brackets with an index in the syntax label[index] results in the error Undeclared label.


    ENUMERATED TYPES, ENUMERATION

    These directives are used with enumerations:

    name .ENUM
         .ENDE [.EEND] [.END]
    
    Example:
    
    .enum portb
     rom_off = $fe
     rom_on = $ff
    .ende
    
    .enum test
     a             ; a=0
     b             ; b=1
     c = 5         ; c=5
     d             ; d=6
    .ende
    

    Enumerations are declared using the directives .ENUM and .ENDE. The name of the enumeration is required and an error will be generated otherwise. Enumeration names may not be the same as mnemonics or pseudo-commands, which will produce a Reserved word error.

    The label values are automatically assigned starting with a default value of 0 and incrementing by 1. You can define the value of each label directly or have them be automatically set.

    Enumerated labels are referenced using this syntax:

     enum_name (field)
    
    or directly like with .LOCAL and .PROC blocks, with a dot between the enumeration name and the field name:
     lda #portb(rom_off)
    
     dta portb.rom_on, portb.rom_off
    
    Enumerations can be used for field declarations in structures (.STRUCT) and variable declarations (.VAR):
    bank portb           // allocate variable BANK of size 1 byte
    .var bank portb      // allocate variable BANK of size 1 byte
    
    .struct test
     a portb
     b portb
    .ends
    
    The size of an enumeration is dependent upon the maximum value of its labels:
        .enum EState
            DONE, DIRECTORY_SEARCH=$ff, INIT_LOADING, LOADING
        .ende
    
    In this example, the enumeration "EState" will have a size of two bytes (WORD).

    The size of an enumeration can be checked with the .LEN directive (equivalent to SIZEOF), where the result will be a value in the range 1..4 (1=BYTE, 2=WORD, 3=LONG, 4=DWORD):

     .print .len EState
    


    ARRAYS

    Declaring dimensional arrays (.ARRAY)

    Directives for arrays:

    name .ARRAY index type [= default_value]
         .ARRAY name count type [= default_value]
         .ENDA [.AEND] [.END]
    
    Available types are .BYTE, .WORD, .LONG, and .DWORD.

    INDEX specifies the maximum permitted value of the array index range [0..INDEX]. This value can be a constant or an expression in the range <0..65535>. If INDEX is omitted, the range is determined by the number of input values.

    CPU mnemonics cannot be used between .ARRAY and .ENDA, and attempting to do so or having other illegal characters will result in the error Improper syntax.

    The array index used for initialization can be specified along with initializer values. A new array index is set by placing it in square brackets at the beginning of a new line, i.e. [expression]. Additional indices can be supplied, separated by a colon (':'). The array values then follow after a equals sign ('='):
    .array tab .byte      ; define array TAB with an unspecified number of elements
     1,3                  ; [0]=1, [1]=3
     5                    ; [2]=5 
     [12] = 1             ; [12]=1
     [3]:[7]:[11] = 9,11  ; [3]=9, [4]=11, [7]=9, [8]=11, [11]=9, [12]=11
    .enda
    

    This facility may seem strange and of limitd use, but it is occasionally useful, such as for declaring lookup tables for translating the scan code of a pressed key or between ATASCII and INTERNAL code.

    .array TAB [255] .byte = $ff   ; allocate 256 bytes [0..255] with initial value $FF
    
     [63]:[127] = "A"              ; assign new values TAB[63]="A", TAB[127]="A"
     [21]:[85]  = "B"
     [18]:[82]  = "C"
     [58]:[122] = "D"
     [42]:[106] = "E"
     [56]:[120] = "F"
     [61]:[125] = "G"
     [57]:[121] = "H"
     [13]:[77]  = "I"
     [1] :[65]  = "J"
     [5] :[69]  = "K"
     [0] :[64]  = "L"
     [37]:[101] = "M"
     [35]:[99]  = "N"
     [8] :[72]  = "O"
     [10]:[74]  = "P"
     [47]:[111] = "Q"
     [40]:[104] = "R"
     [62]:[126] = "S"
     [45]:[109] = "T"
     [11]:[75]  = "U"
     [16]:[80]  = "V"
     [46]:[110] = "W"
     [22]:[86]  = "X"
     [43]:[107] = "Y"
     [23]:[87]  = "Z"
     [33]:[97]  = " "
    
     [52]:[180] = $7e
     [12]:[76]  = $9b
    
    .enda
    

    In this example, an array TAB is created with indices [0..255] and 256 .BYTEs in size, pre-initialized to $FF. The array elements are then set to translate keyboard scan codes (both upper and lowercase, ignoring case) to INTERNAL.

    The colon (':') is used to separate array indices.

    Another example is to center a string:
     org $bc40
    
    .array txt 39 .byte
     [17] = "ATARI"
    .enda
    

    In summary, the .ARRAY directive allows creation of a one-dimensional array of values with a specified type.

    To refer to an array:
     lda tab,y
     lda tab[23],x
     ldx tab[200]
    
    If the index given in square brackets exceeds the maximum index of the array, the error message Constant expression violates subrange bounds is reported.


    MACROS

    Macros help perform repetitive tasks by automating them. They are only kept in memory during assembly unless invoked. With their aid, MADS can push and pop parameters off a software stack for a procedure declared with the directive .PROC and switch extended memory banks with the option BANK SENSITIVE (OPT B+).

    Declaring macros

    Macro pseudo-commands and directives:

    name .MACRO [arg1, arg2 ...] ['separator'] ["separator"]
         .MACRO name [(arg1, arg2 ...)] ['separator'] ["separator"]
         .EXITM [.EXIT]
         .ENDM [.MEND]
         :[%%]parameter
         :[%%]label
    

    name .MACRO [(arg1, arg2 ...)] ['separator'] ["separator"]

    Declares a macro named name with the directive .MACRO. The macro name is required and an error is reported without it. Macro names cannot be the same as an instruction mnemonic or pseudo-command, which will cause a Reserved word error.

    A list of named arguments can be specified for the macro, optionally wrapped in parentheses. Assigning name to macro arguments improves readability of macro code. Argument names and numeric arguments can be used interchangeably.
    .macro SetColor val,reg
     lda :val
     sta :reg
    .endm
    

    At the end of the macro declaration, the argument separator and the argument parsing mode can be supplied (unchanged for single quotes, split into parameters and addressing modes for double quotes).

    The default separators for macro argument parsing are a comma (',') and a space (' ').

  • name .MACRO 'separator'
  • Between the quotes '' we place the separator character used to separate parameters when invoking the macro (only with single quotes).
  • name .MACRO "separator"
  • Double quotes ("") can also be used to set separators for the macro parameters, but this also indicates to MADS that the parameters should be split into two parts: addressing mode and argument.
     test #12 200 <30
    
    test .macro " "
    .endm
    
    This TEST macro is declared with a space as the separator using ", which then causes the macro parameter to be divided into two parts, addressing mode and argument.
     #12   ->  addressing mode '#' argument 12
     200   ->  addressing mode ' ' argument 200
     <30   ->  addressing mode '#' argument 0   (calculated expression value of "<30")
    
     test '#' 12 ' ' 200 '#' 0
    
    NOTE #1: The sign operators '<', '>' are evaluated before parameters are passed to a macro, with the result substituted as the parameter.

    NOTE #2: If the macro parameter is the loop counter '#' or '.R' (!!! the single character '#' or the directive '.R', and not an expression involving one of them !!!) the value of the loop counter is substituted as the macro parameter.

    This property can be used to create iterated label names like "label0", "label1", "label2", "label3"... :
     :32 find #
    
    find .macro
          ift .def label:1
          dta a(label:1)
          eif
         .endm
    
    In this example, the address of each numbered label is written (if it is defined).


    .EXITM [.EXIT]

    End the macro. This terminates the macro invocation.

    .ENDM [.MEND]

    The directive .ENDM or .MEND ends the current macro definition. The .END directive cannot be used as for the .LOCAL, .PROC, .ARRAY, .STRUCT, and .REPT directives.

    :[%%]parameter

    The parameter is a positive decimal number (>=0), followed by a colon (':') or two percent signs ('%%'). If in a macro you want to use ':' for repetition and not to signify a macro parameter, ensure that the next character after the colon is outside of the range '0'..'9':
     :$2 nop
     :+2 nop
     :%10 nop
    
    Parameter :0 (%%0) has special meaning and contains the number of parameters passed. This can be used to check if the required number of parameters was passed to a macro:
      .IF :0<2 || :0>5
        .ERROR "Wrong number of arguments"
      .ENDIF
    
      IFT %%0<2 .or :0>5
        ERT "Wrong number of arguments"
      EIF 
    

    Example macro:

    .macro load_word
    
       lda <:1
       sta :2
       lda >:1
       sta :2+1   
     .endm
    
     test ne
     test eq
    
    .macro test
      b%%1 skip
    .endm
    

    Calling macros

    Macros are called by name, with arguments separated by default with commas (',') or spaces (' '). The maximum number of parameters is limited only by PC memory. If the number of parameters passed is fewer than the number of parameters in the macro, the missing parameters are set to the value -1 ($FFFFFFFF). This property can be used to test if a parameter has been passed, but it is easier to use parameter zero (%%0).

     macro_name [Par1, Par2, Par3, 'Par4', "string1", "string2" ...]
    

    A parameter can be a value or a string delimited by either single quotes ('') or double quotes. ("").

  • Single quotes ' ' are passed to the macro along with the characters within them
  • Double quotes " " mean that only the string within the quotes and not the quotes themselves are passed to the macro

    All label definitions within a macro are local.

    If the assembler does not find a label within the macro, it will then look in the local scope (if there was a .LOCAL directive), then in the procedure (if a procedure is currently being defined), and then finally in the main program.

    Examples of macro calls:

     macro_name 'a',a,>$a000,cmp    ; the default separator ','
     macro_name 'a'_a_>$a000_cmp    ; the declared separator '_'
     macro_name 'a' a >$a000 cmp    ; the default separator ' '
    
    Macros can be called from other macros as well as called recursively. In the latter case, care should be taken to avoid causing stack overflow in MADS. MADS is protected against infinite recursion and will stop with an error once the nesting depth reaches 4095 (with Infinite recursion).

    An example of a macro will overflow the MADS stack:

    jump .macro
    
          jump
    
         .endm
    
    Example program that passes parameters to pseudo-procedures, from ..\EXAMPLES\MACRO.ASM:
     org $2000
     
     proc PutChar,'a'-64    ; call macro PROC, with as parameters
     proc PutChar,'a'-64    ; the name of a procedure to call by JSR
     proc PutChar,'r'-64    ; and a single argument (INTERNAL character code)
     proc PutChar,'e'-64
     proc PutChar,'a'-64
    
     proc Kolor,$23         ; call another procedure to change the background color
    
    ;---
    
    loop jmp loop           ; endless loop to show the effect
    
    ;---
    
    proc .macro             ; declare PROC macro
     push =:1,:2,:3,:4      ; call PUSH macro to push arguments onto the satck
                            ; =:1 calculates the memory bank
     
     jsr :1                 ; jump to procedure (procedure name is the first parameter)
     
     lmb #0                 ; Load Memory Bank, setting bank to 0
     .endm                  ; end of PROC macro
    
    ;---
    
    push .macro             ; declare PUSH macro
    
      lmb #:1               ; set up virtual memory bank
    
     .if :2<=$FFFF          ; if passed argument is less than or equal to $FFFF
      lda <:2               ; put it on the stack
      sta stack
      lda >:2
      sta stack+1
     .endif 
    
     .if :3<=$FFFF
      lda <:3
      sta stack+2
      lda >:3
      sta stack+3
     .endif 
    
     .if :4<=$FFFF
      lda <:4
      sta stack+4
      lda >:4
      sta stack+5
     .endif 
     
     .endm
     
    
    * ------------ *            ; KOLOR procedure
    *  PROC Kolor  *
    * ------------ *
     lmb #1                     ; set virtual bank to 1
                                ; label definitions are now local to this bank
    stack org *+256             ; stack for KOLOR procedure
    color equ stack
    
    Kolor                       ; code for KOLOR procedure
     lda color
     sta 712
     rts
    
     
    * -------------- *          ; PUTCHAR procedure
    *  PROC PutChar  *
    * -------------- *
     lmb #2                     ; set virtual bank to 1 2
                                ; label definitions are now local to this bank
    stack org *+256             ; stack for PUTCHAR procedure
    char  equ stack
    
    PutChar                     ; code for PUTCHAR procedure
     lda char
     sta $bc40
    scr equ *-2
    
     inc scr
     rts
    
    Of course, this example uses a software stack, whereas with the 65816 the hardware stack could be used instead. Because the defined variables are each local to a particular bank, procedure calls can be created with similar structure and function to those of higher-level languages.

    However, it is simpler and more efficient to use the procedures allowed by MADS, which are declared with .PROC. For more information on procedure declaration and operations, see Procedures.


    PROCEDURES (.PROC)

    MADS adds the ability to use procedures with parameters. This feature resembles the familiar mechanisms of high-level languages and is just as easy for a programmer to use.

    The built-in MADS macros (@CALL.MAC, @PULL.MAC, @EXIT.MAC) provide a software stack of 256 bytes, the same size as the hardware stack, a way to pop from the software stack, and to save and restore parameters when calling other procedures. MADS supports recursive procedure calls.

    The programmer is not involved in this mechanism and can focus on his program, only needing to define the appopriate labels and include the needed macros when assembling the program.

    Also, the software stack can be omitted and arguments passed using a more classical method with CPU registers (.REG directive) or with variables (.VAR directive).

    Another feature of .PROC procedures is that it is possible to omit them during assembly if they are not referenced. This produces the warning message Unreferenced procedure ????. They can be removed during assembly by specifying the -x 'Exclude unreferenced procedures' command-line parameter to MADS.

    All labels defined in a .PROC procedure are local but can also be accessed globally, which is uncommon in other programming languages.

    It is possible to define a global label from Within a .PROC procedure (see
    Global labels).

    To access labels within a procedure from outside of it, address it using a dot ('.'):
     lda test.pole
    
    .proc test
    
    pole nop
    
    .endp
    
    If a referenced label is not found within a .PROC procedure, MADS will then look for in enclosing scopes until the global scope is reached. To directly address a global label from within a .PROC procedure (or any other scope) prefix the label name with a colon (':').

    For procedures that use a software stack, MADS requires three specific globally defined labels (the stack location, the stack pointer, and the address of the procedure variables):
  • @PROC_VARS_ADR
  • @STACK_ADDRESS
  • @STACK_POINTER
  • If these labels are undefined and a ..PROC procedure with a software stack is used, MADS assumes the following default values: @PROC_VARS_ADR = $0500, @STACK_ADDRESS = $0600, and @STACK_POINTER = $FE.

    For procedures using a software stack, MADS also requires the declaration of macros with specific names. Declarations of these macros are included with MADS in the following files:
  • @CALL ..\EXAMPLES\MACROS\@CALL.MAC
  • @PUSH ..\EXAMPLES\MACROS\@CALL.MAC
  • @PULL ..\EXAMPLES\MACROS\@PULL.MAC
  • @EXIT ..\EXAMPLES\MACROS\@EXIT.MAC
  • These macros implement the loading and pushing of parameters onto the software stack, the popping and saving of procedure parameters off the software stack, and calling other procedures using the software stack.

    Declaration of .PROC procedures

    Procedure declaration directives:

     name .PROC [(.TYPE PAR1 .TYPE PAR2 ...)] [.REG] [.VAR]
     .PROC name [,address] [(.TYPE PAR1 .TYPE PAR2 ...)] [.REG] [.VAR]
     .ENDP [.PEND] [.END]
    

    name .PROC [(.TYPE Par1,Par2 .TYPE Par3 ...)] [.REG] [.VAR]

    Declares a procedure name using the .PROC directive. The procedure name is required and an error is generated without it. Mnemonic names and pseudo-commands cannot be used as procedure names and will cause a Reserved word error.

    To use MADS's parameter passing mechanism, the parameters have to be declared beforehand. Parameter declarations are enclosed in parentheses ( ). There are four types of parameters:
  • .BYTE (8-bit) relocatable
  • .WORD (16-bit) relocatable
  • .LONG (24-bit) non-relocatable
  • .DWORD (32-bit) non-relocatable
  • In current versions of MADS, it is not possible to pass parameters of structure type (.STRUCT).

    The parameter type comes first, followed by at least one space, followed by the parameter name. Multiple parameters of the same type can be declared, separated by commas (',').

    Example procedure declarations using the software stack:
    name .PROC ( .WORD par1 .BYTE par2 )
    name .PROC ( .BYTE par1,par2 .LONG par3 )
    name .PROC ( .DWORD p1,p2,p3,p4,p5,p6,p7,p8 )
    

    Additionally, by using the .REG or .VAR directives, parameters can be passed to MADS procedures by CPU registers (.REG) or variables (.VAR). The directive specifying the parameter passing convention is placed at the end of the .PROC procedure declaration.

    Example procedure declarations using CPU registers:
    name .PROC ( .BYTE x,y,a ) .REG
    name .PROC ( .WORD xa .BYTE y ) .REG
    name .PROC ( .LONG axy ) .REG
    

    The .REG directive requirse that the parameter names are made up of the letters 'A', 'X', 'Y', or a combination thereof. These refer to the names of the CPU registers and affect the order in which they are used. The number of parameters passed is limited by the number of CPU registers, so at most three bytes can be passed to the procedure. The advantage of this method is speed and lower memory usage.

    Example procedure declarations using variables:
    name .PROC ( .BYTE x1,x2,y1,y2 ) .VAR
    name .PROC ( .WORD inputPointer, outputPointer ) .VAR
    name .PROC ( .WORD src+1, dst+1 ) .VAR
    
    With .VAR, the parameter names indicate the variable names which will be loaded with the passed parameters. This method is slower than .REG but still faster than software stack methods.

    Procedures are exited in the usual way, using the RTS command. Adding the RTS instruction at the end of each code path is the responsibility of the programmer, not the assembler.

    As with a .LOCAL block, a new address can be specified for assembling a .PROC block:
    .PROC label,$8000
    .ENDP
    
    .PROC label2,$a000 (.word ax) .reg
    .ENDP
    
    For procedures that use the software stack, MADS invokes the macro @EXIT at the end of the procedure, whose task is to modify the software stack pointer @STACK_POINTER. This is necessary for proper software stack operation. Users can write their own @EXIT macro, or use the one included with MADS (file ..\EXAMPLES\MACROS\@EXIT.MAC), which currently looks like this:
    .macro @EXIT
    
     ift :1<>0
    
      ift :1=1
       dec @stack_pointer
    
      eli :1=2
       dec @stack_pointer
       dec @stack_pointer
    
      els
       pha
       lda @stack_pointer
       sub #:1
       sta @stack_pointer
       pla
    
      eif
    
     eif
    
    .endm
    

    The macro @EXIT should not alter the contents of CPU registers if you want to return a result from a .PROC procedure using CPU registers.

    .ENDP

    The .ENDP directive ends a procedure declaration block.

    Procedure calls

    A procedure is called by name (the same as for a macro), followed by any provided parameters, separated by a commas (',') or spaces (' '). It is not possible to use other separators.

    If the type of a parameter is different than the type used in the procedure declaration, an Incompatible types error is reported.

    If the number of parameters passed is different than the number of parameters in the procedure declaration, the result is an Improper number of actual parameters error. The exception is procedures which use parameters passed by CPU register (.REG) or variable (.VAR), in which case the extra parameters are assumed to be already loaded into the correct registers or variables.

    There are three ways to pass parameters:

  • '#' by value
  • ' ' by address (without prefix)
  • '@' by accumulator (parameter type .BYTE)
  • "string" as a string, e.g. "label,x"

    Example procedure calls:

     name @ , #$166 , $A400  ; with the software stack
     name , @ , #$3f         ; with .REG or .VAR
     name "(hlp),y" "tab,y"	 ; with .VAR or the stoftware stack (the software stack uses the X register)
    

    When MADS encounters a procedure call that uses the software stack, it executes the macro @CALL. However, if the procedure does not use the software stack, a plain JSR PROCEDURE is used instead of the @CALL macro.

    To the @CALL macro, MADS passes parameters computed based on the procedure declaration, breaking each parameter into three components: addressing mode, parameter type, and parameter value.
    @CALL_INIT 3\ @PUSH_INIT 3\ @CALL '@','B',0\ @CALL '#','W',358\ @CALL ' ',W,"$A400"\ @CALL_END PROC_NAME
    
    Here, the @CALL macro pushes the contents of the accumulator, then the value $166 (358 dec), then the value at the address $A400. For more information on how parameters are passed to the macro (and the importance of '' and ""), see
    Calling macros.

    Parameters passed using the accumulator ('@') should always be the first parameter passed to the procedure. If it is used elsewhere, the accumulator is already modiied by that point (this restriction is imposed by the @CALL macro). Of course, this can be lifted with a custom version of the @CALL macro. With procedures that use .REG or .VAR, a '@' parameter can be used in any position.

    The end of a .PROC procedure is marked by an RTS. After the procedure call, MADS invokes the @EXIT macro to modify the @STACK_POINTER, which is necessary for proper operation of the software stack. The number of bytes passed to the procedure is passed as a parameter to the macro, which then subtracts that number of bytes from the software stack.

    (Editor's note: This is known as a caller-pops convention, since the caller both pushes and pops the parameters off the stack, and is common in C implementations.)

    Adding an RTS instruction at the end of every code path in the procedure is the responsibility of the programmer, and not the assembler.


    Referencing procedure parameters

    Referring to procedure parmaeters does not require additional effort by the programmer:
    @stack_address equ $400
    @stack_pointer equ $ff
    @proc_vars_adr equ $80
    
    name .PROC (.WORD par1,par2)
    
     lda par1
     clc
     adc par2
     sta par1
     
     lda par1+1
     adc par2+1
     sta par1+1
    
    .endp
    
     icl '@call.mac'
     icl '@pull.mac'
     icl '@exit.mac'
    
    At the time of declaration, MADS automatically defines these parameters by assigning values based on @PROC_VARS_ADR. In the preceding example, MADS will define the parameters as PAR1 = @PROC_VARS_ADR and PAR2 = @PROC_VARS_ADR + 2.

    The programmer uses these parameters by the names given in the procedure declaration, similarly as with higher-level languages. In MADS, it is possible to access procedure parameters externally, which is unusual in higher-level languages. For instance, PAR1 can be read as follows:

     lda name.par1
     sta $a000
     lda name.par1+1
     sta $a000+1
    
    This copies the two bytes at PAR1 to addresses $A000 and $A000+1. Of course, this can only be done after completion of this particular procedure. Remember that each procedure has parameters stored at the same area addressed by @PROC_VARS_ADR, so with each new procedure call the parameter area at <@PROC_VARS_ADR .. @PROC_VARS_ADR + $FF> changes.

    If a procedure is declared using .REG type parameters, the programmer should remember to preserve or use parameters before they are modified by the procedure code. With .VAR type parameters, this is not an issue because the parameters are saved in specific memory locations where they can always be read.


    LOCAL AREA

    The main purpose of a local area in MADS is to create a new scope for labels.

    All labels defined in a .LOCAL area are local. However, you can still refer to a local label globally, which is uncommon in other programming languages.

    It is possible to define a global label within a .LOCAL area (see
    Global labels).

    If the assembler cannot find a label within a .LOCAL area, MADS will then look in the global scope. To refer to global labels directly from a .LOCAL area, prefix the label name with a colon (':').

    Declaring .LOCAL scopes

    Local scope directives:

     [name] .LOCAL [,address]
     .LOCAL [name] [,address]
     .ENDL [.LEND] [.END]
    

    [name] .LOCAL [,address]

    Declares a local scope named name with the directive .LOCAL. The local scope name is not required and can be omitted. Local scope names cannot be the same as mnemonics and pseudo-commands, and attempting to use a reserved name will result in a Reserved word error.

    After the name of the local scope (or the .LOCAL directive), a new assembly address can be provided. After the end of the block (.ENDL), the assembly address reverts to the previous address plus the length of the block.

    label .local,$4000
    .endl
    
    .local label2,$8000
    .endl
    
    .local
    .endl
    
    .local label3
    .endl
    
    All definitions within a .LOCAL block are local. To refer to a global label with the same name as a local name, prefix the name with a colon (':'):
    lab equ 1
    
    .local
    
    lab equ 2
    
     lda #lab
     ldx #:lab
    
    .endl
    
    In this example, the A register is set to 2, while the X register is set to 1.

    If the assembler cannot find a label in a .LOCAL scope, it will then check an enclosing macro (if one is being processed), then the enclosing procedure (if there is one), and finally the main program at global scope.

    Within a local scope, all label definitions are qualified by the local scope's name. To reach labels defined in another local scope, both the name of the local scope and the label must be supplied:
     lda #name.lab1
     ldx #name.lab2
    
    .local name
    
    lab1 = 1
    lab2 = 2
    
    .endl
    

    A dot ('.') is used to address labels within a .LOCAL block.

    Local scopes can be nested, as well as placed within procedures declared using the .PROC directive. Local scopes are cumulative, i.e. there may be multiple scopes of the same name and all symbols in those scopes will belong to a common namespace.

    .ENDL

    The .ENDL directive ends a local scope.

    Local scope declaration example:
     org $2000
     
    tmp ldx #0   <-------------   label in global scope
                              |
     lda obszar.pole  <---    |   reference to local scope
                         |    |
    .local obszar        |    |   local scope declaration
                         |    |
     lda tmp   <---      |    |
                  |      |    |
     lda :tmp     |      | <---   reference to global scope
                  |      |
    tmp nop    <---      |        definition in local scope
                         | 
    pole lda #0       <---   <--- definition in local scope
                                |
     lda pole  <----------------- reference within local scope
    
    .endl                         end of local scope
    

    SYNTAX

    MADS accepts the same syntax as QA and XASM. However, it is stricter with comments placed at the end of a line (comments should be preceded the appropriate symbol) and more lenient with whitespace and CPU instruction mnemonics without arguments, i.e.:
       asl            ->  asl @
       lda #          ->  lda #0
    

    MADS will accept no whitespace separating the mnemonic and operand, provided that the operand does not start with a '@', which is used in the names of labels, or '%' and ':', which are used to denote numbered macro parameters (%%number, :number), e.g.:
       lda$44
       lda#
       lda(80),y
    

    Comments

    Comment lines must start with a ';' or '*'. For a single-line comment, however, the safest way is to use a semicolon (';'), as the asterisk ('*') has other meanings and can mean multiplication or the current assembly address. On the other hand, the semicolon is dedicated only for comments.

    The characters '//' can also be used for a single-line comment, and '/* */' for a multi-line or inline comment.
     * this is a comment
                     ; this is a comment
     lda #0      ; this is a comment
     dta  1 , 3     * BAD COMMENT, WILL BE MISINTERPRETED
    
     org $2000 + 1      BAD COMMENT, WILL BE MISINTERPRETED
    
     nop // this is a comment
    
     // this is a comment
    
     dta 1,2, /* comment */ 3,4
    
     lda /* comment */ #0
    
    /*
      ...
      this is a multi-line comment
      ...
    */
    
    /************************************
      this is also a multi-line comment
    *************************************/
    

    The multi-line comment signs '/* */' and the end-line comment sign '//' can be used without restrictions.


    Splicing multiple lines into a single line

    Multiple lines can be spliced into a single line using '\', e.g.:

     lda 20\ cmp 20\ beq *-2
     
        lda 20   \ cmp  20   \   beq *-2
     
      lda #0  \lop  sta $a000,y  \ iny  \ bne lop     ; comments only at the end of this line
    

    If there is no space after the '\' character, a mnemonic or other string can be interpreted as a label, so make sure to treat '\' as the beginning of a new line.

    MADS stops processing the line once either at the end of the chain or when a comment is reached, so comments can be placed only at the end of the line.

    WARNING!!! Putting a '\' at the end of a line tells MADS to splice the current line with the next line. For example:
     lda\
     #\
     12
    
    In this case, we get the result 'LDA #12'.


    Combining multiple mnemonics

    XASM already provided the ability to combine two mnemonics using a ':'. In MADS, this is extended to combine any number of MADS-known mnemonics:

     lda:cmp:req 20
    
     lda:iny:sta:iny $600,y
    

    (Editor's note: All mnemonics in a combined statement are processed with the same argument. This is fine when some of the instructions only have implied addressing. However, it can lead to accidents with instructions that have both implied and memory forms. For instance, "STA:INC:RNE pixels,X+" will assemble as STA pixels,X / INX / INC pixels,X / INX / BNE *.)


    EXPRESSIONS

    The term expression means a series of operators and operands (arguments) that specifies the order of operations, i.e. type and order of evaluation. A compound expression is an expression with two or more operators. Operators that affect only one operand are called unary, and operators with two arguments are called binary.

    Expressions are evaluated in the order determined by priority of each operator in the direction specified by the precedence of each operator.

    NUMBERS

    MADS accepts numbers in decimal, hexadecimal, binary, ATASCII, and INTERNAL format.

  • decimal notation:
     -100
     -2437325
     1743
    
  • hexadecimal notation:
     $100
     $e430
     $000001
     
     0x12
     0xa000
     0xaabbccdd
    
  • binary notation:
     %0001001010
     %000000001
     %001000
    
  • ATASCII code:
     'a'
     'fds'
     'W'*
    
  • INTERNAL code:
     "B"
     "FDSFSD"
     "."*
    
    Only the first charcater of ATASCII or INTERNAL coding is significant. A '*' after the closing quote specifies inverse characters.

    Additionally, there are two possible operations '+' and '-' for strings, which increase or decrease the values of the quoted characters.
     "FDttrteSFSD"-12
     'FDSFdsldksla'+2
    


    Operators

    Binary operators:
    
    +   Addition
    -   Subtraction
    *   Multiplication
    /   Division
    %   Remainder
    &   Bitwise and
    |   Bitwise or
    ^   Bitwise xor
    <<  Arithmetic shift left
    >>  Arithmetic shift right
    =   Equal
    ==  Equal (same as =)
    <>  Not equal
    !=  Not equal (same as <>)
    <   Less than
    >   Greater than
    <=  Less or equal
    >=  Greater or equal
    &&  Logical and
    ||  Logical or
    
    
    Unary operators:
    
    +  Plus (does nothing)
    -  Minus (changes sign)
    ~  Bitwise not (complements all bits)
    !  Logical not (changes true to false and vice versa)
    <  Low (extracts low byte)
    >  High (extracts high byte)
    ^  High 24bit (extracts high byte)
    =  Extracts memory bank
    :  Extracts global variable value
    
    
    Operator precedence:
    
    first []              (brackets)
     + - ~ < >            (unary)
     * / % & << >>        (binary)
     + - | ^              (binary)
     = == <> != < > <= >= (binary)
     !                    (unary)
     &&                   (binary)
    last  ||              (binary)
    

    LABELS

    Labels may be defined in the program with local or global scope, depending on the location where they are defined. Additionally, labels may be defined as temporary, also with local or global scope.

  • A global label is visible from anywhere in the program, even within a macro (.MACRO), procedure (.PROC), or local scope (.LOCAL).

  • A local label is only visible within the .MACRO, .PROC, or .LOCAL scope in which it is defined.

  • Label names must begin with ['A'..'Z','a'..'z','_','?','@'].
  • The rest of the label name may contain: ['A'..'Z','a'..'z','0'..'9','_','?','@']
  • Labels are always at the beginning of a line.
  • A label preceded by whitespace should end in a ':' to avoid misinterpretation as a macro.
  • In addressing expressions, prefixing a label with ':' tells the assembler to refer to the label in the main program (global label).

    Examples of label definitions:

    ?name    EQU  $A000      ; defining a temporary global label
    name      =   *          ; defining a global label
    name2=12                 ; defining a global label
    @?name   EQU  'a'+32     ; defining a global label
      name: equ 12           ; defining a non-global label that does not start at the beginning of the line
             name: = 'v'     ; defining a non-global label that does not start at the beginning of the line
    

    Unlike QA/XASM, a question mark ('?') and at-sign ('@') can be used in label names.

    Using a dot ('.') in a label name is allowed but not recommended. The dot is reserved for extended mnemonics, assembler directives, and addressing new MADS structures.

    A dot ('.') at the beginning of a label name suggests that it is an assembler directive, and a question mark ('?') at the beginning signifies a temporary label that can be changed several times during assembly.


    Anonymous labels

    To ensure clarity when using anonymous labels, their use is limited only to jumps no more than 10 instances away.

    The character '@' is reserved for anonymous labels, and there must be a sign character indicating either forward direction ('+') or backwards direction ('-'). Additionally, you can specify the number of anonymous labels in the range [1..9].

     @+[1..9]     ; forward
     @-[1..9]     ; backward
    
    @ dex   ---- -------
      bne @+   |  --   |
      stx $80  |   |   |
    @ lda #0   |  --   |
      bne @- ---       |
      bne @-1  ---------
    

    Local labels

    Labels defined within a macro (.MACRO), procedure (.PROC), or local scope (.LOCAL) are local labels by default and do not need additional markup.

    Local labels are defined using the following equivalent psuedo commands:
     EQU
      =
    
    To access global labels, i.e. those defined outside of a macro (.MACRO), procedure (.PROC), or local scope (.LOCAL), use the ':' operator:
    lp   ldx #0         ; define global label LP
    
         test
         test
     
    test .macro
    
          lda :lp       ; the ':' prefix causes reference to the global label LP
    
          sta lp+1      ; reference to the local label LP in the macro
    lp    lda #0        ; definition of local label LP in the macro
    
         .endm
    
    In this example, there are two definitions of labels with the same name (LP), but each has a different value and a different scope.


    Global labels

    Each definition outside of a macro (.MACRO), procedure (.PROC), or local scope (.LOCAL) is global.

    Global labels are defined using the following equivalent pseudo commands:
     EQU
      =
    
    Or with .DEF directive syntax:
     .DEF :label [= expression]
    

    The .DEF directive normally defines local labels, but the ':' at the beginning of the label indicates a global label instead. Using the syntax .DEF :label allows definition of global labels within a local scope.

    The ':' at the beginning of the label has special meaning and indicates a global label, or label at mainline level, disgarding any current local scopes.

    For more information on use of the .DEF directive, see
    .DEF Directive.

    An example of defining global labels:
    lab equ *
       lab2 equ $4000
    
    	?tmp = 0
    	?tmp += 40
     
    .proc name
    
          .def :?nazwa   = $A000
               .def :nazwa=20
    
          .local lok1
            .def :@?nazw   = 'a'+32
          .endl
    
    .endp
    
    Examples of defining a global temporary labels include the macro @CALL (in ..\EXAMPLES\MACROS\@CALL.MAC), which defines the temporary label ?@STACK_OFFSET. This is later used by other macros called called by the macro @CALL, and is used to optimize access to parameters on the stack.
    @CALL .macro
    
      .def ?@stack_offset = 0    ; definition of temporary global lavel ?@stack_offset
     
      ...
      ...
     
     
    @CALL_@ .macro
    
      sta @stack_address+?@stack_offset,x
      .def ?@stack_offset = ?@stack_offset + 1    ; modify ?@stack_offset label
    
     .endm 
    

    Temporary labels

    A temporary label has the property that its value can be changed many times during assembly. Normally, attempting to redefine a label results in a Label declared twice error, which does not occur with a temporary label.

    The lifetime of a temporary label depends on the scope in which it is defined. Temporary labels may have local scope (Local labels) or global scope (Global labels).

    A temporary label is created by placing a '?' at the beginning:
     ?label
    
    Temporary labels should not be used to name procedures (.PROC), macros (.MACRO), local scopes (.LOCAL), structures (.STRUCT), or arrays (.ARRAY).

    A temporary label is defined using one of the following equivalent pseudo commands:
     EQU
      =
    
    Additionally, they can be modified using recognizable C operators:
     -= expression
     += expression
     --
     ++
    
    These assignment operators only work with temporary labels, and attempting to use them for other types of labels results in a Improper syntax error message.

    Examples of using temporary labels:
    ?loc = $567
    ?loc2 = ?loc+$2000
    
    	 lda ?loc
    	 sta ?loc2
    
    ?loc = $123
    
    	 lda ?loc
    

    MAE-style temporary labels

    Option OPT ?+ tells MADS that labels starting with '?' should be interpreted as local labels as MAE does. By default, labels starting with '?' are interpreted by MADS as temporary labels (Temporary labels).

    An example of using MAE-style temporary labels:
           opt ?+
           org $2000
    
    local1 ldx #7
    ?lop   sta $a000,x
           dex
           bpl ?lop
    
    local2 ldx #7
    ?lop   sta $b000,x
           dex
           bpl ?lop
    

    SPARTADOS X

    SpartaDOS X and Atari DOS file formats

    Reproduced from Serious Magazine, author Qcyk/Dial.

    A file itself is only a collection of bytes, lots of numbers that can mean both everything and nothing at the same time if you do not know how to interpret them. For this reason, most files are equipped with a variety of headers which store information about what the file contains and are necessary to read them. This includes binary executables loaded under DOS. After all, DOS is a program and like everyone else has a right to expect a certain structure in its data.

    Traditional binary files, recognized by all DOSes for Atari XL/XEs, are built of blocks where each block has its own header. There are two types of headers:

     1. dta a($ffff),a(str_adr),a(end_adr)
    
     2. dta a(str_adr),a(end_adr)
    

    str_adr - address at which the first byte of data will be loaded

    end_adr - address at which the last byte of data will be loaded

    The first block in the file header must be $ffff, followed by other blocks. Each block header should of course be followed by this amount of data:

       (end_adr-str_adr)+1
    

    That's enough of a refresher. The developers of SpartaDOS X have kept the above standard, while adding several new types of headers. The file is still divided into blocks, except that now there are a lot more types of blocks. Here they are:


    1. Non-relocatable block (loaded at fixed address in memory):

        dta a($fffa),a(str_adr),a(end_adr)
    

    This is the same as a $ffff block - it does not matter which you use. However, $fffa will clearly indicate that the program is designed for SDX - another DOS cannot read the file.


    2. Relocatable block (loaded starting at MEMLO):

        dta a($fffe),b(blk_num),b(blk_id)
        dta a(blk_off),a(blk_len)
    

    blk_num - block number in the file. Each relocatable block should have its own number. Because the load addresses of blocks are not known, blocks are just identified by number. They may be in the range 0-7, except that in practice they are usually numbered from 1 upwards.

    blk_id - bits 1-5 are the memory type, indicating where the block is to be loaded. I have encountered two values:

     $00 - main memory
     $02 - extended memory
    
    Also, bit 7 indicates no data block if set. In this case, SDX loads nothing, but still reserves memory.

    blk_off - block base address, which is simply the address at which the code was assembled. Thsi is necessary when relocating addresses referring to the contents of the block.

    blk_len - the length of the block. There should be as much data following as indicated by the header, unless the block is only a reserved area in which case there is no data.

    When writing relocatable code, several limitations imposed by the idea of "relocatable code" must be kept in mind. All addresses referring to program areas must be updated during load, so sequences such as this cannot be used:
           lda <something
           ldx >something
           ...
          something equ *
           ...
        Instead, use something like this, for example:
           lda _something
           ldx _something+1
           ...
          _something dta a(something)
           ...
          something equ *
    

    3. Update addresses in a block referring to a relocatable block:

        dta a($fffd),b(blk_num),a(blk_len)
    

    blk_num - number of block containing the reference targets

    blk_len - update block length (without the header). This is ignored.

    Addresses are updated by adding the difference between the address at which the relocatable block was loaded and the value of blk_off (where the block was originally assembled). This can be illustrated as follows:

           ADR=ADR+(blk_adr-blk_off)
    

    The payload of an update block contains pointers to addresses and special commands. Numbers between $00-$fb are offsets from the last updated location. This location is stored as an address in an update pointer. This pointer can be updated through special functions invoked by values greater than $fb:

    $fc marks the end of the update block,

    $fd,a(ADDR) directly updates the address ADDR. Thus, the update pointer is set to ADDR, which is used as the base for the next offset,

    $fe,b(blk_num) sets the update pointer to the base address of the block specified by blk_num, which is then used for the next offset,

    $ff increases the update pointer by $fa (without updating an address).


    4. Update addresses in blocks targeting procedures with defined symbols:

        dta a($fffb),c'SMB_NAME',a(blk_len)
    

    SMB_NAME - procedure symbol name (or array, system registry, etc.) Eight characters in ATASCII code,

    blk_len - as in a $fffd block.

    After the header, there is a sequence of offsets to locations of addresses to update - the same as in a $fffd block. Addresses are updated by adding the address of the procedure denoted by the symbol to the existing address. This allows use in programs of procedures whose addresses are unknown, such as procedures added by other applications running in the SDX environment. Also, system procedures must be used this way, as they have different addresses in different versions of Sparta.


    5. Symbol definition block:

        dta a($fffc),b(blk_num),a(smb_off)
        dta c'SMB_NAME'
    

    blk_num - number of the block in which the procedure is defined. This means that the procedure must be defined in a relocatable block.

    smb_off - procedure offset in the block, which is an offset from the start of the block (the first byte is 0) plus the value of blk_off of the block. Basically, the address at which the procedure was assembled.

    SMB_NAME - symbol name being defined for the procedure.

    Block types $fffb, $fffc, and $fffd are not kept in memory. The system uses them only during program load.


    Programming SpartaDOS X (SDX)

    The syntax for handling SpartaDOS X programs, was taken from FastAssemblera by the author Marka Goderskiego. Below is a quote from the manual that came with FA. MADS can now assemble source files in *.FAS format without any major problems. Relocatable commands always have two-byte arguments; it is impossible to relocate 3-byte arguments (65816).

    The most important innovation in SDX is the ability for developers to write relocatable code. Since the MOS 6502 does not have relative addressing (except for short branches), the ICD developers created a way to do so using special program blocks. The process is based on loading blocks and then updating addresses within the blcok using special update blocks. It is enough to add the value of memlo to correct addresses, but what addresses to correct, and which ones to leave? That's the point of a special block that contains (specially coded) offsets to those addresses. Therefore, an UPDATE ADDRESS operation must be applied to each RELOC block before running the program. UPDATE ADDRESS must also be performed on any block which refers to SPARTA commands or vectors.

    Another innovation is the introduction of symbols. Some of the SDX service procedures are defined by name! These names always have 8 letters (like filenames). Instead of using arrays of vectors or jumps (like in the OS), use symbols defined with SMB. After loading a block or blocks, SDX loads symbol blocks and updates symbol addresses the same way as with relocatable addresses in the program. Symbols can refer to items in either RELOC or SPARTA blocks.

    Programmers can define custom symbols to replace the ones in SDX or completely new ones for use by other programs. This is done by the UPDATE NEW block. It should be kept in mind that new symbols must be stored in a RELOC block.

    The number of RELOC and EMPTY blocks is limited to 7 by SDX.

    Such blocks can be combined into chains:

           blk sparta $600
           ...
    
           blk reloc main
           ...
    
           blk empty $100 main
           ...
    
           blk reloc extended
           ...
    
           blk empty $200 extended
    
    This means that commands for these blocks can refer to all blocks in the chain.

    The chain is not interrupted by updating addreses or symbols, but is ended by the definition of a new symbol and by other block types, e.g. DOS.

    Note: The chain only makes sense if all blocks are loaded into the same memory, or when a program switches to the appropriate memory references.

    Note: Commands and vectors in RELOC and EMPTY blocks should not refer to SPARTA blocks! This may cause an error when the user loads the program using the LOAD command and uses it after a long time. While RELOC and EMPTY are safe, you never know what is in memory where a SPARTA block was last loaded!

    Equally dangerous is the references to RELOC and EMPTY blocks by SPARTA blocks (for the same reason as above), but during the installation of overlays (*.sys) using INSTALL this is sometimes necessary and therefore acceptable. You can also invoke a SPARTA block (through $2E2) to run immediate, then discard it.

    Note: Addresses can collide between SPARTA blocks and RELOC/EMPTY addresses! FA recognizes references to other blocks by address, assuming a PC for RELOC and EMPTY blocks of $1000, so for mixed programs SPARTA blocks should be below $1000 (e.g. $600) or above the last relocatable block, $4000 using being enough. This error is not detected by the compiler!


    RELOCATABLE CODE

    Relocatable code is code without a fixed address, such that when loaded into a computer it has to work regardless of the load address. SpartaDOS X (SDX) provides a relocation facility for Atari XL/XE code, of which more than be read in the section
    Programming SpartaDOS X.

    A basic limitation of SDX relocatable code is that only WORD addresses are relocated and there is no support for 65816 code. MADS provides the ability to generate code both in SDX format and in a non-SDX format that removes the aforementioned limitations.

    The MADS relocatable code format is similar to that of SDX, as there are main blocks and then blocks with additional address relocation information. MADS uses a simpler update block format, without the "compression" used by SDX.

    Advantages of MADS relocatable code:

  • supports operand sizes for both 6502 and 65816 CPUs
  • can use all CPU instructions without restriction
  • supports relocation of both high and low address bytes

    Limitations of MADS relocatable code:

  • labels defined by EQU must precede .RELOC blocks
  • new labels defined in .RELOC blocks must have its name preceded by a space or tab (global label)=
  • you cannot use the ORG, RMB, LMB, or NMB pseudo instructions, or the .DS directive
  • cannot relocate the highest byte of 24-bit words, i.e. lda ^$121416

    An example of how easy it is to create relocatable code is in the file ..\EXAMPLES\TETRIS_RELOC.ASM, which uses the CPU instruction set and data definition pseudo-instructions no differently than the non-relocatable version in ..\EXAMPLES\TETRIS.ASM.


    Reloctable blocks (.RELOC)

    A MADS relocatable block is created using the directive:

     .RELOC [.BYTE|.WORD]
    
    A block for updating a relocatable MADS block is created using the BLK pseudo-command:
     BLK UPDATE ADDRESS
    
    After the .RELOC directive, it is possible to specify a relocation block type (.BYTE, .WORD), with the default being .WORD type. Type .BYTE is for blocks that must be placed in zero page (instructions will use zero page), which MADS will assemble to address $0000. Type .WORD means that MADS will assemble the block starting at address $0100 and that it can be placed anywhere in memory (except for zero page).

    The .RELOC block produces a header like the famous DOS header, further expanded by 10 bytes to a total of 16 bytes:

    HEADER            .WORD = $FFFF
    START_ADDRESS     .WORD = $0000
    END_ADDRESS       .WORD = FILE_LENGTH-1
    MADS_RELOC_HEADER .WORD = $524D
    UNUSED            .BYTE = $00
    CONFIG            .BYTE (bit0)
    @STACK_POINTER    .WORD
    @STACK_ADDRESS    .WORD    
    @PROC_VARS_ADR    .WORD
    
    MADS_RELOC_HEADER always $524D, corresponding to the characters 'MR' (M-ADS R-ELOC)
    FILE_LENGTH the length of the relocatable file without the 16-byte header
    CONFIG currently only bit 0 is used, where bit0=0 means relocatable blocks are assembled starting at $0000, and bit0=1 means blocks are assembled at $0100.

    The last 6 bytes contain information about the values of labels needed for the operation of the software stack, @STACK_POINTER, @STACK_ADDRESS, and @PROC_VARS_ADR, if used in relocatable blocks. If the individual .RELOC blocks were assembled with different values of these labels, linking them together will produce an Incompatible stack parameters warning. If the software stack labels are not used, the values are zero.

    The pseudo-command .RELOC switches MADS to relocatable code generation mode, taking into account the operand sizes of 6502 and 65816 instructions. In this mode, it is impossible to use the ORG, LMB, NMB, and RMB psuedo-instructions or the .DS directive. It is impossible to exit MADS relocatable code generation mode, but it is possible to have more than one .RELOC block.

    Using the .RELOC directive will also increase the MADS virtual bank counter, and thus create a local scope not visible to other blocks. For more information on virtual banks, see the section Virtual memory banks (OPT B-).

    At the end of a .RELOC block it is necessary to generate an update block, using the same BLK syntax for SDX relocatable blocks ("BLK UPDATE ADDRESS"). The encoding format for this block is different than for SDX and is as follows:

    HEADER       WORD ($FFEF)
    TYPE         CHAR (B-YTE, W-ORD, L-ONG, D-WORD, <, >)
    DATA_LENGTH  WORD
    DATA         WORD [BYTE]
    
    HEADER always set to $FFEF
    TYPE data type is stored in bits 0..6 and specifies the type of addresses to update, where "<" means the lower address byte and ">" means the upper address byte.
    DATA_LENGTH number of 2-byte data items (addresses) to modify
    DATA offsets for updating the relocatable block, where at each address a value of type TYPE is read and then updated to the final address

    The exception is an update block for address high bytes ">", where for such a block an extra BYTE is stored for each address (low byte of address being modified). To adjust the high bytes, the high byte has to be read from the WORD address in the DATA, added to the current relocation address, and then added to the low byte in the BYTE field of the DATA. The newly calculated byte is then store back at the WORD address in the DATA.


    External symbols

    External symbols indicate that the represented variables and procedures are stored somewhere outside, beyond the current program. The location need not be specified, only the names and the types. Since the translation of instructions to appropriate machine code depends on the type of data represented by a symbol, the assembler needs to know the size of the data used.

    Currently there is no support for manipulating external symbols of type '^' (highest byte).

    External symbosl may be used in both relocatable .RELOC blocks as well as usual DOS ones.

    External symbols are declared using the pseudo-instruction EXT or the .EXTRN directive:
    label EXT type
    label .EXTRN type
    .EXTRN label1,label2,label3... type
    
    An update block for referencing external symbols is produced using the BLK psuedo-instruction:
     BLK UPDATE EXTERNAL
    
    NOTE: This will write symbol names used by the program..

    External symbols of value type can also be defined (.BYTE, .WORD, .LONG , .DWORD):

    name EXT .BYTE
    
    label_name EXT .WORD
    
     .EXTRN label_name .WORD
    
    wait EXT .PROC (.BYTE delay)
    
    External symbol declarations of procedure (.PROC) type default to .WORD, and attempts to reference the label will be interpreted by MADS as an attempt to call the procedure. For more about procedure calls, see
    Procedures.

    During the assembly process, references to external symbols are replaced with the value zero.

    External symbols can be useful when assembling part of a program separately from the rest of it. In this case, there are often references to other procedures and variables are defined elsewhere, and only the type and not value are known. With the help of external symbols, such a program can be assembled without the full procedure and variable definitions.

    Another use for external symbols is for "plugins", or external programs connected to the main program to add additional functionality. These are types of libraries, using the procedures of the main program and expanding its capabilities. Creating such a plugin requires determining what procedures the main program provides (their name + parameters and type), and a procedure to read the file from the external symbols, which then attaches the plugins to the main program.

    The following is the format of the file header produced by BLK UPDATE EXTERNAL for external symbols of type B-YTE, W-ORD, L-ONG, and D-WORD:

    HEADER        WORD ($FFEE)
    TYPE          CHAR (B-YTE, W-ORD, L-ONG, D-WORD, <, >)
    DATA_LENGTH   WORD
    LABEL_LENGTH  WORD
    LABEL_NAME    ATASCII
    DATA          WORD .. .. ..
    
    HEADER always set to $FFEE
    TYPE bits 0..6 contain the type of data to modify
    DATA_LENGTH number of 2-byte data items (addresses) to modify
    LABEL_LENGTH symbol name length in bytes
    LABEL_NAME the symbol name, coded in ATASCII
    DATA offset data for the relocation process. At each indicated address here, the value of type TYPE is read and then based on the actual value of the symbol.

    An applied example of external symbols and .STRUCT structures is the graphical primitives library in the directory ..\EXAMPLES\LIBRARIES\GRAPHICS\LIB. Individual modules use a fairly large number of zero page variables, and if we want to place these in relocatable code each individual variable would have to be declared as an external symbol by EXT (or .EXTRN). We can simplify this by using only one symbol and external data of structure (.STRUCT) type. These structures define a "map" of variables called ZP and one ZPAGE external symbol, of type .BYTE because we want it to be in zero page. Now, when referring to the variable, we need to do it in a way that forces relocation such as ZPAGE + ZP.DX. The result is a fully relocatable module with relocated variables in zero page.


    Public symbols

    Public symbols make variables and procedures available to other blocks in the rest of the relocatable assembly program. With public symbols, you can refer to variables and procedures from libraries.

    Public symbols can be used in relocatable .RELOC blocks as well as usual DOS blocks.

    MADS automatically detects whether a public label is a variable, constant, or procedure defined by .PROC, and does not need any additional information as for external symbols.

    Public symbols are declared using the following directives:
     .PUBLIC label [,label2,...]
     .GLOBAL label [,label2,...]
     .GLOBL label [,label2,...]
    
    The directives .GLOBAL and .GLOBL have been added for compatibility with other assemblers. They are identical in meaning to .PUBLIC directive.

    Update blocks for public symbols are created using the BLK pseudo-command:
     BLK UPDATE PUBLIC
    

    Below is the header format produced by BLK UPDATE PUBLIC:

    HEADER        WORD ($FFED)
    LENGTH        WORD
    TYPE          BYTE (B-YTE, W-ORD, L-ONG, D-WORD)
    LABEL_TYPE    CHAR (C-ONSTANT, V-ARIABLE, P-ROCEDURE, A-RRAY, S-TRUCT)
    LABEL_LENGTH  WORD
    LABEL_NAME    ATASCII
    ADDRESS       WORD
    
    MADS automatically selects the appropriate type for public labels:
  • C-ONSTANT
  • label is not subject to relocation
  • V-ARIABLE
  • label is subject to relocation
  • P-ROCEDURE
  • procedura defined by .PROC, subject to relocation
  • A-RRAY
  • array defined by .ARRAY, subject to relocation
  • S-TRUCT
  • structure defined by .STRUCT, not subject to relocation
    If the symbol is of structure (.STRUCT) type, this additional information is saved (the type of the structure, name of the structure, and number of elements of the structure):
    STRUCT_LABEL_TYPE    CHAR (B-YTE, W-ORD, L-ONG, D-WORD)
    STRUCT_LABEL_LENGTH  WORD
    STRUCT_LABEL_NAME    ATASCII
    STRUCT_LABEL_REPEAT  WORD
    
    If the symbol is of array (.ARRAY) type, this additional information is saved (maximum element index, declared element type):
    ARRAY_MAX_INDEX  WORD
    ARRAY_TYPE       CHAR (B-YTE, W-ORD, L-ONG, D-WORD)
    
    If the symbol is of procedure (.PROC) type, this additional information is saved, regardless of whether the procedure does or does not declare parameters:
    PROC_CPU_REG  BYTE (bits 00 - regA, 01 - regX, 10 - regY)
    PROC_TYPE     BYTE (D-EFAULT, R-EGISTRY, V-ARIABLE)
    PARAM_COUNT   WORD
    

    .REG symbols of the procedure are then included, of PARAM_COUNT count:

    PARAM_TYPE    CHAR (B-YTE, W-ORD, L-ONG, D-WORD)
    ...
    ...
    

    .VAR symbols of the procedure are included next along with their names, where PARAM_COUNT specifies the total length of the data:

    PARAM_TYPE    CHAR (B-YTE, W-ORD, L-ONG, D-WORD)
    PARAM_LENGTH  WORD
    PARAM_NAME    ATASCII
    ...
    ...
    
    HEADER always set to $FFED
    LENGTH number of symbols stored in the update block
    TYPE type of symbol data: B-YTE, W-ORD, L-ONG, D-WORD
    LABEL_TYPE symbol type: V-ARIABLE, C-ONSTANT, P-ROCEDURE, A-RRAY, S-TRUCT
    For type P, additional stored information: PROC_CPU_REG, PROC_TYPE, PARAM_COUNT, PARAM_TYPE
    For type A, additional stored information: ARRAY_MAX_INDEX, ARRAY_TYPE
    For type S, additional stored information: STRUCT_LABEL_TYPE, STRUCT_LABEL_LENGTH, STRUCT_LABEL_NAME, STRUCT_LABEL_REPEAT
    LABEL_LENGTH public symbol name length in bytes
    LABEL_NAME public symbol name stored as ATASCII
    ADDRESS address assigned to the symbol in the relocatable .RELOC block. This value is relocated by adding its current assembly address.
    PROC_CPU_REG information about the .REG CPU register usage records for a procedure
    PROC_TYPE type of procedure:
  • D-EFAULT default type: parameters passed using MADS software stack
  • R-EGISTRY: procedure parameters passed using CPU registers (.REG)
  • V-ARIABLE: procedure parameters passed by variables (.VAR)
  • PARAM_COUNT information about the number of register-passed parameters (.REGs) or total length of type and name data for variable-passed parameters (.VARs)
    PARAM_TYPE parameter types, recorded using the characters 'B', 'W', 'L', 'D'
    PARAM_LENGTH parameter name length (.VAR)
    PARAM_NAME parameter name coded as ATASCII (.VAR)


    Linking (.LINK)

     .LINK 'filename'
    
    The directive .LINK requires as a parameter the filename of the file to link. Only Atari DOS files are accepted, not SDX files.

    If the file load address is different than $0000, it means that the file does not contain relocatable code, but may include update blocks for external and public symbols. The .LINK directive accepts files at any address, but only those starting at $0000 are subject to relocation. More information on how to construct such a file is included in the section Relocatable blocks (.RELOC).

    The .LINK directive allows linking of relocatable and non-relocatable code. MADS automatically relocates the file based on all three types of update blocks (ADDRESS, EXTERNAL, PUBLIC).

    There is no limit to the address at which a file can be relocated.

    If a block being relocated requires the MADS software stack, the labels @STACK_POINTER, @STACK_ADDRESS, and @PROC_VARS_ADR are automatically updated based on the .RELOC block header. It is necessary that the main program and the .RELOC blocks operate on the same software stack.


    MNEMONICS

    Available 6502 opcodes

       LDA   LDX   LDY   STA   STX   STY   ADC   AND  
       ASL   SBC   JSR   JMP   LSR   ORA   CMP   CPY  
       CPX   DEC   INC   EOR   ROL   ROR   BRK   CLC  
       CLI   CLV   CLD   PHP   PLP   PHA   PLA   RTI  
       RTS   SEC   SEI   SED   INY   INX   DEY   DEX  
       TXA   TYA   TXS   TAY   TAX   TSX   NOP   BPL  
       BMI   BNE   BCC   BCS   BEQ   BVC   BVS   BIT  
    
    A mnemonic extension can be placed after a dot '.' for LDA, LDX, LDY, STA, STX, and STY:
       .b or .z                BYTE
       .a or .w or .q   WORD
    
    e.g.:
       lda.w $80   ; AD 80 00
       lda   $80   ; A5 80
    

    Available illegal 6502 opcodes

       ASO   RLN   LSE   RRD   SAX   LAX   DCP   ISB
       ANC   ALR   ARR   ANE   ANX   SBX   LAS   SHA
       SHS   SHX   SHY   NPO   CIM
    

    Available 65816 opcodes

    Of course, all 6502 opcodes are available, as well as:
       STZ   SEP   REP   TRB   TSB   BRA   COP   MVN  
       MVP   PEA   PHB   PHD   PHK   PHX   PHY   PLB  
       PLD   PLX   PLY   RTL   STP   TCD   TCS   TDC  
       TSC   TXY   TYX   WAI   WDM   XBA   XCE   INA
       DEA   BRL   JSL   JML
    
    It is possible to use XASM-style a:, z:, and r: mnemonic extensions:
     XASM        MADS
     lda a:0     lda.a 0
     ldx z:0     lda.z 0
    
     org r:$40   org $40,*
    
    Mnemonic extensions can be placed after a dot ('.') for LDA, LDX, LDY, STA, STX, and STY:
       .b or .z                BYTE
       .a or .w or .q   WORD
       .t or .l                TRIPLE, LONG (24bit)
    
    e.g.:
       lda.w #$00   ; A9 00 00
       lda   #$80   ; A9 80
    

    The following commands cannot have their operand given in absolute addressing form (some assemblers do not require the '#' character, but MADS requires it):

    #$xx

       SEP   REP   COP
    

    #$xxxx

       PEA
    

    Another exception is long indirect addressing mode, which is represented by square brackets [ ]. These brackets are used to group subexpressions, but if the assembler encounters the character '[' first it is interpreted as the start of long indirect addressing, and if 65816 mode is not enabled a Illegal adressing mode results. To "trick" the assembler, place the character '+' before the '['.

     lda [2+4]     ; lda [6]
     lda +[2+4]    ; lda 6
    

    CPU DETECTION

    Detecting the 6502 and 65816 CPUs

    This example is taken from
    http://www.s-direktnet.de/homepages/k_nadj/cputest.html. The program is able to detect the presence of the following microprocessors: 6502, 65C02, and 65816.
    /*
    
    How to detect on which CPU the assembler code is running
    
    (This information is from Draco, the author of SYSINFO 2.0)
    
    You can test on plain 6502-Code if there is a 65c816 CPU, the 16-Bit processor avaible
    in some XLs as a turbo-board, avaible. Draco told me how to do this:
    
    First we make sure, whether we are running on NMOS-CPU (6502) or CMOS (65c02,65c816).
    I will just show the "official" way which doesn`t uses "illegal opcodes":
    
    */
    
     org $2000
    
     opt c+
    
    DetectCPU
    
     lda #$99
     clc
     sed
     adc #$01
     cld
     beq DetectCPU_CMOS
    
    DetectCPU_02
    
     ldx #<_6502
     ldy #>_6502
     jsr $c642
    
     lda #0
     rts
    
    DetectCPU_CMOS
    
     lda #0
     rep #%00000010		;reset Z bit
     bne DetectCPU_C816
    
    DetectCPU_C02
    
     ldx #<_65c02
     ldy #>_65c02
     jsr $c642
    
     lda #1
     rts
    
    DetectCPU_C816
    
     ldx <_65816
     ldy >_65816
     jsr $c642
    
     lda #$80
     rts
    
    _6502   dta c'6502',$9b
    _65c02  dta c'65c02',$9b
    _65816  dta c'65816',$9b
    

    The next CPU detection example is limited to distinguishing a 6502 from a 65816 microprocessor. The program instructions are read differently by a 6502 than by a 65816. A 6502 executes 'inc @' and a 'nop' instead of 'xba' followed by 'sbc #'. With this "transparency" we can be assured that the program does not perform illegal operations and correctly recognizes the correct CPU. The idea for this concise and very clever test comes from Ullrich von Bassewitz.
     org $2000
    
     opt c+                 ; 65816 enabled
    
     lda #0
     
     inc @                  ; increment accumulator
     
     cmp #1
     bcc cpu6502
    
    ; ultimate test for 65816 presence
    
     xba           ; put $01 in B accu
     dec @         ; A=$00 if 65C02
     xba           ; get $01 back if 65816
     inc @         ; make $01/$02
     
     cmp #2
     bne cpu6502
    
    cpu65816
    
     ldx <text65816
     ldy >text65816
     jsr $c642
     rts
     
    cpu6502
    
     ldx <text6502
     ldy >text6502
     jsr $c642
     rts
    
    text6502  dta c'6502',$9b
    text65816 dta c'65816',$9b
    

    MEMORY BANKS

    For probably anyone who has ever worked with the 8-bit Atari architecture, the term "memory bank" is associated with extended memory, divided into 16KB size banks, and switched in the address range <$4000..$7FFF>.

    MADS can interpret banks this way (option OPT B+,
    Hardware memory banks), but by default they are interpreted as virtual banks (option OPT B-, Virtual memory banks).

    The following pseudo commands apply to banks:
     LMB #value
     NMB
     RMB
    

    LMB # (Load Memory Bank)

    Sets the MADS bank counter to a value in the range <$00..$FF> (BANK = value):
     lmb #0
     lmb #bank
     lmb #5 , $6500      ; only with OPT B+
    

    NMB (Next Memory Bank)

    Increments the MADS bank counter (BANK = BANK + 1).
     nmb
     nmb  $6500          ; only with OPT B+
    

    RMB (Reset Memory Bank)

    Resets the MADS bank counter (BANK = 0).
     rmb
     rmb $3500           ; only with OPT B+
     rmb $8500           ; only with OPT B+
    

    During assembly, MADS assigns the current bank counter value to each newly defined label. The programmer can affect the value of the bank counter through pseudo commands.

  • Labels assigned with the MADS bank counter =0 are global.
  • Labels assigned with the MADS bank counter >0 are local.


    Virtual memory banks (OPT B-)

    In MADS, the term "virtual memory bank" refers to any area designated by a newly defined label set to the current value of the bank counter (the default bank counter is zero). That is, a virtual memory bank is not necessary a memory area in the range <$4000..$7FFF>, but each label presents a code area of the program which has been assigned a code (bank counter value) in the range <$00..$FF> with appropriate pseudo-commands for use by the programmer (NMB, RMB, LMB).

    The exceptions are .RELOC blocks, where the bank counter cannot be changed manually and is automatically updated by MADS, incrementing it for each instance of the .RELOC directive. Bank counter values are in the range <$0001..$FFF7>.

    The programmer can read the bank counter value associated with a label using the equal operator '=':
    label
    
     ldx #=label
    
    In this example, the X CPU register is set to the bank counter value associated by MADS with the label LABEL.

    Another useful operator is the colon (':') placed at the beginning of the label name, which causes MADS to allow references to labels outside of the area specified by the current MADS bank counter. Sometimes this may cause problems, such as if there is more than one label with the same name in different local scopes or in areas with a different virtual bank number.
     lmb #5
    
    label5
     nop
    
     lmb #6
    
    label6
     nop
    
     lda :label5
    
    In this example, without the operator ':' at the beginning of the label name in the instruction 'lda :label5' the error ERROR: Undeclared label LABEL5 (BANK=6) would result.

    Virtual memory banks can be used to index an array containing values for the PORTB register. This is the main use of the option OPT B+.


    Hardware memory banks (OPT B+)

    This mode of operation can be called "bank sensitive".

    Hardware banks are an extension of virtual memory banks and are understood by MADS as expanded memory banks in the range <$4000..$7FFF>. The pseudo commands NMB, RMB, and LMB are extended to call the macro @BANK_ADD, which can be found in ..\EXAMPLES\MACROS\.

    In this mode of operation, MADS requires the definitions for the following macros:
     @BANK_ADD
     @BANK_JMP
    
    and requires label definitions with the names:
    @TAB_MEM_BANKS
    @PROC_ADD_BANK
    
    The @TAB_MEM_BANKS label specifies the address of an array with values to write to the PORTB register for switching extended memory banks. You can take advantage of pre-written expanded memory bank detection routines included with MADS, in ..\EXAMPLES\PROCEDURES\@MEM_DETECT.ASM.

    The label @PROC_ADD_BANK is used by the macro @BANK_ADD and defines the address of the code for switching extended memory banks.

    The programmer can read the bank counter value associated with a label using the '=' operator:
    label
    
     ldy #=label
    
    In this example, the Y register is set to the memory bank value associated with the label LABEL by MADS.

    If the MADS bank counter = 0:
  • program code must be placed outside of <$4000..$7FFF>
  • newly defined labels in this area are global
  • all defined labels can be accessed without limitation, regardless of bank number
  • jumping into a bank is possible using the macro @BANK_JMP (..\EXAMPLES\MACROS\@BANK_JMP.MAC); the parameter for this macro does not have to be preceded by the ':' operator

    If the MADS bank counter > 0:
  • program code must be within <$4000..$7FFF>
  • newly defined labels in this area are local
  • only global labels and labels within the current bank can be accessed
  • the pseudo-commands LMB and NMB will call the macro @BANK_ADD, which creates a new bank with the MADS extended memory bank counter and sets a new assembly address (defaults to $4000)
  • the pseudo-command RMB resets the MADS memory bank counter and sets a new assembly address outside of the bank (defaults to $8000)
  • jumping to another bank is possible using the macro @BANK_JMP (..\EXAMPLES\MACROS\@BANK_JMP); the parameter for this macro does not have to be preceded by the ':' operator

    An example of the use of MADS bank sensitive mode can be found in the file ..\EXAMPLES\XMS_BANKS.ASM. In this example, the program code is located in two different extended memory banks and runs as if it were a single program.


  • HISTORY

    v1.9.5

    - added pseudo-command SET to redefine labels, with a similar effect as temporary labels that begin with '?', e.g.:

    temp set 12
    
         lda #temp
    
    temp set 23
    
         lda #temp
    

    - added ability to force addressing mode in XASM-style ('a:', 'z:'):

     XASM        MADS
     lda a:0     lda.a 0
     ldx z:0     lda.z 0
    

    - added ability to specify a new code relocation address in XASM-style ('r:'):

     XASM        MADS
     org r:$40   org $40,*
    

    - improved performance of '-x Exclude unreferenced procedures' switch; .VAR variables are not allocated for unused procedures
    - extended single-line syntax for :rept loops so that the loop counter can now be used as a parameter :1 (%%1):

    line0
    line1
    line2
    line3
    
    ladr :4 dta l(line:1)
    hadr :4 dta h(line:1)
    

    - added a warning message when unstable illegal 6502 opcodes are used, i.e. CIM
    - added new functionality to pseudo-opcodes RUN and INI to retain the previous assembly address when assembling to $2E0 (RUN), $2E2 (INI)
    - added support for anonymous labels @, @+[1..9] (forward), @-[1..9] (backward); for clarity, their use is limited only to conditional branches no more than 10 instances away:

    @ dex   ---- -------
      bne @+   |  --   |
      stx $80  |   |   |
    @ lda #0   |  --   |
      bne @- ---       |
      bne @-1  ---------
    

    - extended directives #IF and #WHILE to allow arguments declared by .VAR, whereas previously only a variable was allowed:

     .var temp .word
    
     #if temp>#2100
     #end
    
     #if .word temp>#2100
     #end
    

    v1.9.4

    - dodana normalizacja ścieżek dla plików, tak aby działały pod Unixami, znaki '\' zamieniane są na '/'
    - poprawione przekazywanie dyrektyw jako parametrów do procedur i makr, dyrektywy nie były rozpoznawane przy włączonym przełączniku -c (case sensitive)
    - poprawione działanie .USE [.USING]
    - dodana informacja w postaci ostrzeżenia (WARNING) o etykiecie powodującej nieskończoną ilość przebiegów asemblacji (INFINITE LOOP)
    - dodany zapis dwóch bajtów nagłówka FF FF dla pliku zawierającego blok o adresie ładowania $FFFF
    - komentarze po mnemonikach nie wymagających argumentu zostaną potraktowane jako błąd, wyjątkiem jest łączenie rozkazów w stylu xasm poprzez znak ':', np.:

     pla $00          ->  ERROR: Extra characters on line
     pha:pla $00      ->  OK
    

    - rozszerzona składnia makr o możliwość używania parametrów w postaci nazw a nie tylko wartości numerycznych-decymalnych, np.:

    .macro SetColor val,reg
     lda :val
     sta :reg
    .endm
    
    .macro SetColor2 (arg1, arg2)
     lda #:arg1
     sta :arg2
    .endm
    

    - naprawione definiowanie etykiet dla n/w sytuacji, pierwsza etykieta nie zostanie zignorowana

    temp  label = 100
    

    v1.9.3

    - poprawione przetwarzanie bloków .PROC, które w pewnych okolicznościach mogły zostać pominięte podczas asemblacji
    - poprawiony zapis BLK EMPTY dla plików SDX jeśli zastosowaliśmy deklarację takiego bloku przez .DS
    - poprawki dotyczące testowania końca linii
    - dodane dyrektywy .FILESIZE, .SIZEOF jako odpowiednik dotychczasowej dyrektywy .LEN
    - rozszerzona składnia dla pól struktury .STRUCT, np.:

    .struct name
     .byte label0
     .byte :5 label1
     label2 .byte
     label3 :2 .word
    .ends
    

    v1.9.2

    - możliwość określenia adresu dla .ZPVAR = $XX
    - usprawnione odwołania do etykiet wyliczeniowych .ENUM, np. enum_label(field0, field1)
    - dodana możliwość generowania bloku dla symboli zewnętrznych BLK UPDATE EXTRN dla plików DOS-a, poprzednio tylko dla plików .RELOC, np.:

      .extrn vbase .word
      org $2000
      lda #$80
      sta vbase+$5d
    
      blk update extrn
    

    - dodany komunikat błędu "Could not use NAME in this context" w przypadku rozkazów odwołań do bloków .MACRO, .ENUM, .STRUCT
    - poprawiony błąd który uniemożliwiał użycie 'EQU' w nazwie etykiety
    - dodana dyrektywa .CB +byte,....., ostatni bajt ciągu znakowego zapisywany jest w inwersie
    - dodana obsługa segmentów poprzez dyrektywy .SEGDEF, .SEGMENT, .ENDSEG
    - dodana nowa dyrektywa #CYCLE #N generująca kod 6502 o zadanej liczbie cykli N
    - dodana obsługa nielegalnych rozkazów CPU 6502, przykład w pliku ..\examples\test6502_illegal.asm
    - uaktualnione pliki konfiguracyjne dla Notepad++ '..\syntax\Notepad++'
    - poprawiony zapis pliku LST
    - naprawiona alokacja pamięci dla zmiennych strukturalnych, rozszerzona składnia dla .STRUCT

    .struct LABEL
     x,y,z .word     // wiele zmiennych tego samego typu w jednej linii
     .byte a,b
    .ends
    
    .enum type
      a=1,b=2
    .ende
    
    .struct label2
      x type
      type y
    .ends
    

    v1.9.0

    - naprawiony zapis linii z komentarzem /* */ do pliku listingu *.LST, poprzednio takie linie nie były zapisywane
    - poprawka dla etykiet deklarowanych z linii komend -d:label, poprzednio takie etykiety widziane były tylko w pierwszym przebiegu
    - w przypadku addytywności bloków .LOCAL tylko pierwszy adres z takich bloków jest zapisywany
    - poprawki dotyczące parsowania makr, poprzednio etykiety zaczynające się od END mogły zostać zinterpretowane jako pseudo rozkaz END
    - poprawka odczytu dla pustego pliku relokowalnego, poprzednio występował błąd 'Value out of range'
    - poprawki dla .USING (.USE)

    v1.8.8 - 1.8.9

    - uaktualniony silnik duchów programowych ..\EXAMPLES\SPRITES\CHARS o duchy 8x24
    - w przypadku braku podania rozszerzenia pliku i braku istnienia takiego pliku dla ICL 'filename' zostanie domyślnie przyjęte rozszerzenie *.ASM ICL 'filename.asm'
    - poprawione działanie komentarzy /* */ w blokach .MACRO i .REPT
    - usunięty błąd uniemożliwiający poprawną asemblację bloku #IF, #WHILE dla wyrażeń łączonych przez .OR, .AND
    - przełączniki w linii komend mogą być poprzedzone tylko znakiem '-', poprzednio także '/' jednak były problemy z działaniem tego znaku na MacOSX
    - poprawiony zakres działania dyrektywy .USING, dla aktualnej przestrzeni nazw i kolejnych zawierających się w tej przestrzeni nazw

    v1.8.6 - 1.8.7

    - usprawnione rozpoznawanie komentarzy /* */ w wyrażeniach
    - domyślny adres dla .ZPVAR ustawiony na $0080, poprzednio $0000
    - dodana nowa dyrektywa .ELIF jako krótszy odpowiednik dyrektywy .ELSEIF
    - rozszerzone działanie dyrektywy .LEN o możliwość podania jako parametru nazwy pliku, zwracana jest wówczas długość takiego pliku
    - usprawnione działanie dyrektywy .DEF w wyrażeniach warunku .IF (.IFDEF, .IFNDEF)

    v1.8.5

    - dodane makro relokujące moduły RMT ...\EXAMPLES\MSX\RMT_PLAYER_RELOCATOR\
    - dodany test składni dla nie asemblowanych procedur .PROC gdy aktywny jest przełącznik -x "Exclude unreferenced procedures"
    - poprawione działanie przełącznika "-d:label[=value]", podanie wartości dla etykiety jest teraz opcjonalne, domyślnie mads przypisze wartość 1
    - dyrektywy .DS i .ALIGN nie spowodują alokacji zmiennych zdefiniowanych przez .VAR
    - alokacja zmiennych .VAR przed nowym blokiem ORG nie nastąpi jeśli blok ORG znajduje się w bloku .LOCAL lub .PROC
    - poprawione łamanie wierszy znakiem '\' w ciągach ograniczonych nawiasami ()
    - usunięty błąd powodujący relokowanie adresu dla wyrażenia dyrektywy .ERROR (ERT)
    - usunięte zauważone błędy przy parsowaniu parametrów linii komend
    - usunięte zauważone błędy dotyczące optymalizacji długości kodu makro rozkazów MVA, MWA itp.
    - poprawiony kod realizujący zagnieżdżanie bloków .PROC
    - poprawiony kod realizujący działanie pseudo rozkazów warunku IFT ELI ELS EIF
    - dodany komunikat "'#' is allowed only in repeated lines" dla przypadków użycia licznika pętli # (.R) poza pętlą
    - usunięty błąd powodujący błędne alokowanie zmiennych zadeklarowanych przez dyrektywę .VAR podczas wykonywania makra
    - w celu ujednolicenia składni odwołania do etykiet typów wyliczeniowych możliwe są tylko poprzez znak kropki '.', poprzednio także przez '::'
    - możliwe krótsze odwołania do typów wyliczeniowych enum_label(fields), np. :

    .enum typ
     val0 = 1
     val1 = 5
     val2 = 9
    .ende
    
     lda #typ(val0|val2)  ; == "lda #typ.val0|typ.val2"
    

    - rozszerzona składnia dyrektywy .SAV, np.:

     .sav 'filename',offset,length
     .sav 'filenema',length
     .sav [offset] 'filename',offset2,length
     .sav length
     .sav offset,length
    

    - rozszerzona składnia dyrektywy .ARRAY, w przypadku braku podania maksymalnego indeksu tablicy zostanie on obliczony na podstawie ilości wprowadzonych elementów, elementy można wprowadzać bez konieczności poprzedzenia ich indeksem [expression], np.:

    .array temp .byte
     1,4,6                  ; [0..2]   = 1,4,6
     [12] = 9,3             ; [12..13] = 9,3
     [5]:[8] = 10,16        ; [5..6]   = 10,16 ; [8..9] = 10,16
     0,0,\                  ; [14..17] = 0,0,1,1
     1,1
    .enda                   ; 18 elementów, TEMP [0..17]
    

    - dodana możliwość alokacji zmiennej typu strukturalnego przy pomocy dyrektyw .VAR i .ZPVAR, np.:

    .struct Point
     x .byte
     y .byte
    .ends
    
     .var a,b,c Point
     .zpvar Point f,g,i
    

    - dodana możliwość alokacji zmiennej typu wyliczeniowego przy pomocy dyrektyw .VAR i .ZPVAR, np.:

    .enum Boolean
     false = 0
     true = 1
    .ende
    
     .var test Boolean
     .zpvar Boolean test
    

    - dodana możliwość deklaracji pól struktury przy pomocy typów wyliczeniowych, np.:

    .enum EState
      DONE, DIRECTORY_SEARCH, INIT_LOADING, LOADING
    .ende
     
    .struct SLoader
        m_file_start .word
        m_file_length .word
     
        m_state EState
    .ends
    

    v1.8.3 - 1.8.4

    - nowy silnik duchów programowych z minimalnymi wymaganiami pamięci, bez dodatkowych buforów pamięci obrazu ...EXAMPLES\SPRITES\CHARS_NG
    - nowa wersja pakera Huffmana (kompatybilna z Free Pascal Compiler-em, "fpc -MDelphi sqz15.pas") i dekompresora Huffmana SQZ15 ...EXAMPLES\COMPRESSION\SQUASH
    - poprawiony kod generowany dla rozkazów MVP, MVN, PEA, BRA (CPU 65816)
    - dodane nowe rozkazy BRL, JSL, JML (CPU 65816), jako odpowiedniki rozkazów długich skoków BRA, JSR, JMP
    - blok aktualizacji etykiet zewnętrznych (external) został rozszerzony o zapis młodszego i starszego bajtu adresu takiej etykiety
    - poprawione działanie dyrektywy .USE (.USING), działa niezależnie od przestrzeni nazw w której zostanie użyta
    - usunięty błąd, który powodował w pewnych sytuacjach pomijanie asemblacji bloku #IF, #WHILE
    - dodana możliwość definiowania zmiennych poprzez dyrektywę .DS lub pseudo rozkaz ORG przed blokiem .RELOC
    - dodana dodatkowa forma składni dla dyrektywy .VAR, z tym że dla takiego przypadku nie ma możliwości określenia adresu umiejscowienia zmiennych w pamięci

     .VAR .TYPE lab1 lab2 lab3 .TYPE lab4 .TYPE lab5 lab6 ...
    
     .var .byte a,b,c .dword i j
    

    - dodana możliwość definicji pojedyńczych zmiennych typu strukturalnego w krótszy sposób aniżeli dotąd przez DTA

    .struct @point
     x .byte
     y .byte
    .ends
    
    pointA	@point		; pointA dta @point [0] <=> pointA dta @point
    pointB	@point		; pointB dta @point [0] <=> pointB dta @point
    
    points	dta @point [100]
    

    - dodana nowa dyrektywa .ZPVAR umożliwiająca automatyczne przydzielenie miejsca zmiennym na stronie zerowej

     .ZPVAR TYPE label1, label2 label3 = $80	; LABEL1=$80, LABEL2=LABEL1+TYPE, LABEL3=LABEL2+TYPE
     .ZPVAR label4, label5 TYPE			; LABEL4=LABEL3+TYPE, LABEL5=LABEL4+TYPE
    
     .print .zpvar
    

    - poprawione działanie dyrektywy .ERROR i pseudo rozkazu ERT, możliwe jest umieszczenie dodatkowych informacji w wierszu podobnie jak dla .PRINT (.ECHO) np.:

      ERT *>$6000 , 'BUUU przekroczyliśmy zakres pamięci o ' , *-$6000 , ' bajtów'
    

    - dodana możliwość zagnieżdżania bloków procedur .PROC, ten sam kod może być wywoływany z różnymi parametrami np.:

    .proc copySrc (.word src+1) .var
    
     .proc ToDst (.word src+1, dst+1) .var
     .endp
    
    	ldy #0
    src	lda $ffff,y
    dst	sta $ffff,y
    	iny
    	bne src
    
    	rts
    .endp
    
    	copySrc.ToDst #$a080 #$b000
    
    	copySrc #$a360
    

    - dodane nowe dyrektywy .ENUM i .ENDE (.EEND)

    .enum	dni_tygodnia
    
    	poniedzialek = 1
    	wtorek, sroda = 5, czwartek = 7
    	piatek
    	sobota
    	niedziela
    
    .ende
    
    	ift dzien==dni_tygodnia::wtorek
    	.print 'wtorek'
    	eif
    

    - rozszerzona funkcjonalność komentarzy wieloliniowych /* */ o możliwość umieszczania ich gdziekolwiek

     lda #12+ /* komentarz */ 23
    

    - umożliwiona relokacja adresów definiowanych dyrektywą .DEF

     .reloc 
     .def label=*
     lda label
    

    - dodana możliwość użycia znaków { } do oznaczenia bloku (z wyjątkiem bloków .MACRO), znak '{','}' zostaje rozpoznany na początku nowego wiersza, np.:

    #while .word ad+1<=#$bc40+39
    {
    ad	sta $bc40
    
    	inw ad+1
    }
    
    .proc lab
    {
    	.local temp2
    	{
    	}
    
    	.array tab [255] .long
    	{}
    }
    

    v1.8.2

    - zniesione ograniczenie długości pliku dla pseudo rozkazu INS (poprzednio długość wczytywanego pliku ograniczona była do 65536 bajtów)
    - dodany komunikat błędu 'The referenced label ... has not previously been defined properly' w przypadku etykiet, które nie zostały zdefiniowane do końca, np. tylko w pierwszym przebiegu wartością nieokreśloną
    - dodana nowa dyrektywa .ECHO jako odpowiednik dyrektywy .PRINT, dodatkowo informacje generowane przez .PRINT (.ECHO) zapisywane są teraz także w listingu *.LST
    - dodana nowa dyrektywa .ALIGN pozwalająca na wyrównanie do zadanego zakresu pamięci, dodatkowo można określić wartość jaką wypełnić pamięć

      [label] .ALIGN N[,fill]
    

    - dodany nowy przełącznik -U (Warn of unused labels)

    1.8.1

    - rozszerzone działanie znaku backslash '\', umieszczenie go na końcu wiersza oznacza kontynuację aktualnego wiersza od nowego wiersza, np.:

      macro_temp \
      _____________________________________parametr1_________________________________________________\
      _____________________________________parametr2_________________________________________________\
      _____________________________________parametr3_________________________________________________
    
      lda\
      #____________________________________label________________________________________\
      +__________________________________expression___________________________________
    

    - zmienione testowanie niekończącego wywoływania się makr po którym wystąpi błąd 'Infinite loop'
    - naprawiony zapis etykiet do pliku *.LAB, błąd powstał po dodaniu addytywności obszarów LOCAL
    - poprawione działanie pseudo rozkazu SIN (kod zapożyczony z XASM)
    - poprawione rozpoznawanie dyrektyw przy włączonym przełączniku -C (Case sensitive)
    - usprawniony odczyt bloków .REPT (wskazanie prawidłowej linii z błędem) i .MACRO
    - zablokowane użycie .VAR w bloku .REPT
    - umożliwione zagnieżdżanie oraz wielokrotne uruchamianie (poprzez makra) pętli .REPT i :repeat (poprzednio występował komunikat 'Use .REPT directive')
    - umożliwione przekazywanie parametrów do bloku .REPT, np.

    .REPT 10, #
    label:1           ; LABEL0, LABEL1, LABEL2 ... LABEL9
    .ENDR
    
    .REPT 5, $12,$33,$44,$55,$66
     dta :1,:2,:3,:4,:5            ; $12,$33,$44,$55,$66
     dta :5,:4,:3,:2,:1            ; $66,$55,$44,$33,$12
    .ENDR
    

    1.7.9 - 1.8.0

    - poprawiony błąd w opisie przełącznika -F, poprzednio 'Label at first column', prawidłowy opis to 'CPU command at first column'
    - przepisana od nowa obsługa dyrektywy .DS i opcji OPT F+ (dodana możliwość użycia bloków RUN i INI)
    - przepisana od nowa obsługa opcji OPT ?+ (etykiety lokalne w standardzie MAE)
    - dodana możliwość upublicznienia w blokach PUBLIC tablic zadeklarowanych przez .ARRAY oraz deklaracji struktur .STRUCT
    - dyrektywa generująca kod 6502 dla decyzji .TEST zastąpiona została przez dyrektywę #IF, dyrektywa .ENDT przez #END, dodatkowo możliwe jest użycie dyrektywy #ELSE np.:

     # if .byte i>#8 .and .byte i<#200
     # else
           #if .word j = #12
           #end
     # end
    

    - dyrektywa generująca kod 6502 dla iteracji .WHILE zastąpiona została przez dyrektywę #WHILE, dyrektywa .ENDW przez #END, np.:

     lda 20               ->       lda 20
     # while .byte @=20   ->  wait cmp 20
     # end                ->       sne
                          ->       jmp wait
    

    - dyrektywy #IF i #WHILE akceptują dwa dodatkowe operatory '==' i '!='
    - dodana dyrektywa .EXITM jako odpowiednik .EXIT
    - dodana dyrektywa .FI jako odpowiednik .ENDIF
    - dodana dyrektywa .IFDEF jako krótszy odpowiednik dyrektyw .IF .DEF
    - dodana dyrektywa .IFNDEF jako krótszy odpowiednik dyrektyw .IF .NOT .DEF
    - umożliwione zostało definiowanie makr w obszarze procedury .PROC, podsumowując aktualnie dopuszczalne jest zdefiniowanie makra w obszarze .LOCAL i .PROC
    - wystąpienie jakiegokolwiek ostrzeżenia podczas asemblacji nie zmieni kodu wyjścia (exit_code=0), zmiana podyktowana potrzebą kompatybilności z linuxowym makefile
    - ujednolicony sposób deklaracji etykiet lokalnych i globalnych, "białe znaki" przed nazwą etykiety nie wymuszą zdefiniowania takiej etykiety jako globalnej, umożliwi to tylko dyrektywa .DEF :LABEL
    - poprawione makra @CALL.MAC i @CALL_2.MAC, zmienna tymczasowa globalna ?@stack_offset modyfikowana jest teraz przez dyrektywę .DEF
    - rezygnacja z opcji -E (Eat White spaces), aktualnie jest ta opcja zawsze włączona
    - poprawione wyświetlanie numeru linii z błędem w aktualnie wykonywanym makrze
    - skrócone nazwy etykiet tworzonych podczas wykonywania makr (łatwiejsza ich identyfikacja w pliku *.LAB)
    - poprawione działanie opcji OPT H-
    - dodane nowe makro rozkazy INL (increse LONG), IND (increse DWORD), DEL (decrese LONG), DED (decrese DWORD)
    - dodane nowe makro rozkazy CPB (compare BYTE), CPW (compare WORD), CPL (compare LONG), CPD (compare DWORD)
    - usprawnione i rozszerzone działanie dyrektyw #TEST i #WHILE w oparciu o kod generowany przez makro rozkazy CPB, CPW, CPL, CPD, dyrektywy #TEST i #WHILE dla wyrażeń '=#0' i '<>#0' generują najkrótszy kod wynikowy
    - dodana optymalizacja długości generowanego kodu dla makro rozkazów MWA, MWX, MWY
    - dodana nowa opcja OPT R optymalizująca kod makro rozkazów MWA, MWX, MWY, MVA, MVX, MVY ze względu na zawartość rejestrów, np.:

                        opt r-        opt r+
        mva #0 $80  ->  lda #$00  ->  lda #0 
        mva #0 $81  ->  sta $80   ->  sta $80
                        lda #$00  ->  sta $81
                        sta $81   ->
    

    - rozszerzona funkcjonalność dyrektywy .DEF o możliwość przypisania wartości nowo deklarowanej etykiecie, np.:

     .def label = 1
    

    - rozszerzona funkcjonalność dyrektywy .DEF o możliwość zdefiniowania etykiety globalnej niezależnie od aktulnego obszaru lokalnego, np.:

     .def :label
    

    - umożliwiona została addytywność obszarów .LOCAL, tzn. może istnieć wiele obszarów lokalnych o tej samej nazwie, symbole zawarte w takich obszarach należeć będą do wspólnej przestrzeni nazw, np.:

    .local namespace
    
     .proc proc1
     .endp
    
    .endl
    
    .local namespace
    
     .proc proc2
     .endp
    
    .endl
    

    1.7.8

    - dodane dyrektywy .MEND, .PGEND, .REND jako odpowiedniki .ENDM, .ENDPG, .ENDR
    - obecnie deklaracja makra musi kończyć się dyrektywą .ENDM lub .MEND (poprzednio dopuszczalne było użycie dyrektywy .END)
    - poprawiony sposób wykonywania makr dzięki czemu umożliwione zostało wykonanie dyrektywy .ENDL z poziomu wykonywanego makra
    - poprawione zauważone błędy dotyczące starszych bajtów relokowanego adresu oraz bloku aktualizacji symboli publicznych
    - dodana nowa dyrektywa .USING (.USE) pozwalająca określić ścieżkę poszukiwań dla nazw etykiet
    - poprawione działanie dyrektyw .LOCAL, .DEF, których błędne działanie objawiało się w szczególnych przypadkach
    - poprawione działanie makro rozkazów skoków (SNE, RNE itp.), których błędne działanie objawiało się w szczególnych przypadkach
    - rozszerzona składnia dyrektywy .TEST (kod 6502 dla warunku) o dowolną ilość wyrażeń połączonych przez .OR lub .AND (brak możliwości zmiany piorytetu wartościowania przy pomocy nawiasów), np.:

     .test .byte k>#10+1 .or .word j>#100 .and .word j<#105 .or .byte k<=#5
     ...
     ...
     .endt
    

    - rozszerzona składnia dyrektywy .WHILE (kod 6502 dla pętli) o dowolną ilość wyrażeń połączonych przez .OR lub .AND (brak możliwości zmiany piorytetu wartościowania przy pomocy nawiasów), np.:

     .while .byte k>#4 .and .byte k<#39
     ...
     ...
     .endw
    

    1.7.6 - 1.7.7

    - dodany nowy przełącznik -B:ADDRESS umożliwiający asemblacje od zadanego adresu
    - dodany nowa opcja OPT F+- pozwalająca tworzyć bloki ciągłej pamięci (przydatne dla cartów)
    - dodana obsługa parametrów typu .LONG i .DWORD przekazywanych do procedur .PROC typu .VAR (poprzednio akceptowanymi typami parametrów był tylko .BYTE i .WORD)
    - dodana nowa dyrektywa .FL realizująca zapis liczb rzeczywistych REAL w formacie FP Atari, np.:

    pi .fl 3.1415926535897932384626433832795  ; 40 03 14 15 92 65
    tb .fl 0.5 12.34 -2.30 0.00002
    tb .fl 0.5, 12.34, -2.30, 0.00002
    

    - umożliwiony został zapis wartości innych typów niż tylko .BYTE w bloku .ARRAY
    - dodana obsługa typów wielokrotnych dla .STRUCT, poprzednio takie typy były akceptowane jednak pamięć nie była właściwie dla nich rezerwowana, np.:

      .struct test
       x :200 .byte
       y :999 .long
      .ends
    
    buf dta test [0]
    

    - poprawione błędy dotyczące generowania kodu relokowalnego zauważone przez Laoo, np.:

      .reloc
    
       lda temp
    temp .long $aabbcc
    

    - błąd 'Addres relocation overload' wystąpi teraz tylko gdy wyrażenie będzie dotyczyć więcej niż jednej etykiety relokowalnej, poprzednio każde wyrażenie z udziałem etykiety relokowalnej powodowało wyświetlenie tego komunikatu błędu
    - blok aktualizacji symboli plublicznych rozszerzony został o możliwość przekazywania stałych różnych typów B-YTE, W-ORD, L-ONG, D-WORD, poprzednio przekazywanym typem był tylko W-ORD
    - zmienione działanie dyrektywy .VAR w blokach .LOCAL znajdujących się w bloku .PROC, zmienne takie zawsze odkładane są na końcu bloku przed dyrektywą .ENDP, w pozostałych przypadkach na końcu bloku .LOCAL przed dyrektywą .ENDL
    - umożliwiona została relokowalność kodu generowanego przez dyrektywy .WHILE i .TEST
    - poprawione działanie testowania wartości typu .WORD w kodzie generowanym przez dyrektywy .WHILE i .TEST
    - dodana nowa dyrektywa .ADR zwracająca adres etykiety przed zmianą adresu asemblacji
    - dodana nowa dyrektywa .LEN zwracająca długość bloków zdefiniowanych przez .PROC i .ARRAY
    - poprawione działanie operacji dzielenia, mnożenia i modulo, poprzednio błędnie był interpretowany piorytet dla tych operacji
    - komentarze z końca linii nie poprzedzone znakiem komentarza będą powodować wystąpienie błędu 'Unexpected end of line'
    - dodana możliwość przypisania zmiennej pól zdefiniowanych przez strukture, np.:

    @point .struct
           x .byte
           y .byte
           .ends
    
    a @point
    b @point
    c @point
    

    - rozszerzona składnia .STRUCT o możliwość dodania nowych pól bez definiowania nazwy pola, np.:

     .struct @id
      id .word
     .ends
    
     .struct @mem
      @id
      adr .word
     .ends
    

    - rozszerzona składnia makro rozkazu MWA o możliwość użycia adresowania pośredniego strony zerowej postindeksowanego Y, np.:

      mwa ($80),y $a000,x
      mwa $bc40,y ($f0),y
      mwa ($80),y ($82),y
    

    - rozszerzona składnia dyrektywy .EXTRN, obecnie możliwe jest zapowiedzenie większej ilości etykiet różnych typów w jednym wierszu, zapowiedzenie procedury .PROC w takim wierszu musi znajdować się na jego końcu, np.:

      .extrn a,b,c,d .byte  x y z .word  line .proc(.byte x,y) .reg
    

    - rozszerzona składnia dyrektywy .VAR, obecnie możliwe jest zadeklarowanie większej ilości etykiet różnych typów w jednym wierszu oraz przypisanie im adresu od którego zostaną odłożone w pamięci, np.:

      .var x y z .byte bit :2 .dword = $80
    

    - rozszerzona składnia dla parametrów procedur przekazywanych przez zmienne .VAR, możliwe jest podanie przesunięcia np.:

    move .proc (.word src+1,dst+1) .var
    
    src lda $ffff
    dst sta $ffff
    
         .endp
    

    - dodana nowa dyrektywa .NOWARN wyłączająca wyświetlenie ostrzeżenia dla aktualnie asemblowanego wiersza, np.:

     .nowarn PROCNAME
    

    - dodane nowe makro rozkazy PHR, PLR, realizujące odkładanie i zdejmowanie wartości rejestrów z udziałem stosu sprzętowego, np.:

      PHR -> PHA         PLR -> PLA
             TXA                TAY
             PHA                PLA
             TYA                TAX
             PHA                PLA
    

    - dodane nowe makro rozkazy ADB, SBB realizujące dodawanie i odejmowanie wartości typu .BYTE, np.:

     ADB $80 #12 $b000  ->  lda $80
                            clc
                            adc #12
                            sta $b000
    
     SBB #200 $a000     ->  lda #200
                            sec
                            sbc $a000
                            sta $a000
    

    - dodana możliwość użycia składni C dla liczb szestnastkowych, np.:

     lda 0x2000
     ldx #0x12
    
    temp = 0x8000
    

    1.7.5

    - dyrektywa .DS w blokach relokowalnych SDX RELOC i MADS RELOC deklaruje od teraz pusty blok
    - dodany nowy przełącznik -F, który umożliwia umieszczanie rozkazów CPU i pseudo rozkazów od pierwszej kolumny w wierszu
    - przepisane od nowa procedury odczytu bloków .MACRO, .REPT oraz procedura realizująca dzielenie wiersza przy pomocy znaku '\'
    - dodane nowe pseudo rozkazy ADW, SBW realizujące dodawanie i odejmowanie wartości typu WORD dla CPU6502, np.:

      adw hlp #40        ; hlp=hlp+40
      adw hlp #20 pom    ; pom=hlp+20
    

    - rozszerzone działanie dyrektywy .DEF o możliwość zdefiniowania etykiety, np.: .DEF label
    - zwiększona liczba przebiegów dla deklaracji etykiet przez EQU dla pewnych szczególnych przypadków

    1.7.4

    - naprawione działanie dyrektywy .PRINT, dotąd mogła nie wyświetlić wartości etykiet zaczynającej się na literę 'A','B','C','D','E','F','G','H','L','T','V'
    - zablokowane działanie dyrektywy .DS w blokach .RELOC i SDX oraz naprawione jej działanie z instrukcją warunkową .IF (IFT)
    - usprawnione przeszukiwanie ścieżek dostępu -i:path (można odwoływać się do podkatalogów tam zawartych)
    - w przypadku wystąpienia błędów podczas asemblacji wyświetlane są one wszystkie a nie tylko pierwszy z błędów
    - poprawione zauważone błędy, m.in. użycie makra w pliku .RELOC mogło spowodować w pewnych sytuacjach zapis błędnej informacji o relokownych adresach
    - uproszczony został sposób kończenia procedur wykorzystujących stos programowy MADS-a, nie ma potrzeby używania dyrektywy .EXIT, a dyrektywa .ENDP nie powoduje już dodatkowych działań na stosie programowym
    - dodana nowa dyrektywa .SYMBOL jako odpowiednik bloku aktualizacji BLK UPDATE NEW SYMBOL 'SYMBOL', dyrektywę .SYMBOL można użyć w dowolnym miejscu programu
    - dodane automatyczne wywoływanie bloków aktualizacji (ADDRESS, EXTERNAL, PUBLIC, SYMBOL) dla .RELOC i SDX
    - dodane nowe dyrektywy .BY, .WO, .HE, .EN, .SB (zapożyczone z MAE)
    - dodany nowy przełącznik OPT ?- (domyślnie) etykiety ze znakiem zapytania (?labels) traktowane są jako etykiety tymczasowe, OPT ?+ etykiety ze znakiem zapytania (?labels) traktowane są jako lokalne i tymczasowe, nazwą obszaru lokalnego jest ostatnio użyta etykieta bez znaku zapytania
    - dodane dyrektywy .LEND, .PEND, .AEND, .WEND, .TEND, .SEND jako odpowiedniki dyrektyw .ENDL, .ENDP, .ENDW, ENDW, .ENDT, .ENDS
    - dodane nowe dyrektywy .GLOBAL i .GLOBL jako odpowiednik (zamiennik) dyrektywy .PUBLIC
    - dodana optymalizacja skoków warunkowych JEQ, JNE, JPL, JMI, JCC, JCS, JVC, JVS, jeśli jest taka możliwość wybierany jest skok krótki typu BEQ, BNE, BPL, BMI, BCC, BCS, BVC, BVS
    - dodany nowy domyślny separator znak spacji dla przekazywanych parametrów do .PROC, .MACRO, dotąd był to tylko znak przecinka
    - usprawnienia dotyczące przekazywania parametrów do makr i procedur, np. paramatrem makra może być dyrektywa zwracająca wartość wyrażenia lub symbol licznika pętli '#'

      :12 makro #
    

    - dodana możliwość użycia znaku spacji jako separatora dla .VAR, .EXTRN, np.

      .EXTRN a b c d .word
      .VAR i = 1  j = 2 .byte
      .VAR a b c d .byte
    

    - rozszerzona składnia dla .VAR umożliwiająca zaincjowanie zmiennych stałą, np.:

     .var i = 10  j = 12 .byte
     .var a , b = 2 .byte
    

    - dodane nowe dyrektywy .WHILE, .ENDW pozwalające na automatyczne wygenerowanie kodu dla pętli WHILE, np.:

             ldx #$ff
     .while .word adr < #$bc40+40*24
             stx $bc40
        adr: equ *-2
             inw adr
     .endw
    

    - dodane nowe dyrektywy .TEST, .ENDT pozwalające na automatyczne wygenerowanie kodu dla warunku, np.:

     .test .byte (@>=#'a')
      .test .byte (@<=#'z')
          
      .endt
     .endt
    

    1.7.3

    - dodana możliwość zmiany adresu asemblacji .PROC lub .LOCAL bez zmiany adresu ładowania
    - usunięto optymalizację kodu dla makro rozkazów MWA itp., która mogła powodować w szczególnych przypadkach zapętlenie się MADS-a
    - dodane dyrektywy .REG, .VAR pozwalające określić sposób przekazywania parametrów do procedur (.REG przez rejestry CPU, .VAR przez zmienne)
    - dodana dyrektywa .VAR pozwalająca na deklarację zmiennych w blokach .PROC, .LOCAL, zadeklarowane zmiennne są fizycznie odkładane na końcu takiego bloku
    - rozszerzona składnia dla dyrektywy .EXTRN, np. EXTRN label1,label2,label3... TYPE
    - jesli brak deklaracji etykiet dla stosu programowego MADS-a, przyjmowane są domyślne wartości @PROC_VARS_ADR=$0500, @STACK_ADDRESS=$0600, @STACK_POINTER=$FE
    - dodany repeat_counter #, który można używać zamiennie z dyrektywą .R
    - wystapi błąd '^ not relocatable' przy próbie relokacji rozkazu 'lda ^label'
    - dodana obsługa symboli publicznych dla stałych (C-ONSTANT) w blokach PUBLIC
    - poprawiona relokowalnosc dla tablic .ARRAY, danych stworzonych przez .STRUCT, parametrów przekazywanych do procedur przez stała #

    v1.7.2

    - przepisana na nowo obsługa pseudo rozkazów REQ, RNE, RPL, RMI, RCC, RCS, RVC, RVS, SEQ, SNE, SPL, SMI, SCC, SCS, SVC, SVS
    - poprawione działanie dyrektywy .LINK dla bloków o stałych adresach
    - poprawione testowanie słów zarezerwowanych (można używać nazw zarezerwowanych dla 65816 gdy używamy tylko 6502)
    - zmiany w listingu, wyświetla informacje o numerze banku tylko gdy bank > 0
    - dodana obsługa makro rozkazów MWA, MWX, MWY, MVA, MVX, MVY, ADD, SUB, INW, DEW (do ich obsługi nie są już potrzebne makra)

    v1.7.1

    - dodana możliwość używania nazw mnemoników 65816 w trybie pracy 6502, w trybie 65816 wystąpi już błąd Reserved word
    - poprawione działanie pseudo rozkazów skoków SCC, RNE itp. w makrach
    - usprawnione wykonywanie wielu makr rozdzielonych znakiem dwukropka ':'

    v1.7.0

    - usunięty błąd, który powodował zbyt mała liczbę przebiegów asemblacji
    - dodana obsługa pseudo rozkazów JEQ, JNE, JPL, JMI, JCC, JCS, JVC, JVS (makra nie są już potrzebne do ich obsługi)

    v1.6.9

    - rozszerzona składnia dla .ARRAY, .PUT
    - dodany pseudo rozkaz EXT pozwalający na deklaracje etykiety external
    - dodane makra JEQ, JNE, JPL, JMI, JCC, JCS
    - dodane dyrektywy .PAGES i .ENDPG
    - dodana dyrektywa .END zastepujaca inne dyrektywy .END?
    - przełącznik -H zastąpiony został przez -HC (generuje plik nagłówkowy dla CC65)
    - dodany nowy przełącznik -HM generujący plik nagłówkowy dla MADS-a z sortowaniem na etykiety typu CONSTANTS, VARIABLES, PROCEDURES
    - dodana nowa dyrektywa .RELOC generująca kod relokowalny w formacie MADS-a

    v1.6.8

    - dodana nowa dyrektywa .PUT oraz rozszerzona składnia dla dyrektywy .GET (../EXAMPLES/MSX/MPT_PLAYER/MPT_RELOCATOR.MAC , ../EXAMPLES/MSX/TMC_PLAYER/TMC_RELOCATOR.MAC)
    - dodana obsługa pseudo rozkazów XASM-a REQ, RNE, RPL, RMI, RCC, RCS, RVC, RVS, SEQ, SNE, SPL, SMI, SCC, SCS, SVC, SVS
    - dodana możliwość łączenia dowolnej liczby znanych MADS-owi mnemoników przy pomocy znaku ':' (styl XASM-a), np.:

      lda:cmp:req 20
      ldx:ldy:lda:iny label
    

    v1.6.6 - 1.6.7

    - źródło MADS-a kompatybilne z Free Pascal Compiler, po kompilacji możliwe jest jego używanie na innych platformach systemowych, jak np. Linux, Mac OS, OS/2 itp.
    - od teraz MADS sam dobiera odpowiednią liczbę przebiegów asemblacji, przełącznik '/3' nie jest już potrzebny
    - poprawiony i rozbudowany został mechanizm przekazywania parametrów do MADS-a (rozdział 'Przełączniki assemblera')
    - poprawione zostało wywołanie makra w linii rozdzielanej znakiem '\' oraz usprawnione rozpoznawanie i wykonywanie linii rozdzielanych znakami '\'
    - poprawiony błąd, w którym MADS mylił dyrektywę .ENDM z pseudorozkazem IFT
    - poprawione działanie instrukcji warunkowych .ELSEIF, .ELSE
    - poprawione testowanie poprawności instrukcji warunkowych w makrach
    - obsługa procedur .PROC została rozbudowana o nowe makra i mechanizmy, dzięki którym podobna jest w działaniu jak i łatwości użycia do procedur z języków wyższego poziomu
    - dla procedur .PROC z zadeklarowanymi parametrami potrzebna jest teraz dodatkowa deklaracja @PROC_VARS_ADR
    - brak ograniczeń w liczbie parametrów przekazywanych do procedur, jedynym ograniczeniem jest dostępna pamięć
    - dodany nowy przełącznik /d:label=value pozwalający zdefiniować nową etykietę MADS-a z poziomu linii poleceń
    - dodany nowy przełącznik /x "Exclude unreferenced procedures" pozwalający pominąć podczas asemblacji nie używane w programie procedury zadeklarowane dyrektywą .PROC
    - nowa opcja OPT T+ (track sep, rep) śledząca zmiany rozmiaru rejestrów A,X,Y dokonywane przez rozkazy SEP, REP (CPU 65816)
    - nowe biblioteki w katalogu ..\EXAMPLES\LIBRARIES
    - w deklaracji obszaru lokalnego .LOCAL nie jest wymagane podanie nazwy obszaru
    - nowe operatory '-=', '+=', '++', '--' pozwalające zmniejszyć/zwiększyć wartość etykiety tymczasowej, np.:

      ?label --      ->   ?label=?label-1
      ?lab ++        ->   ?lab=?lab+1
      ?temp += 3     ->   ?temp=?temp+3
      ?ofset -= 5    ->   ?ofset=?ofset-5
    

    - rozszerzona o znak przecinka składnia deklaracji parametrów procedur, np.:

     .proc nazwa (.byte a,b,c .word d,e)
     .endp