<--  back   Last regenerated: 2022-04-20 17:31:36 kio

zasm - Z80 Assembler – Version 4.4

CPU instructions

8080 instructions

These are the instructions which are common to the Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 and the Intel 8080.
The 8080 lacks the index registers, the second register Pseudo instructions: defl, set and '='
Labels: SET
set and has no jump relative instructions. Also it has no 0xCB and 0xED prefixed commands.

Note: for the 8080 assembler mnemonics see chapter '8080 assembler instructions'.

nop
ld RR,NN        RR = BC DE HL SP
add hl,RR
inc RR
dec RR
 
ld (bc),a
ld a,(bc)
ld (de),a
ld a,(de)
ld (NN),hl
ld hl,(NN)
ld (NN),a
ld a,(NN)
 
inc R           R = B C D E H L (HL) A
dec R
ld R,N
 
rlca
rrca
rla
rra
daa
cpl
scf
ccf
 
halt
 
ld  R,R         R = B C D E H L (HL) A
                except ld (hl),(hl)
 
add a,R         R = B C D E H L (HL) A
adc a,R
sub a,R
sbc a,R
and a,R
xor a,R
or  a,R
cp  a,R
 
ret
ret CC
jp  NN
jp  CC,NN
call NN
call CC,NN
rst  N
 
pop  RR         RR = BC DE HL AF
push RR         RR = BC DE HL AF
 
add a,N
adc a,N
sub a,N
sbc a,N
and a,N
xor a,N
or  a,N
cp  a,N
 
out (N),a
in a,(N)
 
ex (sp),hl
ex de,hl
di
ld sp,hl
ei

Z80 instructions

List of all Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 opcodes, which were not already present in the Intel 8080. These are all instructions which use the index registers and the second register Pseudo instructions: defl, set and '='
Labels: SET
set, the relative jumps and the 0xCB and 0xED prefixed opcodes.

ex af,af'
exx
djnz DIS
jr  DIS
jr  nz,DIS
jr  z,DIS
jr  nc,DIS
jr  c,DIS
 
rlc R           R = B C D E H L (HL) A
rrc R
rl  R
rr  R
sla R
sra R
srl R
 
bit N,R
res N,R
Pseudo instructions: defl, set and '='
Labels: SET
set N,R   in R,(c) R = B C D E H L A out (c),R   in f,(c)   sbc hl,RR RR = BC DE HL SP adc hl,RR ld (NN),RR ld RR,(NN)   neg retn im N N = 0 1 2 ld i,a ld r,a ld a,i ld a,r reti rrd rld   ldi cpi ini outi ldd cpd ind outd ldir cpir inir otir lddr cpdr indr otdr   ld RR,NN RR = IX IY add hl,RR inc RR dec RR ld (NN),RR ld RR,(NN) pop RR push RR ex (sp),RR ld sp,RR   inc R R = (IX+N) (IY+N) dec R ld R,N add a,R adc a,R sub a,R sbc a,R and a,R xor a,R or a,R cp a,R   ld R1,R2 R1 = B C D E H L A and R2 = (IX+N) (IY+N) ld R1,R2 R1 = (IX+N) (IY+N) and R2 = B C D E H L A

Z180 instructions

These are the instructions added in the Command Line Options: --z180
Pseudo instructions: .z80, .z180 and .8080
Z180 / HD64180 cpu.

in0  R,(N)      R = B C D E H L F A
mult RR         RR = BC DE HL SP
out0 (N),R      R = B C D E H L A
otim
otdm
otimr
otdmr
slp
tst  R          R = B C D E H L (HL) A
tst  N
tstio N

Illegal instructions

List of all illegal Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 opcodes. The Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 cpu does not trap undefined opcodes but 'just does something' instead. For many undocumented opcodes it is well known what they do, and sometimes it is something useful.

Undocumented opcodes after a combination of index register plus prefix 0xCB behave differently on different CPU brands.

On CPUs like the Command Line Options: --z180
Pseudo instructions: .z80, .z180 and .8080
Z180 / HD64180 which trap illegal opcodes these instructions cannot be used.

sll R               R = b c d e h l (hl) a
 
out (c),0xFF        for NMOS CPUs
out (c),0           for CMOS CPUs
in  f,(c)
in  (c)             syntax variant
 
inc R               R = xh, xl, yh, yl or syntax variant: ixh, ixl, iyh, iyl
dec R
ld  R,N
add a,R
adc a,R
sub a,R
sbc a,R
and a,R
xor a,R
or  a,R
cp  a,R
 
ld  R1,R2           R1 = b c d e xh xl a  and  R2 = xh or xl
ld  R1,R2           R1 = b c d e yh yl a  and  R2 = yh or yl
ld  R1,R2           R1 = xh or xl  and  R2 = b c d e xh xl a
ld  R1,R2           R1 = yh or yl  and  R2 = b c d e yh yl a
 
--Command Line Options: --ixcbxh, .ixcbxh, _ixcbxh_
--ixcbr2, .ixcbr2, _ixcbr2_

Commands for command line options: --ixcbxh, .ixcbxh, _ixcbxh_
--ixcbr2, .ixcbr2, _ixcbr2_
ixcbr2:   rlc (RR+dis),R RR = ix iy, R = b c d e h l a rrc (RR+dis),R rl (RR+dis),R rr (RR+dis),R sla (RR+dis),R sra (RR+dis),R sll (RR+dis),R srl (RR+dis),R   bit N,(RR+dis),R RR = ix iy, R = b c d e h l a res N,(RR+dis),R Pseudo instructions: defl, set and '='
Labels: SET
set N,(RR+dis),R   --Command Line Options: --ixcbxh, .ixcbxh, _ixcbxh_
--ixcbr2, .ixcbr2, _ixcbr2_

Commands for command line options: --ixcbxh, .ixcbxh, _ixcbxh_
--ixcbr2, .ixcbr2, _ixcbr2_
ixcbxh:   rlc R R = xh xl yh yl or ixh, ixl, iyh, iyl rrc R rl R rr R sla R sra R srl R   bit N,R R = xh xl yh yl or ixh, ixl, iyh, iyl res N,R Pseudo instructions: defl, set and '='
Labels: SET
set N,R

Syntax variants

zasm supports different syntax for some opcodes:

ex  hl,de       ex  de,hl
ex  (sp),RR     ex  RR,(sp)     RR = hl, ix, iy
jp  (RR)        jp  RR
in  R,(c)       in  R,(bc)
out (c),R       out (bc),R      R = b c d e h l (hl) a
in  a,(N)       in a,N
out (N),a       out N,A
rst 0           rst 0
rst 1           rst 8
rst 2           rst 16
rst 3           rst 24
rst 4           rst 32
rst 5           rst 40
rst 6           rst 48
rst 7           rst 56
add a,R         add R           R = b c d e h l (hl) a
adc a,R         adc R               and (ix+dis) (iy+dis)
sub a,R         sub R
sbc a,R         sbc R
and a,R         and R
xor a,R         xor R
or  a,R         or  R
cp  a,R         cp  R

Some variants apply to notation for arguments:

ld  a,N         ld  a,#N
ld  a,(ix+0)    ld  a,(ix)
ld  a,(ix+dis)  ld  a,dis(ix)

Beyond that, zasm provides convenience definitions for compound instructions to increase readability and maintainability by reducing the number of lines in a source files.

Convenience definitions

These are convenience definitions for combinations of real instructions.

Those which are made from illegal opcodes can't be used for the Command Line Options: --z180
Pseudo instructions: .z80, .z180 and .8080
Z180.

All opcodes which do not use the index registers or the 0xCB group can also be used for the 8080.

All these combinations have no side effect.

ld  bc,de
ld  bc,hl
ld  de,bc
ld  de,hl
ld  hl,bc
ld  hl,de
 
ld  bc,ix       ; illegal ...
ld  bc,iy       ; ...
ld  de,ix       ; ...
ld  de,iy       ; ...
ld  ix,bc       ; ...
ld  ix,de       ; ...
ld  iy,bc       ; ...
ld  iy,de       ; ...
 
ld  bc,(ix+dis)
ld  bc,(iy+dis)
ld  de,(ix+dis)
ld  de,(iy+dis)
ld  hl,(ix+dis)
ld  hl,(iy+dis)
 
ld  (ix+dis),bc
ld  (iy+dis),bc
ld  (ix+dis),de
ld  (iy+dis),de
ld  (ix+dis),hl
ld  (iy+dis),hl
 
ld  bc,(hl)
ld  de,(hl)
ld  bc,(hl++)
ld  de,(hl++)
ld  bc,(--hl)
ld  de,(--hl)
 
ld  (hl),bc
ld  (hl),de
ld  (--hl),bc
ld  (--hl),de
ld  (hl++),bc
ld  (hl++),de
 
ld  (--bc),a
ld  (--de),a
ld  (bc++),a
ld  (de++),a
ld  a,(--bc)
ld  a,(--de)
ld  a,(bc++)
ld  a,(de++)
 
ld  R,(hl++)
ld  R,(--hl)
 
rr  bc              ; 0xCB group
rr  de
rr  hl
sra bc
sra de
sra hl
srl bc
srl de
srl hl
rl  bc
rl  de
rl  hl
sla bc
sla de
sla hl
sll bc              ; sll undocumented
sll de              ; sll undocumented
sll hl              ; sll undocumented
 
rr  (hl++)          ; 0xCB group
rrc (hl++)
rl  (hl++)
rlc (hl++)
sla (hl++)
sra (hl++)
sll (hl++)          ; sll undocumented
srl (hl++)
bit N,(hl++)
Pseudo instructions: defl, set and '='
Labels: SET
set N,(hl++) res N,(hl++)   rr (--hl) ; 0xCB group rrc (--hl) rl (--hl) rlc (--hl) sla (--hl) sra (--hl) sll (--hl) ; sll undocumented srl (--hl) bit N,(--hl) Pseudo instructions: defl, set and '='
Labels: SET
set N,(--hl) res N,(--hl)   add (hl++) adc (hl++) sub (hl++) sbc (hl++) and (hl++) or (hl++) xor (hl++) cp (hl++)   add (--hl) adc (--hl) sub (--hl) sbc (--hl) and (--hl) or (--hl) xor (--hl) cp (--hl)

Load/store Quad Registers

since version 4.4.2.

actually, these are not implemented! only usable in '.Run test code and test your expectations: .expect register
Run test code and test your expectations: .expect cc
expect' so far.

Quad registers are combinations of two 16 bit registers BC, DE, HL, SP, IX or IY.
these can also be .expected in #test segments.

ld  bcde,NNNN
ld  bchl,NNNN
ld  bcix,NNNN
etc.
 
ld  debc,(NN)
ld  dehl,(NN)
ld  deix,(NN)
etc.
 
ld  (NN),hlbc
ld  (NN),hlde
ld  (NN),ixiy
etc.
 
push bcde
push dehl
push hlix
etc.

pop bcde
pop dehl
pop hlix
etc.

8080 assembler instructions

NOP
 
LXI R,D16   R = B D H SP
INX R
DAD R
DCX R
 
STAX B
STAX D
LDAX B
LDAX D
 
INR R       R = B C D E H L M A
DCR R
MVI R,D8
 
RLC
RRC
RAL
RAR
SHLD adr
DAA
LHLD adr
CMA
STA adr
STC
LDA adr
CMC
 
MOV R,R         R = B C D E H L M A
                except MOV M,M
HLT
 
ADD R           R = B C D E H L M A
ADC R
SUB R
SBB R
ANA R
XRA R
ORA R
CMP R
 
RET
RNZ
RZ
RNC
RC
RPO
RPE
RP
RM
 
JMP adr
JNZ adr
JZ adr
JNC adr
JC adr
JPO adr
JPE adr
JP adr
JM adr
 
CALL adr
CNZ adr
CZ adr
CNC adr
CC adr
CPO adr
CPE adr
CP adr
CM adr
 
RST N
 
POP R       R = B D H PSW
PUSH R
 
ADI D8
ACI D8
SUI D8
SBI D8
ANI D8
XRI D8
ORI D8
CPI D8
 
OUT D8
IN  D8
XTHL
PCHL
XCHG
DI
SPHL
EI

8080 assembler instructions for Z80 opcodes

This table lists the 8080 assembler syntax for the additional opcodes of the Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 cpu.

They were rarely used, because people quickly switched over to the much more readable Zilog Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 mnemonics. But there were some 8080 assemblers which added the new Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 opcodes using 'their' syntax. It is absolutely not recommended to write new Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 programs using 8080 assembler syntax, not even for writing new 8080 programs. Use Zilog Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 syntax (the default for any Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 assembler) instead.

Most mnemonics are taken from the CROSS manual except the following:
I doubt these were ever used…

RLCR r      CROSS-Doc: used RLC which is already used for RLCA, also deviation from naming scheme
RRCR r      CROSS-Doc: used RRC which is already used for RRCA, also deviation from naming scheme
OTDR        CROSS-Doc: used OUTDR which is a 5 letter word
OTIR        CROSS-Doc: used OUTIR which is a 5 letter word
DADX rr     CROSS-Doc: no opcode for ADD IX,rr
DADY rr     CROSS-Doc: no opcode for ADD IY,rr
PCIX        CROSS-Doc: no opcode for JP IX
PCIY        CROSS-Doc: no opcode for JP IY
INC  r      CROSS-Doc: no opcode for IN r,(c)
OUTC r      CROSS-Doc: no opcode for OUT (c),r
STAR        CROSS-Doc: no opcode for LD R,A
LDAI        CROSS-Doc: no opcode for LD A,I
LDAR        CROSS-Doc: no opcode for LD A,R

Some opcodes were extended to be used with dis(X) and dis(Y) as well.

The new registers I, R were not accessed by name but with dedicated mnemonics.

The index registers were abbreviated X and Y and an access (IX+dis) was written as dis(X).

New mnemonics
8080 syntax     Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 syntax
DJNZ dis djnz dis JRZ dis jr z,dis JRNZ dis jr nz,dis JRC dis jr c,dis JRNC dis jr nc,dis JMPR dis jr dis EXX exx EXAF ex af,af' XTIX ex ix,(sp) XTIY ex iy,(sp) PCIX jp ix PCIY jp iy CCD cpd CCDR cpdr CCI cpi CCIR cpir LDI ldi LDIR ldir LDD ldd LDDR lddr IND ind INDR indr INI ini INIR inir OUTD outd OUTI outi OTDR otdr note: CROSS used OUTDR OTIR otir note: CROSS used OUTIR STAI ld i,a STAR ld r,a LDAI ld a,i LDAR ld a,r IM0 im 0 IM1 im 1 IM2 im 2 RETN retn RETI reti RLD rld RRD rrd NEG neg SPIX ld sp,ix SPIY ld sp,iy SBCD NN ld (NN),bc named acc. to SHLD; note: *not* sbc! SDED NN ld (NN),de "" SSPD NN ld (NN),sp "" SIXD NN ld (NN),ix "" SIYD NN ld (NN),iy "" LBCD NN ld bc,(NN) named acc. to LHLD LDED NN ld de,(NN) "" LSPD NN ld sp,(NN) "" LIXD NN ld ix,(NN) "" LIYD NN ld iy,(NN) "" INC R in r,(c) R = B C D E H L A; note: *not* inc! INP R in r,(c) "" OUTC R out (c),r R = B C D E H L A OUTP R out (c),r "" DADC R adc hl,rr R = B D H SP DSBC R sbc hl,rr R = B D H SP DADX R add ix,rr R = B D X SP DADY R add iy,rr R = B D Y SP RES N,R res n,r N = [0…7]; R = B C D E H L M A dis(X) dis(Y) Pseudo instructions: defl, set and '='
Labels: SET
SET N,R Pseudo instructions: defl, set and '='
Labels: SET
set n,r "" BIT N,R bit n,r "" SLAR R sla r R = B C D E H L M A dis(X) dis(Y) SRLR R srl r "" SRAR R sra r "" RALR R rl r "" RARR R rr r "" RRCR R rrc r "" RLCR R rlc r ""
Existing mnemonics

Existing 8080 mnemonics which now also can be used with index registers

8080 syntax     Command Line Options: --z80
Pseudo instructions: .z80, .z180 and .8080
Targets: #target Z80
Z80 syntax
ADD R add a,r R = B C D E H L M A dis(X) dis(Y) ADC R adc a,r "" SUB R sub a,r "" SBB R sbc a,r "" ANA R and r "" ORA R or r "" XRA R xor r "" CMP R cmp r "" INR R inc r "" DCR R dec r "" MVI R,N ld r,N "" MOV R,R lr r,r ""; M, dis(X) or dis(Y) can only occur on one side DCX R dec rr R = B D H SP X Y INX R inc rr "" LXI R ld rr,NN "" PUSH R push rr R = B D H PSW X Y POP R pop rr ""

Valid HTML   Valid CSS