Skip to content
mkoloberdin edited this page Aug 8, 2021 · 50 revisions

SjASMPlus Documentation

License

SjASMPlus is licensed under zlib license.

About

SjASMPlus is Z80 Assembly Language Cross Compiler. It is available for Linux/Unix/macOS and Windows systems. It is based on SjASM source code by Sjoerd Mastijn (http://xl2s.tk/)

Main Features

  • Z80/R800 documented and undocumented opcodes support

  • Very fast compilation: millions of lines in seconds on modern PCs

  • Code inlining through colon (LD A,C:INC A:PUSH AF:IFDEF FX:LD A,D:ENDIF…)

  • Structures to define data structures in memory more easily (STRUCT pseudo-op)

  • Conditional assembly

  • Macro definitions

  • Local labels

  • User’s messages

  • Temporary labels

  • Special features for ZX-Spectrum computers, clones and emulators

  • Defines and array of defines

  • Fake instructions such as LD HL,DE (LD H,D:LD L,E) and more

  • Source and binary file inclusion

  • Multi-line C-style block comments

  • Multi-file output and file updating

Credits

Special thanks to Sjoerd Mastijn, the author of SjASM.

Aprisobal- main programming, documentation, etc.

Thanks to:

And big thanks to all people, who helped me in development of the compiler!

Feedback

What's new?

See Change Log.

Old SjASMPlus 1.06 log was removed.

Where to get and how to use

Packages

This section is severely outdated

The latest binaries and the source code are available at Github: https://github.com/sjasmplus/sjasmplus

Win32 package has:

  • sjasmplus.exe - the Win32 executable. This is out compiler and we will use it.

  • examples directory - some examples of use

  • documentation directory - documentation in various formats

DOS and FreeBSD versions has same files in their packages.

Linux version you can compile using GCC and Makefile from sources package.

MacOS X version you can compile using XCode package and included Makefile.

Command line

Usage:

sjasmplus [options] sourcefile(s)

Option flags as follows:

-i<path> or -I<path> or --inc=<path>
                         Include path
--lst                    Save listing to <sourcefile1>.lst
--lst=<filename>         Save listing to <filename>
--lstlab                 Enable label table in listing
--sym                    Save symbols list to <sourcefile1>.sym
--sym=<filename>         Save symbols list to <filename>
--exp=<filename>         Save exports to <filename> (see EXPORT pseudo-op)
--labels                 Save symbols(labels) list to <sourcefile1>.lab
                           in format compatible with UnrealSpeccy emulator
--labels=<filename>      Save symbols(labels) list to <filename>
                           in format compatible with UnrealSpeccy emulator
--raw                    Save all output to <sourcefile1>.out
--raw=<filename>         Save all output to <filename> ignoring OUTPUT pseudo-ops
--output-dir=<directory> Write all output files to the specified directory
Note: use OUTPUT,LUA/ENDLUA and other pseudo-ops to control output
Logging:
--nobanner               Do not show startup message
--msg=error              Show only error messages
--msg=all                Show all messages (by default)
--fullpath               Show full path to error file
Other:
--reversepop             Enable reverse POP order (as in base SjASM version)
--dirbol                 Enable processing directives from the beginning of line
--nofakes                Disable fake instructions
--dos866                 Convert from Windows CP1251 to DOS CP866 (Cyrillic)

Source file format

Lines in the source file should have the following form:

Label Operator Operand Comment

All fields are optional. Lines without label should start with whitespace. Operators and operands can be inlined:

      Operator Operand:Operator Operand:Operator Operand... Comment

Comments should start with ; or //. Comment blocks start with /* and end with */.

    ; comment
    // comment
     ld /* comment */ a,80
    /*
     comment
    */
     ld /*
     but this won't be ld a,3!
     */ a,3

Labels

Labels

Labels are case-sensitive and may be of any reasonable length, that is: up to about 70 characters. Label definitions should start on the beginning of a line, but don't have to be followed by a colon (:). Generally labels should start with a letter or an underscore (_), the following characters may be chosen from letters, numbers and the following special symbols: _, ., !, ?, # and @. Note that the . has special meaning, as it is used between module names, labels and local labels. The following are all legal and distinct labels:

    Kip
    KIP
    Kip@@
    MAIN.loop?

It is possible to use mnemonics, pseudo-ops and register names as labels but it is not advisable to do so. Also note that the identifiers defined with the DEFINE pseudo-op use another name space.

Local labels

When there is a module definition (see module pseudo-op) all labels (except those starting with a @) are local to that module. To use a label from outside the module use modulename.labelname, in this example: vdp.Cls Labels starting with a . are also local to the previous non-local label.

    MODULE main
    Main:                           ; main.Main
            CALL SetScreen          ; SetScreen
            CALL vdp.Cls            ; vdp.Cls
    .loop:                          ; main.Main.loop
            LD A,(.event)           ; main.Main.event
            CALL ProcesEvent        ; label not found: main.ProcesEvent
            DJNZ .loop              ; main.Main.loop

        MODULE vdp
    @SetScreen:               ; SetScreen
    .loop                     ; vdp.SetScreen.loop
            RET
    Cls:                      ; vdp.Cls
    .loop                     ; vdp.Cls.loop
            DJNZ .loop        ; vdp.Cls.loop
            RET

        ENDMODULE
    Main.event                ; main.Main.event
        BYTE 0

@-Labels

Labels starting with a @ are not touched by the label processing and used 'as-is'. See SetScreen in the previous example code.

        MODULE xxx
    Label      ; xxx.Label
    .Local     ; xxx.Label.Local
    @Label     ; Label
    .Local     ; xxx.Label.Local => duplicate label error
    @Label2    ; Label2
    .Local     ; xxx.Label2.Local
    @yyy.Local ; yyy.Local
    yyy.Local  ; xxx.yyy.Local

Temporary labels

To keep the number of used labels reasonable it is possible to use numbers as labels. These labels can only be used as labels to jump to. To jump to these labels, use the number followed by an F for forward branches or a B for backward branches. Temporary labels should not be used within macro's.

            ADD A,E
            JR NC,1F
            INC D
    1       LD E,A
    2       LD B,4
            LD A,(DE)
            OUT (152),A
            DJNZ 2B

Constants, expressions and other features

Numeric constants

Numeric constants should always start with a digit or $, # or %. The following formats are supported:

12     decimal
12d    decimal
0ch    hexadecimal
0xc    hexadecimal
$c     hexadecimal
#c     hexadecimal
1100b  binary
%1100  binary
14q    octal
14o    octal

Character and string constants

Character constants are characters surrounded by single quotes. It is possible to use double quotes in some cases, but in general it is better to use single quotes. String constants are characters surrounded by double quotes. The following escape sequences are recognized:

\\ 92
\? 63
\' 39
\" 34
\A 7
\B 8
\D 127
\E 27
\F 12
\N 10
\R 13
\T 9
\V 11

    BYTE "stringconstant"  ;
    BYTE 'stringconstant'  ;with single quotes escape sequences above (\N,\T..) will not work
    LD HL,'hl'
    LD HL,"hl" ; :(
    LD A,"7"   ; :(
    LD A,'8'   ; :)
    LD A,'\E'
    LD A,'"'
    LD A,"'"

Expressions

Expressions are evaluated in 32 bits in this version of SjASMPlus.

$ represents the current program counter. $$ represents the current page in the current slot in the real device emulation mode.

It is possible to use parenthesis ( and ) to override the precedence of the operators. The following operators may be used in expressions:

!     !x       logical not
~     ~x       complement
+     +x       does absolutely nothing :)
-     -x       minus
low   low x    low 8 bits of 16 bit value
high  high x   high 8 bits of 16 bit value
not   not x    logical not

*     x*y      multiplication
/     x/y      division
%     x%y      modulo
mod   x mod y  modulo

+     x+y      addition
-     x-y      subtraction

<<    x<<y     shift left
>>    x>>y     shift right signed
>>>   x>>>y    shift right unsigned
shl   x shl y  shift left
shr   x shr y  shift right signed

<?    x<?y     minimum
>?    x>?y     maximum

<     x<y      less than
>     x>y      greater than
<=    x<=y     equal or less than
>=    x>=y     equal or greater than

=     x=y      equal
==    x==y     equal
!=    x!=y     not equal

&     x&y      bitwise and
and   x and y  bitwise and

^     x^y      bitwise xor
xor   x xor y  bitwise xor

|     x|y      bitwise or
or    x or y   bitwise or

&&    x&&y     logical and

||    x||y     logical or

Assembly language

This version only accepts Z80 mnemonics. There are some additions to what I think is standard Z80:

  • [ and ] can be used in stead of ( and ) for indirections. So LD A,[HL] is the same as LD A,(HL).

  • IN F,(C) and OUT (C),0 and SLL/SLI can be used.

  • IXL (or LX, XL), IYL (or LY, YL), IXH (or HX, XH) and IYH (or HY, YH) registers are supported.

  • Can write code throught colon: ORG 100h:LD A,10:LD B,10:SUB B:RET:IFDEF AA:.....

  • JP HL, JP IX and JP IY may be used instead of JP (HL), etc.

  • EX AF,AF or EX AF or EXA may be used instead of EX AF,AF'.

  • R800's MULUB and MULUW are recognized (but won't work on Z80, of course:)

  • RLC, RRC, RL, RR, SLA, SRA, SLL (SLI), RES, SET undocumented instructions added.

        SET 4,(IX+4),C ; (aka LD C,SET 4,(IX+4)) is LD C,(IX+4) / SET 4,C / LD (IX+4),C
        RRC (IY),A     ; (aka LD A,RRC (IY+0))   is LD A,(IY)   / RRC A   / LD (IY),A
  • PUSH and POP can take register lists:
        PUSH AF,BC  ; push af / push bc
        POP  AF,BC  ; pop  af / pop  bc
  • and all other commands support this.
        LD A,B,B,D,D,H
       /* this is:
         LD A,B
         LD B,D
         LD D,H
       */
       ;or you can write  LD A,B:LD B,D:LD D,H

Fake instructions

Of course the Z80 is only an 8 bit CPU, but sometimes ld hl,de would be nice. SjASMPlus now 'fakes' some instructions like that. This improves the readability of the source, but it might not be the fastest way to get the result. Also possibly some 'new' load instructions do affect the flags in ways you wouldn't expect. Anyway, here's the list:

      rl bc
      rl de
      rl hl
      rr bc
      rr de
      rr hl
      sla bc
      sla de
      sla hl
      sll bc
      sll de
      sll hl
      sli bc
      sli de
      sli hl
      sra bc
      sra de
      sra hl
      srl bc
      srl de
      srl hl

      ld bc,bc
      ld bc,de
      ld bc,hl
      ld bc,ix
      ld bc,iy
      ld bc,(hl)
      ld bc,(ix+nn)
      ld bc,(iy+nn)

      ld de,bc
      ld de,de
      ld de,hl
      ld de,ix
      ld de,iy
      ld de,(hl)
      ld de,(ix+nn)
      ld de,(iy+nn)

      ld hl,bc
      ld hl,de
      ld hl,hl
      ld hl,ix
      ld hl,iy
      ld hl,(ix+nn)
      ld hl,(iy+nn)

      ld ix,bc
      ld ix,de
      ld ix,hl
      ld ix,ix
      ld ix,iy

      ld iy,bc
      ld iy,de
      ld iy,hl
      ld iy,ix
      ld iy,iy

      ld (hl),bc
      ld (hl),de

      ld (ix+nn),bc
      ld (ix+nn),de
      ld (ix+nn),hl

      ld (iy+nn),bc
      ld (iy+nn),de
      ld (iy+nn),hl

      ldi bc,(hl)
      ldi bc,(ix+nn)
      ldi bc,(iy+nn)

      ldi de,(hl)
      ldi de,(ix+nn)
      ldi de,(iy+nn)

      ldi hl,(ix+nn)
      ldi hl,(iy+nn)

      ldi (hl),bc
      ldi (hl),de

      ldi (ix+nn),bc
      ldi (ix+nn),de
      ldi (ix+nn),hl

      ldi (iy+nn),bc
      ldi (iy+nn),de
      ldi (iy+nn),hl

      ldi a,(bc)
      ldi a,(de)
      ldi a,(hl)
      ldi b,(hl)
      ldi c,(hl)
      ldi d,(hl)
      ldi e,(hl)
      ldi h,(hl)
      ldi l,(hl)
      ldi a,(ix+nn)
      ldi b,(ix+nn)
      ldi c,(ix+nn)
      ldi d,(ix+nn)
      ldi e,(ix+nn)
      ldi h,(ix+nn)
      ldi l,(ix+nn)
      ldi a,(iy+nn)
      ldi b,(iy+nn)
      ldi c,(iy+nn)
      ldi d,(iy+nn)
      ldi e,(iy+nn)
      ldi h,(iy+nn)
      ldi l,(iy+nn)

      ldd a,(bc)
      ldd a,(de)
      ldd a,(hl)
      ldd b,(hl)
      ldd c,(hl)
      ldd d,(hl)
      ldd e,(hl)
      ldd h,(hl)
      ldd l,(hl)
      ldd a,(ix+nn)
      ldd b,(ix+nn)
      ldd c,(ix+nn)
      ldd d,(ix+nn)
      ldd e,(ix+nn)
      ldd h,(ix+nn)
      ldd l,(ix+nn)
      ldd a,(iy+nn)
      ldd b,(iy+nn)
      ldd c,(iy+nn)
      ldd d,(iy+nn)
      ldd e,(iy+nn)
      ldd h,(iy+nn)
      ldd l,(iy+nn)

      ldi (bc),a
      ldi (de),a
      ldi (hl),a
      ldi (hl),b
      ldi (hl),c
      ldi (hl),d
      ldi (hl),e
      ldi (hl),h
      ldi (hl),l
      ldi (ix+nn),a
      ldi (ix+nn),b
      ldi (ix+nn),c
      ldi (ix+nn),d
      ldi (ix+nn),e
      ldi (ix+nn),h
      ldi (ix+nn),l
      ldi (iy+nn),a
      ldi (iy+nn),b
      ldi (iy+nn),c
      ldi (iy+nn),d
      ldi (iy+nn),e
      ldi (iy+nn),h
      ldi (iy+nn),l

      ldd (bc),a
      ldd (de),a
      ldd (hl),a
      ldd (hl),b
      ldd (hl),c
      ldd (hl),d
      ldd (hl),e
      ldd (hl),h
      ldd (hl),l
      ldd (ix+nn),a
      ldd (ix+nn),b
      ldd (ix+nn),c
      ldd (ix+nn),d
      ldd (ix+nn),e
      ldd (ix+nn),h
      ldd (ix+nn),l
      ldd (iy+nn),a
      ldd (iy+nn),b
      ldd (iy+nn),c
      ldd (iy+nn),d
      ldd (iy+nn),e
      ldd (iy+nn),h
      ldd (iy+nn),l

      ldi (hl),nn
      ldi (ix+nn),nn
      ldi (iy+nn),nn

      ldd (hl),nn
      ldd (ix+nn),nn
      ldd (iy+nn),nn

      sub hl,bc
      sub hl,de
      sub hl,hl
      sub hl,sp

ldi increases the data pointer after the data access, so LDI A,(HL) is the same as LD A,(HL):INC HL. Likewise, LDD A,(DE) is LD A,(DE):DEC DE.

Real device emulation mode

To enable this mode you must use pseudo-op DEVICE.

In this mode the compiler compiling program to virtual memory (as at MSX's WB-ASS2, ZX-Spectrum's GENS, ZEUS, ALASM etc). After this all you can use new pseudo-ops as SAVEBIN, SAVEHOB, SAVETRD, SAVETAP, PAGE, SLOT, LABELSLIST and use special functions in Lua scripts.

    DEVICE ZXSPECTRUM128
    ;in this device, SLOT 3 enables to current by default.    

    ORG 32768
StartProg:
    JP $

    DEVICE NONE
    ;do something, if you don't want to corrupt virtual
    ;memory with other code, for example, loader of code.
    ;...code...

    ;return to our virtual device:
    DEVICE ZXSPECTRUM128

    SAVESNA "snapshotname.sna",StartProg

    SAVETAP "tapefile.tap",StartProg

Predefined devices:

Device Name Description
NONE Disable real device emulation mode. By default.
PLAIN Plain 64K memory, with no switchable pages.
ZXSPECTRUM48 The same as PLAIN
ZXSPECTRUM128 Has 8 RAM pages (0-7) with size 4000h. Has 4 slots (0-3) of size 4000h, 4 pages (0-3) of size 4000h. Slot 3 (located at 0C000h) set to current by default.
ZXSPECTRUM256 Same as Russian clone Scorpion 256. Has 16 RAM pages (0-15) with size 4000h.
ZXSPECTRUM512 Same as Russian clones ATM Turbo 512 and Pentagon 512. Has 32 RAM pages (0-31) with size 4000h.
ZXSPECTRUM1024 Same as Russian clones ATM Turbo 2 and Pentagon 1024 SL. Has 64 RAM pages (0-63) with size 4000h.

If you want to see other devices you must write to us. See Feedback chapter.

Predefined defines

SjASMPlus has predefined defines.

  • _SJASMPLUS = 1
    IFDEF _SJASMPLUS
      ;code for sjasmplus
    ELSE
      ;code for other compiler
    ENDIF
  • _VERSION = "version"
    IF _VERSION = "1.07"
      ;code for 1.07
    ELSE
      ;code for other version
    ENDIF
  • _RELEASE = releasenumber
    IF _RELEASE = 1 ; 0 - is stable version
      ;code for Release Candidate 1
    ELSE
      ;code for other version
    ENDIF
  • _ERRORS = <number> - Number of errors.

  • _WARNINGS = <number> - Number of warnings.

Pseudo-ops (aka Pseudo-instructions, Directives etc)

Simple example of usage

    .SOMEPSEUDOOP ; or
    SOMEPSEUDOOP  ; or
    somepseudoop

Almost complete list

.<expression> <code>

Repeat <code> <expression> times. Doesn't work in the beginning of line.

 .3        INC A    ;will be compiled to INC A:INC A:INC A
len        EQU 10
 .(12-len) BYTE 0   ;will be compiled to BYTE 0,0
ABYTE <offset> <bytes>

Defines a byte or a string of bytes. The offset is added to each of the following bytes.

    ABYTE 2 4,9    ; Same as BYTE 6,11
    ABYTE 3 "ABC"  ; Same as BYTE "DEF"
ABYTEC <offset> <bytes>

Defines a byte or a string of bytes, where the last byte of the string will have bit 7 set. The offset is added to each of the following bytes.

    ABYTEC 0 "KIP"        ; Same as BYTE "KI",'P'|128
    ABYTEC 1 "ABC",0,"DE" ; Same as BYTE "BC",'D'|128,1,'E','F'|128
ABYTEZ <offset> <bytes>

Defines a byte or a string of bytes, followed by a zero. The offset is added to each of the following bytes.

    ABYTEZ 0 "KIP"        ; Same as BYTE "KIP",0
ALIGN <2,4,8,16,32,64,128,256,512,1024,2048,4096,8192,16384 or 32768>, <byte>

Align fills zero or more byte with <byte> until the new address modulo <expression> equals zero.

    ALIGN         ; => ALIGN 4 - simply align by 4
    ALIGN 2       ; by 2
    ALIGN 2,0     ; + fills memory by zero
ASSERT <expression>

An "assertion failed" error is issued if the expression evaluates to zero.

STACKPOINTER=0D500H
    ASSERT END_OF_PROGRAM < STACKPOINTER
END_OF_PROGRAM
    END
BINARY <filename>[,offset[,length]]

Synonym of INCBIN.

BLOCK <length>[,<fill byte>]

Defines space. Has to be followed by the number of byte to reserve, optionally followed by the value to fill these bytes with.

    BLOCK 500     ; define a block of 500 bytes of zero
    BLOCK 500,0   ; define a block of 500 bytes of zero
    BLOCK 400,-1  ; define a block of 400 bytes of 255
BYTE <bytes>

Defines a byte or a string of bytes. Each value should be between -129 and 256.

    BYTE 0x56
    BYTE 1,-78,'@'
    BYTE "Format C:? ",0h
DB

Synonym of BYTE.

DC

Same as BYTE, but every last character of a string will have bit 7 set.

    DC "kip" ; same as BYTE "ki",'p'|128
DD

Synonym of DWORD.

DEFARRAY <id> <replacements>

Array of DEFINEs

    DEFARRAY myarray 10*20,"A",20,</D,40>,50,70
CNT DEFL 0 ;or CNT=0
    DUP 6
    DISPLAY myarray[CNT]
CNT DEFL CNT+1 ;or CNT=CNT+1
    EDUP
DEPHASE

Synonym of ENT.

DEFB

Synonym of BYTE.

DEFD

Synonym of DWORD.

DEFDEVICE <deviceid>

Sorry, not available yet. If you want to see a new device in SjASMPlus, please write us.

DEFINE <id> <replacement>

The identifier <id> will be replaced with the <replacement>. The replacement could be omitted, in such case it is still possible to check if the identifier was defined with IFDEF or IFNDEF.

    DEFINE str_honderd "Honderd"
    BYTE str_honderd,0             ; BYTE "Honderd",0
DEFM

Synonym of BYTE.

DEFS

Synonym of BLOCK.

DEFW

Synonym of WORD.

DEVICE <deviceid>

Enables real device emulation mode by it identifier.

Predefined devices' identifiers list:

    ; NONE - Turn off real device emulation mode
    ; ZXSPECTRUM48 - ZX-Spectrum 48
    ; ZXSPECTRUM128 - ZX-Spectrum 128
    ; SCORPION256 - Scorpion 256 - exUSSR clone of ZX-Spectrum 128
    ; ATMTURBO512 - ATM-Turbo 512 - exUSSR clone of ZX-Spectrum 128

    ; Disable:
    DEVICE NONE
    ; Enable:
    DEVICE ZXSPECTRUM128
DISP <address>

Set the address in which the part of code should work. PHASE and TEXTAREA are synonyms of DISP. ENT is restore current address. UNPHASE, DEPHASE and ENDT are synonyms of ENT

SCREEN EQU $4000
    ORG $8000
    LD HL,BEGIN
    LD DE,SCREEN
    LD BC,ENDOFPROG-BEGIN
    LDIR
    CALL SCREEN
    DI
    HALT
BEGIN  DISP SCREEN ;code will compile for address $4000, but to the current ORG
MARKA  DEC A
    HALT
    JP NZ,MARKA
    RET
       ENT
ENDOFPROG
DISPLAY <bytes>

This pseudo-op comes from ZX-Spectrum assembler ALASM.

Out to console a string of bytes. Each value should be between -129 and 256. Keys /D, /H and /A set format of output of numbers:

/D - out only in Decimal
/H - out only in Hexadecimal
/A - out both in Hexadecimal and Decimal
    ORG 100h
TESTLABEL:
    ;...some code...
    RET
    DISPLAY "-- Some Program -- by me"
    DISPLAY "TESTLABEL address is:",/A,TESTLABEL
/*  
The following strings will be output to the console:
> -- Some Program -- by me
> TESTLABEL address is:0x100,257
*/
DM

Synonym of BYTE.

DS

Synonym of BLOCK.

DUP <count>

DUP specifies the number of times to generate the statements inside the macro. DUP can be used in macros.

    DUP 3
    NOP
    EDUP
/*this will expand to:
    NOP
    NOP
    NOP
*/
DW

Synonym of WORD.

DWORD

Defines a so called doubleword (32-bit word). Values should be between -2147483649 and 4294967296.

    DWORD 4000h,0d000h
    DWORD 4
DZ

Same as BYTE, but an extra zero will be added at the end.

    DZ 1      ; same as BYTE 1,0
    DZ "kip"  ; same as BYTE "kip",0
EMPTYTRD <filenameoftrdimage>

Useful only for ZX-Spectrum users

Create the empty TRD image for emulators of ZX-Spectrum. See example of SAVETRD.

ENCODING WIN|DOS

Useful only for non-English users (Cyrillic-encodings-specific)

Директива, судя по всему, создана для пользователей Windows и подразумевает что исходники всегда в кодировке 1251. Соответственно, параметр данной директивы относится к желаемой кодировке исходя их вышесказанного, т.е. WIN оставляет текст как есть, а DOS перекодирует Windows CP1251 -> DOS CP866.

It appears that this directive was added for Russian Windows users, therefore it assumes that the source is always ANSI CP1251-encoded and the directive's parameter refers to the desired encoding. So if you use ENCODING DOS, SjASMPlus will automatically convert strings from ANSI/Windows CP1251 to DOS CP866. ENCODING WIN has no effect. Default is WIN.

    ENCODING "WIN"
    DB "тексттекст" ;will be тексттекст
    ENCODING "DOS"
    DB "тексттекст" ;will be ⥪бв⥪бв
END[ EntryPoint]

The assembler will stop at this point. This pseudo-op doesn't work at the beginning of line (with or without the --dirbol option).

The optional EntryPoint parameter may be used by SAVESNA and SAVETAP directives as the default entry point.

ENDLUA

See Lua scripting.

ENDMOD

Synonym of ENDMODULE.

ENDMODULE

To indicate the end of a module (see MODULE), and use the previous module name.

    MODULE M1
A                 ; M1.A
    MODULE M2
A                 ; M2.A
    ENDMODULE
B                 ; M1.B
    ENDMODULE
ENDT

Synonym of ENT.

ENT

Restore current address. See DISP for more information.

EQU

To give a label a value other than the current program counter. = can be used instead of EQU. The label should not already exist.

Label EQU 3
Kip=3
EXPORT label

The named label will be written to the export-file, in the form label: EQU value. This way the export-file can be included in other sources.

DRIE=3
    EXPORT DRIE
FPOS <position>

The FPOS directive makes it possible to set the file position to anywhere in the output file.

In combination with OUTPUT "<filename>",r it is possible to update existing files.

; This example will result in a file with a length of one byte:
    BYTE 0
    FPOS 0
    BYTE 1
    END
INCBIN <filename>[,offset[,length]]

To include a binary file into the output file. The offset and length are optional.

    INCBIN "gfx.scc",7        ; include gfx.scc, skip first 7 bytes
    INCBIN "rantab.com",3,256 ; include 256 bytes from offset 3
    INCBIN gfx.scc ,7         ; note the space between the filename
                              ; and the ',7' here :)
INCHOB <filename>[,offset[,length]]

To include a data from a hobeta file into the outputfile. The offset and length are optional.

    INCHOB "gfx.$c",7        ; include gfx.scc, skip first 7 bytes
    INCHOB "sprs.$c",3,256   ; include 256 bytes from offset 3
    INCHOB gfx.$c ,7         ; note the space between the filename
                             ; and the ',7' here :)
INCLUDE <filename>

To include another source file into the current. Source files can be nested 20 levels deep. If the file cannot be found in the current directory (the current directory is the directory the current file comes from) the file will be searched for in the directories specified at the command line. When angle brackets are used, the command line directories are searched before the current directory.

    INCLUDE <VDP.I>
    INCLUDE MORE.I
    INCLUDE "MORE.I"
INCLUDELUA <filename>

See Lua scripting.

INCTRD <filenameoftrdimage>,<filenameintrdimage>[,offset[,length]]

To include a file from a TRD image into the output file. The offset and length are optional.

    INCTRD "test.trd","mygfx.C" ; include mygfx.C from test.trd
    INCTRD "test.trd","mygfx.C",12 ; include mygfx.C from test.trd,
                                   ; skip first 12 bytes
INSERT <filename>[,offset[,length]]

INSERT is a synonym of INCBIN. See above.

LABELSLIST <filename>

Useful only for ZX-Spectrum Emulator UNREALSPECCY.

Works only in real device emulation mode. See DEVICE.

Save labels list in the following format:

NN:ADDRESS LABELNAME

, where NN denotes RAM page numbers.

    LABELSLIST "x:/somepath/user.l"
LUA [pass]

See Lua scripting.

MEMORYMAP

Not available yet.

MODULE <name>

Labels are to be unique only in the current module. Also note the use of @ to suppress all this label-processing. (The @ is NOT part of the label name though!)

    MODULE xxx
Kip                ; label xxx.Kip
    CALL Kip       ; call xxx.Kip
    CALL yyy.Kip   ; call yyy.Kip
    CALL Kop       ; call xxx.Kop
    CALL @Kop      ; call Kop
    Call @Kip      ; call Kip

    MODULE yyy
Kip                ; label yyy.Kip
@Kop               ; label Kop
@xxx.Kop           ; label xxx.Kop

    MODULE         ; no modulename
Kip                ; label Kip
ORG <address>

Set the program counter to a specific address.

    ORG 100h ; or 0x100, or $100, or #100

    ; useful macro that padding code
    MACRO PADORG addr
         ; add padding
         IF $ < addr
         BLOCK addr-$
         ENDIF
         ORG addr
    ENDM

    MACRO PADORG2 addr
         ; add padding + display warning
         IF $ > addr
           ; no padding
           DISPLAY /L, "Warning! PADORG failed! ", $, " is more than ", addr
         ELSE
           ; add padding
           BLOCK addr-$
         ENDIF
         ORG addr
    ENDM
OUTPUT "<filename>",mode

With OUTPUT it is possible to create multiple files from one source. All following instructions will be assembled to this file.

There are three possible output modes: truncate (overwrite existing files, this is the default), rewind (open and execute FPOS 0) and append (open and leave the file pointer at the end of the file).

    OUTPUT “<filename>”,t  ; truncate (default)
    OUTPUT “<filename>”,r  ; rewind
    OUTPUT “<filename>”,a  ; append
    OUTPUT loader.com
    ORG 100H
    INCLUDE loader.asm
    INCLUDE bios.asm

    OUTPUT bigfile.dat
    ORG 4000H
    INCLUDE main.asm
    ORG 8000H
    INCLUDE data.asm

This will create two files: loader.com and bigfile.dat.

When SjASMPlus is invoked without specifying an output file, there is still one created even when no bytes are output to it. So when the above file is called bigfile.asm, and assembled with the following line:

sjasmplus bigfile.asm

The following files are created:

Bigfile.out  ; file length is zero
Loader.com
Bigfile.dat
PAGE <number>

Works only in real device emulation mode. See DEVICE.

Set the current memory page to current slot.

    PAGE 7 ; set page 7

    ; Save $4000 bytes beginning from $C000 of RAM to file
    SAVEBIN "ram7.bin",$C000,$4000
PHASE

Synonym of DISP.

REPT <count>

Synonym of DUP.

SAVEBIN <filename>,<startadress>,<lengthofcode>

Works only in real device emulation mode. See DEVICE.

Save a block of RAM.

    PAGE 7 ;set 7 page to current slot

    ; Save 4000h bytes starting from address C000h of RAM to file
    SAVEBIN "ram7.bin",$C000,$4000

    ; Save 3000h bytes starting from address 8000h of RAM to file
    SAVEBIN "ram2.bin",$8000,$3000
SAVEHOB <filename>,<filename_in_trdos>,<startadress>,<lengthofcode>

Works only in real device emulation mode. See DEVICE.

Save a block of RAM in Hobeta format.

    PAGE 7 ; set page 7 to current slot

    ; Save 4000h bytes starting from C000h
    SAVEHOB "ram7.$c","myfile1.C",$C000,$4000

    ; Save 3000h bytes starting from 8000h
    SAVEHOB "ram2.$c","myfile2.C",$8000,$3000
SAVESNA <FileName>[,EntryPoint]

Works only in real device emulation mode. See DEVICE.

Save a snapshot for ZX-Spectrum emulators.

The EntryPoint parameter is optional if it's defined by the END directive.

    DEVICE ZXSPECTRUM128
    ORG $8000
START  .... ; some code
    RET
    SAVESNA "game.sna",START ; Save snapshot to file game.sna
                             ; The entry point address is START ($8000)
SAVETAP <FileName>[,EntryPoint]

Works only in real device emulation mode. See DEVICE.

Save a tape file for ZX-Spectrum emulators. Generated tape file supports ZX-Spectrum clones with extended RAM such as ATM Turbo 512 etc.

The EntryPoint parameter is optional if it's defined by the END directive.

    DEVICE ZXSPECTRUM48
    ORG $8000
START  .... ; some code
    RET
    SAVETAP "game.tap",START ; Save tape file to file game.tap
                             ; The entry point address is START ($8000)
SAVETRD <filenameoftrdimage>,<filename_in_trdos>,<startadress>,<lengthofcode>

Work only in real device emulation mode. See DEVICE.

Save a snapshot for ZX-Spectrum emulators.

    EMPTYTRD "test.trd" ;create empty TRD image
    PAGE 7 ;set 7 page to current slot

    ; Save 4000h bytes starting from C000h to a file in a TRD image
    SAVETRD "test.trd","myfile1.C",$C000,$4000

    ; Save 3000h bytes starting from 8000h to a file in a TRD image
    SAVETRD "test.trd","myfile2.C",$8000,$3000
SHELLEXEC <filename>[, <parameters>]

Execute external program <filename> using optional command line <parameters>.

    OUTPUT "mybin.bin"
    ;some code
    IF ((_ERRORS = 0) + (_WARNINGS = 0))
        SHELLEXEC "x:/mydeveloping/bin2tap.exe mybin.bin mytap.tap"
       ; or SHELLEXEC "x:/mydeveloping/bin2tap.exe","mybin.bin mytap.tap"
    ENDIF
SIZE <filesize in bytes>

If the resulting file is less than the given length, as many bytes are added as necessary. See OUTPUT for more.

    SIZE 32768       ; make sure the file will be 32K
SLOT <number>

Works only in real device emulation mode. See DEVICE.

Set current slot. Slots are defined by MEMORYMAP pseudo-op. Use pseudo-op PAGE to change page in the current slot.

    DEVICE ZXSPECTRUM128
    SLOT 3 ; from 0C000h to 0FFFFh
    PAGE 1 ; set page 1 to slot 3
    ORG 0C000h
    ; your program here
    PAGE 2
    INCBIN "somegfx.bin"
    ; ....
TEXTAREA <address>

Synonym of DISP.

UNDEFINE <id>

Removes an identifier defined by DEFINE

    DEFINE Release 1

    IFDEF Release
      DISPLAY "Building release version"
    ENDIF

    UNDEFINE Release

    IFNDEF Release
      DISPLAY "It works!"
    ENDIF

    IFDEF _SJASMPLUS
      DISPLAY "Yes, it's sjasmplus!"
    ENDIF

    UNDEFINE *  ; undefine all identifiers

    IFNDEF _SJASMPLUS
      DISPLAY "It's not sjasmplus??"
    ENDIF
UNPHASE

Synonym of ENT.

WORD <words>

Defines a word. Values should be between -32787 and 65536.

    WORD 4000h,0d000h
    WORD 4,"HA"

Conditional assembly

It may be useful to assemble or not a block of code based on a certain condition.

IF <expression>

If <expression> is non-zero the following lines are assembled until an ELSE or ENDIF.

IFN <expression>

If <expression> is zero the following lines are assembled until an ELSE or ENDIF.

IFDEF <id>

The condition is true if there is an id defined. These are NOT labels.

    IFDEF MSX_LEAN_AND_MEAN
        CALL InitOwnMM
    ELSE
        CALL InitDos2MemMan
    ENDIF
IFNDEF <id>

The condition is true if there isn't an id defined. These are NOT labels.

1   IN A,(0C4H)
    AND 2
    IFNDEF DEBUG
        JR NC,1B
    ENDIF
IFUSED <label>

The condition is true if the specified label was used somewhere in the code. You can create libraries of useful functions using IFUSED pseudo-op:

    OUTPUT "TEST.OUT"

    CALL LABEL3 ; LABEL3 - yes
    LD A,(LABEL1) ; LABEL1 - yes

    IFUSED LABEL1
LABEL1:
    DB 1
    ENDIF

    IFUSED LABEL2
LABEL2:
    DB 2
    ENDIF

    IFUSED LABEL3
LABEL3:
    DB 3
    ENDIF

    IFUSED LABEL4
LABEL4:
    DB 4
    ENDIF

    LD A,LABEL2 ; LABEL2 - yes

    RET

; Output will contain bytes from LABEL1 to LABEL3 (1, 2, 3),
; but won't contain from LABEL4, because this label is not used.

; Alternative syntax:
LABEL5:
    IFUSED ; sjasmplus will use name of previous label, i.e. LABEL5

    ENDIF
IFNUSED <label>

The condition is true if the label was not used anywhere in the code.

ELSE

See IF. If the condition is not true, the else-part is assembled.

ENDIF

Every IF should be followed by an ENDIF.

Macros

The MACRO pseudo-op defines a macro. It should be followed by the name of the macro, optionally followed by the parameters. The following lines will be stored as the macro-body until an ENDM pseudo-op is encountered. Macros have to be defined before their use.

  MACRO ADD_HL_A
    ADD A,L
    JR NC,.hup
    INC H
.hup
    LD L,A
  ENDM

Labels in a macro starting with a dot are local to each macro expansion.

  MACRO WAVEOUT reg, data
    LD A,reg
    OUT (7EH),A
    LD A,data
    OUT (7FH),A
  ENDM

; this macro will make
  WAVEOUT 2,17
; expand to:
  LD A,2
  OUT (7EH),A
  LD A,17
  OUT (7FH),A
  MACRO LOOP
    IF $-.lus<127
      DJNZ .lus
    ELSE
      DEC B
      JP NZ,.lus
    ENDIF
  ENDM

Main
.lus
    CALL DoALot
    LOOP
; This will expand to:
Main
.lus                  ; Main.lus
    CALL DoALot
    DJNZ .lus         ; Main.lus

Angle brackets can be used when the arguments contain commas.

    MACRO UseLess data
      DB data
    ENDM

    UseLess <10,12,13,0>
; expands to:
    DB 10,12,13,0

; use '!' to include '!' and '>' in those strings.

    UseLess <5, 6 !> 3>
; expands to:
    DB 5, 6 > 3

    UseLess <"Kip!!",3>
; expands to:
    DB "Kip!",3

Structures

Structures can be used to define data structures in memory more easily. The name of the structure is set to the total size of the structure.

Using

A structure definition starts with: STRUCT <name>,[<initial offset>] and ends with ENDS.

Structure definitions are local to the current module, but, as with labels, @ can be used to override this.

Lines between STRUCT and ENDS should have the following format:

membername pseudo-operation operands

All fields are optional. Lines without label should start with whitespace.

Instructions

Between the STRUCT and ENDS pseudo-instructions the following instructions can be used:

BYTE [<defaultvalue>]

To define a one byte member. The defaultvalue is used when no initialization value is given when the structure is declared. (DB and DEFB may be used instead of BYTE).

WORD [<defaultvalue>]

To define a two byte member. The defaultvalue is used when no initialization value is given when the structure is declared. (DW and DEFW may be used instead of WORD).

D24 [<defaultvalue>]

To define a three byte member. The defaultvalue is used when no initialization value is given when the structure is declared.

DWORD [<defaultvalue>]

To define a four byte member. The defaultvalue is used when no initialization value is given when the structure is declared. (DD and DEFD may be used instead of WORD).

BLOCK <length>[,<fillbyte>]]

To define an member of the specified number of bytes. (#, DS and DEFS may be used instead of WORD).

ALIGN [<expression>]

To align the offset. If the expression is omitted, 4 is assumed. (## May be used instead of ALIGN).

<structure name> [<init values>]

It is possible to nest structures, and give new defaults for the BYTE and WORD members.

Examples

    STRUCT SCOLOR
RED BYTE 4
GREEN   BYTE 5
BLUE    BYTE 6
    ENDS

This is identical to:

SCOLOR      EQU 3 ; lenght
SCOLOR.RED  EQU 0 ; offset
SCOLOR.GREEN    EQU 1 ; offset
SCOLOR.BLUE EQU 2 ; offset

    STRUCT SDOT
X   BYTE
Y   BYTE
C   SCOLOR 0,0,0 ; use new default values
    ENDS

This is identical to:

SDOT        EQU 5 ; length
SDOT.X      EQU 0 ; offset
SDOT.Y      EQU 1 ; offset
SDOT.C      EQU 2 ; offset
SDOT.C.RED  EQU 2 ; offset
SDOT.C.GREEN    EQU 3 ; offset
SDOT.C.BLUE EQU 4 ; offset

    STRUCT SPOS,4
X   WORD
Y   BYTE
    ALIGN 2
AD  WORD
    ENDS

This is identical to:

SPOS    EQU 10 ; length
SPOS.X  EQU  4 ; offset
SPOS.Y  EQU  6 ; offset
SPOS.AD EQU  8 ; offset

When a structure is defined it is possible to declare labels with it:

COLOR SCOLOR

This is identical to:

COLOR
COLOR.RED   BYTE 4
COLOR.GREEN BYTE 5
COLOR.BLUE  BYTE 6

Note the default values.

Or without label:

COLORTABLE
    SCOLOR 0,0,0
    SCOLOR 1,2,3
    SCOLOR ,2
    ; etc.

This is identical to:

COLORTABLE
    BYTE 0,0,0
    BYTE 1,2,3
    BYTE 4,2,6
    ; etc.

DOT1 SDOT 0,0, 0,0,0     ; or 0,0,0,0,0 or {0,0,{0,0,0}}

Only BYTE and WORD members can be initialized.

The resulting labels can be used as any other label:

    ld b,(ix+SCOLOR.RED)
    ld a,(COLOR.GREEN)
    ld de,COLOR
    ; etc.

Warning

Do not use the offset labels in indirections like:

    LD A,(SDOT.X)

This will conflict with further 'improvements' ;-)

If this is absolutely necessary (why?) use something like this:

   LD A,(+SDOT.X)
Clone this wiki locally