Difference between revisions of "Z80"

From CPCWiki - THE Amstrad CPC encyclopedia!
Jump to: navigation, search
(Manuals)
(Oddities)
Line 2,055: Line 2,055:
 
* While the syntax of ADD, ADC and SBC instructions all explicitely mention the A register, the SUB instruction does not mention it
 
* While the syntax of ADD, ADC and SBC instructions all explicitely mention the A register, the SUB instruction does not mention it
 
* The 16-bit commands ADD HL,ss, ADC HL,ss and SBC HL,ss exist but not the command SUB HL,ss
 
* The 16-bit commands ADD HL,ss, ADC HL,ss and SBC HL,ss exist but not the command SUB HL,ss
 +
* The NOP instruction takes 4 cycles. This is the minimum amount of cycles an instruction can take.
  
 
<br>
 
<br>

Revision as of 03:46, 4 September 2024

Zilog Z80A

The Z80 is an 8-bit microprocessor designed by Zilog founder and CEO Federico Faggin, first released in July 1976. It is the CPU used in the Amstrad CPC computers.

The Z80/Z80A was a very popular microprocessor, used in a wide range of applications, from early gaming consoles like the ColecoVision or the Sega Master System to personal computers like the ZX Spectrum and the MSX.

It was even used in the MegaDrive as the sound CPU and in the Commodore C128 as a secondary processor in order to achieve CP/M compatibility.

Description

The Z80 microprocessor is an 8-bit CPU with a 4-bit ALU and a 16-bit address bus capable of direct access to 64KB of memory space. The Z80 is a little-endian CPU, meaning it stores 16-bit values with the least significant byte first, followed by the most significant byte. It has a language of 252 root instructions and with the reserved 4 bytes as prefixes, access to an additional 308 instructions. The Z80 was modelled after the Intel 8080 and contains the seventy-eight 8080 opcodes as a subset to its language.

While not in the same league as the Intel 80x86 or the Motorola 68000 series, the Z80 is extremely useful for low cost control applications. One of the more useful features of the Z80 is the built-in refresh circuitry for ease of design with DRAMs.

The Z80 has about 8500 transistors. It comes in a 40-pin DIP package. It has been manufactured in A, B, and C models, differing only in maximum clock speed. It also has been manufactured as a stand-alone microcontroller with various configurations of on-chip RAM and EPROM.


Part numbers used in the Amstrad CPC during its lifetime

The Z80 CPU has been manufactured by others, and various Z80s have been used in the construction of the CPC during its lifetime.

  • SGS Z8400AB1
  • ST Z8400AB1
  • ZILOG Z8400APS
  • ZILOG Z0840004PSC

Zilog ended the production of the Z80 in April 2024. The chip is still available in ample quantities through NOS chip suppliers.


Modern incarnations

Apart from surplus/new Z80-clones that are quite easy to find, many emulations depend on software implementations of the Z80:

  • The T80 is a VHDL implementation of the Z80 and Z80A, finished in 2002 on OpenCores
  • arnold uses InkZ80, written in C++ (apart from the author-designed C simulation)
  • On OpenCores, there is also a Verilog implementation of the Z80.

Zilog itself offers the eZ80 processor, a new, 50MHz design. Kits now have reached a less-than-prohibitive price range and may be available without a business.


Block Diagram

Z80 Block Diagram.gif


Registers

Register Size Description Notes
B, C, D, E, H, L 8-bit General-purpose registers Can form 16-bit pairs: BC, DE, HL
A (Accumulator) 8-bit Main register for arithmetic, logic, and data transfer Most used register
F (Flags) 8-bit
  • bit7 - SF - Sign Flag
  • bit6 - ZF - Zero Flag
  • bit5 - F5 - Undocumented
  • bit4 - HF - Half Carry Flag
  • bit3 - F3 - Undocumented
  • bit2 - PF - Parity Flag (also sometimes used for Overflow)
  • bit1 - NF - Negation Flag (last ALU op was subtract or compare)
  • bit0 - CF - Carry Flag
Flags are affected by most operations.

HF and NF are used in the DAA algorithm.

AF', BC', DE', HL' 16-bit Alternate register set Swappable with primary registers for fast context switching
SP (Stack Pointer) 16-bit Points to top of the stack Used for subroutine calls and interrupt handling
PC (Program Counter) 16-bit Points to the next instruction Automatically increments as instructions execute
IX, IY (Index Registers) 16-bit Used for indexed addressing Can be split into IXH/IXL, IYH/IYL for 8-bit access
I (Interrupt Vector) 8-bit Holds base address for interrupt mode 2 Combined with external data to form an interrupt vector
R (Memory Refresh) 8-bit Increments after each M1 cycle (instruction or prefix fetch) to refresh DRAM Only the lower 7 bits are incremented


Internal state

Register Size Description Notes
IM (Interrupt Mode) 2-bit Specifies the interrupt mode (0, 1, or 2) Controls how interrupts are handled:
  • IM 0: External devices provide an opcode to execute
  • IM 1: Fixed vector at 0038h
  • IM 2: Vector provided by I register and external data
IFF1 1-bit Interrupt enable flag Set when interrupts are enabled, cleared on disable
IFF2 1-bit IFF1 buffer Allows interrupts to be enabled after the instruction following EI
WZ 16-bit Internal temporary register pair. Also known as MEMPTR Used for memory and address calculations
IR (Instruction Register) 8-bit Holds the opcode of the currently executing instruction Internally used, not accessible by the programmer
EIP (Extended Instruction Prefix) 2-bit Holds the prefix for extended instructions (CB, ED, or none) Used for extended instruction sets like bitwise ops
IMP (Indexing Mode Prefix) 2-bit Specifies the indexing mode (DD for IX+d, FD for IY+d, or none for HL) Indicates use of index registers (IX or IY) for memory access


Z80 Instructions

Legend

Notation Meaning Respective Opcode Bits
A 16-bit address or immediate alalalal ahahahah
B Bit number (0..7) bbb = 000..111
C Condition (nz, z, nc, c, po, pe, p, m)

nz: ZF=0, z: ZF=1, nc: CF=0, c: CF=1, po: PF=0, pe: PF=1, p: SF=0, m: SF=1

ccc = 000, 001, 010, 011, 100, 101, 110, 111
D 8-bit signed relative offset dddddddd
E 16-bit relative address dddddddd (E minus address of next instruction)
I Index register (ix, iy) i = 0, 1
J Half index register (ixh, ixl, iyh, iyl) (i, b) = (0, 0), (0, 1), (1, 0), (1, 1)
N 8-bit immediate nnnnnnnn
P 16-bit register pair (bc, de, hl, af) pp = 00, 01, 10, 11
Q 16-bit register (bc, de, hl/ix/iy, sp) qq = 00, 01, 10, 11
R 8-bit general purpose register (a, b, c, d, e, h, l) rrr (or sss) = 111, 000, 001, 010, 011, 100, 101
S Restart address (0x00, 0x08,..., 0x38) sss = 000, 001,..., 111

Flags

  • - = no change
  • + = change by definition (if noted, by the operation marked with '=> flags', otherwise by the only non-single-bit operation):
* S = sign, bit 7 of the result byte (accumulator or high byte for 16-bit operations)
* Z = zero, set if the result is zero (8 or 16-bit value)
* 5 = undocumented, bit 5 of the result byte
* H = half-carry, the carry (theoretical bit 4) of the low nibble of the result byte
* 3 = undocumented, bit 3 of the result byte
* P = parity (set if the result byte has an even number of bits set) or overflow (set when crossing the boundary of the signed range); always specified
* N = negative, set if the previous operation was a subtraction; always specified
* C = carry, the theoretical bit 8 of the result byte
  • 0 = always reset
  • 1 = always set
  • X = change described under Effect
  • P = parity (only for the parity flag)
  • V = overflow (only for the parity flag)
  • A = OR with the respective bit of the accumulator
  • C = set if the counter (bc) is nonzero after decrementing

Miscellaneous

  • () = indirection
  • (()) = I/O port
  • [] = operator precedence (to avoid confusion with indirection)
  • E.B = the Bth bit of the value of expression E
  • * = any bit value (0 or 1)
  • wz = an internal 16-bit register connected to 16-bit operations
  • tmp, tmp2 = temporary storage whose value is thrown away after each instruction

Letter A

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
adc a,R 10001rrr 1 4 (4) + + + + + V 0 + a += R + cf Add with Carry
adc a,J 11i11101 1000110b 2 8 (4,4) + + + + + V 0 + a += J + cf
adc a,N 11001110 nnnnnnnn 2 7 (4,3) + + + + + V 0 + a += N + cf
adc a,(hl) 10001110 2 7 (4,3) + + + + + V 0 + a += (hl) + cf
adc a,(I+D) 11i11101 10001110 dddddddd 5 19 (4,4,3,5,3) + + + + + V 0 + a += (I+D) + cf
adc hl,Q 11101101 01qq1010 4 15 (4,4,4,3) + + + + + V 0 + hl += Q + cf
add a,R 10000rrr 1 4 (4) + + + + + V 0 + a += R Add
add a,J 11i11101 1000010b 2 8 (4,4) + + + + + V 0 + a += J
add a,N 11000110 nnnnnnnn 2 7 (4,3) + + + + + V 0 + a += N
add a,(hl) 10000110 2 7 (4,3) + + + + + V 0 + a += (hl)
add a,(I+D) 11i11101 10000110 dddddddd 5 19 (4,4,3,5,3) + + + + + V 0 + a += (I+D)
add hl,Q 00qq1001 3 11 (4,4,3) - - + + + - 0 + hl += Q
add I,Q 11i11101 00qq1001 4 15 (4,4,4,3) - - + + + - 0 + I += Q
and R 10100rrr 1 4 (4) + + + 1 + P 0 0 a := a AND R Logical AND
and J 11i11101 1010010b 2 8 (4,4) + + + 1 + P 0 0 a := a AND J
and N 11100110 nnnnnnnn 2 7 (4,3) + + + 1 + P 0 0 a := a AND N
and (hl) 10100110 2 7 (4,3) + + + 1 + P 0 0 a := a AND (hl)
and (I+D) 11i11101 10100110 dddddddd 5 19 (4,4,3,5,3) + + + 1 + P 0 0 a := a AND (I+D)

Letter B

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
bit B,R 11001011 01bbbrrr 2 8 (4,4) + + + 1 + P 0 - tmp := R AND [1 << B] Test Bit
bit B,(hl) 11001011 01bbb110 3 12 (4,4,4) + + X 1 X P 0 - tmp := (hl) AND [1 << B],

f5 := wz.13, f3 := wz.11

bit B,(I+D) 11i11101 11001011 dddddddd 01bbb*** 6 20 (4,4,3,5,4) + + X 1 X P 0 - tmp := (I+D) AND [1 << B],

f5 := [I+D].13, f3 := [I+D].11

Letter C

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
call A 11001101 alalalal ahahahah 5 17 (4,3,4,3,3) - - - - - - - - sp -= 2, (sp) := pc, pc := A Call
call C,A 11ccc100 alalalal ahahahah 5/3 17/10 (4,3,4,3,3/4,3,3) - - - - - - - - if C then sp -= 2, (sp) := pc, pc := A Conditional Call
ccf 00111111 1 4 (4) - - A X A - 0 X hf := cf, cf := ~cf Complement Carry Flag
cp R 10111rrr 1 4 (4) + + X + X V 1 + tmp := a - R, f5 := R.5, f3 := R.3 Compare
cp J 11i11101 1011110b 2 8 (4,4) + + X + X V 1 + tmp := a - J, f5 := J.5, f3 := J.3
cp N 11111110 nnnnnnnn 2 7 (4,3) + + X + X V 1 + tmp := a - N, f5 := N.5, f3 := N.3
cp (hl) 10111110 2 7 (4,3) + + X + X V 1 + tmp := a - (hl), f5 := (hl).5, f3 := (hl).3
cp (I+D) 11i11101 10111110 dddddddd 5 19 (4,4,3,5,3) + + X + X V 1 + tmp := a - (I+D), f5 := (I+D).5, f3 := (I+D).3
cpd 11101101 10101001 4 16 (4,4,3,5) + + X + X C 1 - tmp := a - (hl) => flags, bc -= 1, hl -= 1,

f5 := [tmp - hf].1, f3 = [tmp - hf].3

Compare and Decrement
cpdr 11101101 10111001 6/4 21/16 (4,4,3,5,5/4,4,3,5) + + X + X C 1 - cpd, if bc <> 0 and nz then pc -= 2 Compare and Decrement, Repeat
cpi 11101101 10100001 4 16 (4,4,3,5) + + X + X C 1 - tmp := a - (hl) => flags, bc -= 1, hl += 1,

f5 := [tmp - hf].1, f3 = [tmp - hf].3

Compare and Increment
cpir 11101101 10110001 6/4 21/16 (4,4,3,5,5/4,4,3,5) + + X + X C 1 - cpi, if bc <> 0 and nz then pc -= 2 Compare and Increment, Repeat
cpl 00101111 1 4 (4) - - + 1 + - 1 - a := ~a Complement

Letter D

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
daa 00100111 1 4 (4) + + + X + P - X tmp := a,

if nf then

if hf or [a AND 0x0f > 9] then tmp -= 0x06
if cf or [a > 0x99] then tmp -= 0x60

else

if hf or [a AND 0x0f > 9] then tmp += 0x06
if cf or [a > 0x99] then tmp += 0x60

endif,

tmp => flags, cf := cf OR [a > 0x99],

hf := a.4 XOR tmp.4, a := tmp

Decimal Adjust Accumulator
dec R 00rrr101 1 4 (4) + + + + + V 1 - R -= 1 Decrement
dec J 11i11101 0010b101 2 8 (4,4) + + + + + V 1 - J -= 1
dec (hl) 00110101 3 11 (4,4,3) + + + + + V 1 - (hl) -= 1
dec (I+D) 11i11101 00110101 dddddddd 6 23 (4,4,3,5,4,3) + + + + + V 1 - (I+D) -= 1
dec Q 00qq1011 2 6 (6) - - - - - - - - Q -= 1
dec I 11i11101 00101011 3 10 (4,6) - - - - - - - - I -= 1
di 11110011 1 4 (4) - - - - - - - - iff1 := 0, iff2 := 0 Disable Interrupts
djnz E 00010000 dddddddd 4/3 13/8 (5,3,5/5,3) - - - - - - - - b -= 1, if b <> 0 then pc := E Decrement, Jump Non-Zero

Letter E

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
ei 11111011 1 4 (4) - - - - - - - - iff1 := 1, iff2 := 1 after the next instruction Enable Interrupts
ex (sp),hl 11100011 6 19 (4,3,4,3,5) - - - - - - - - (sp) <=> hl Exchange
ex (sp),I 11i11101 11100011 7 23 (4,4,3,4,3,5) - - - - - - - - (sp) <=> I
ex af,af' 00001000 1 4 (4) X X X X X X X X af <=> af'
ex de,hl 11101011 1 4 (4) - - - - - - - - de <=> hl
exx 11011001 1 4 (4) - - - - - - - - bc, de, hl <=> bc', de', hl'

Letter H

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
halt 01110110 1 4 (4) - - - - - - - - wait for interrupt Suspends CPU operation

Letter I

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
im 0 11101101 01*0*110 2 8 (4,4) - - - - - - - - mode 0: execute instruction on bus Set Interrupt Mode
im 1 11101101 01*10110 2 8 (4,4) - - - - - - - - mode 1: execute rst 38h
im 2 11101101 01*11110 2 8 (4,4) - - - - - - - - mode 2: call (i * 256 + byte on bus)
in a,(N) 11011011 nnnnnnnn 3 11 (4,3,4) - - - - - - - - a := ((N)) I/O Input
in R,(c) 11101101 01rrr000 4 12 (4,4,4) + + + 0 + P 0 - R := ((c))
in f,(c) 11101101 01110000 4 12 (4,4,4) + + + 0 + P 0 - tmp := ((c))
inc R 00rrr100 1 4 (4) + + + + + V 0 - R += 1 Increment
inc J 11i11101 0010b100 2 8 (4,4) + + + + + V 0 - J += 1
inc (hl) 00110100 3 11 (4,4,3) + + + + + V 0 - (hl) += 1
inc (I+D) 11i11101 00110100 dddddddd 6 23 (4,4,3,5,4,3) + + + + + V 0 - (I+D) += 1
inc Q 00qq0011 2 6 (6) - - - - - - - - Q += 1
inc I 11i11101 00100011 3 10 (4,6) - - - - - - - - I += 1
ind 11101101 10101010 5 16 (4,5,3,4) + + + X + X X X tmp := ((c)), (hl) := tmp, hl -= 1,

b -= 1 => flags, nf := tmp.7,

tmp2 = tmp + [[c - 1] AND 0xff],

pf := parity of [[tmp2 AND 0x07] XOR b],

hf := cf := tmp2 > 255

I/O Input and Decrement
indr 11101101 10111010 6/5 21/16 (4,5,3,4,5/4,5,3,4) + + + X + X X X ind, if b <> 0 then pc -= 2 I/O Input and Decrement, Repeat
ini 11101101 10100010 5 16 (4,5,3,4) + + + X + X X X tmp := ((c)), (hl) := tmp, hl += 1,

b -= 1 => flags, nf := tmp.7,

tmp2 := tmp + [[c + 1] AND 0xff],

pf := parity of [[tmp2 AND 0x07] XOR b],

hf := cf := tmp2 > 255

I/O Input and Increment
inir 11101101 10110010 6/5 21/16 (4,5,3,4,5/4,5,3,4) + + + X + X X X ini, if b <> 0 then pc -= 2 I/O Input and Increment, Repeat

Letter J

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
jp A 11000011 alalalal ahahahah 3 10 (4,3,3) - - - - - - - - pc := A Jump
jp (hl) 11101001 1 4 (4) - - - - - - - - pc := hl
jp (I) 11i11101 11101001 2 8 (4,4) - - - - - - - - pc := I
jp C,A 11ccc010 alalalal ahahahah 3 10 (4,3,3) - - - - - - - - if C then pc := A Conditional Jump
jr E 00011000 dddddddd 3 12 (4,3,5) - - - - - - - - pc := E Relative Jump
jr nz,E 00100000 dddddddd 3/2 12/7 (4,3,5/4,3) - - - - - - - - if nz then pc := E Conditional Relative Jump
jr z,E 00101000 dddddddd 3/2 12/7 (4,3,5/4,3) - - - - - - - - if zf then pc := E
jr nc,E 00110000 dddddddd 3/2 12/7 (4,3,5/4,3) - - - - - - - - if nc then pc := E
jr c,E 00111000 dddddddd 3/2 12/7 (4,3,5/4,3) - - - - - - - - if cf then pc := E

Letter L

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
ld R1,R2 01rrrsss 1 4 (4) - - - - - - - - R1 := R2 Load
ld R,J 11i11101 01rrr10b 2 8 (4,4) - - - - - - - - R := J
ld J,R 11i11101 0110brrr 2 8 (4,4) - - - - - - - - J := R
ld ixh,ixl 11011101 01100101 2 8 (4,4) - - - - - - - - ixh := ixl
ld ixl,ixh 11011101 01101100 2 8 (4,4) - - - - - - - - ixl := ixh
ld iyh,iyl 11111101 01100101 2 8 (4,4) - - - - - - - - iyh := iyl
ld iyl,iyh 11111101 01101100 2 8 (4,4) - - - - - - - - iyl := iyh
ld R,N 00rrr110 nnnnnnnn 2 7 (4,3) - - - - - - - - R := N
ld R,(hl) 01rrr110 2 7 (4,3) - - - - - - - - R := (hl)
ld R,(I+D) 11i11101 01rrr110 dddddddd 5 19 (4,4,3,5,3) - - - - - - - - R := (I+D)
ld (hl),R 01110rrr 2 7 (4,3) - - - - - - - - (hl) := R
ld (hl),N 00110110 nnnnnnnn 3 10 (4,3,3) - - - - - - - - (hl) := N
ld (I+D),R 11i11101 01110rrr dddddddd 5 19 (4,4,3,5,3) - - - - - - - - (I+D) := R
ld (I+D),N 11i11101 00110110 dddddddd nnnnnnnn 6 19 (4,4,3,5,3) - - - - - - - - (I+D) := N
ld a,(bc) 00001010 2 7 (4,3) - - - - - - - - a := (bc)
ld a,(de) 00011010 2 7 (4,3) - - - - - - - - a := (de)
ld a,(A) 00111010 alalalal ahahahah 4 13 (4,3,3,3) - - - - - - - - a := (A)
ld (bc),a 00000010 2 7 (4,3) - - - - - - - - (bc) := a
ld (de),a 00010010 2 7 (4,3) - - - - - - - - (de) := a
ld (A),a 00110010 alalalal ahahahah 4 13 (4,3,3,3) - - - - - - - - (A) := a
ld i,a 11101101 01000111 3 9 (4,5) - - - - - - - - i := a
ld r,a 11101101 01001111 3 9 (4,5) - - - - - - - - r := a
ld a,i 11101101 01010111 3 9 (4,5) + + + 0 + X 0 - a := i, pf := iff2
ld a,r 11101101 01011111 3 9 (4,5) + + + 0 + X 0 - a := r, pf := iff2
ld Q,A 00qq0001 alalalal ahahahah 3 10 (4,3,3) - - - - - - - - Q := A
ld I,A 11i11101 00100001 alalalal ahahahah 4 14 (4,4,3,3) - - - - - - - - I := A
ld Q,(A) 11101101 01qq1011 alalalal ahahahah 6 20 (4,4,3,3,3,3) - - - - - - - - Q := (A)
ld hl,(A) 00101010 alalalal ahahahah 5 16 (4,3,3,3,3) - - - - - - - - hl := (A)
ld I,(A) 11i11101 00101010 alalalal ahahahah 6 20 (4,4,3,3,3,3) - - - - - - - - I := (A)
ld (A),Q 11101101 01qq0011 alalalal ahahahah 6 20 (4,4,3,3,3,3) - - - - - - - - (A) := Q
ld (A),hl 00100010 alalalal ahahahah 5 16 (4,3,3,3,3) - - - - - - - - (A) := hl
ld (A),I 11i11101 00100010 alalalal ahahahah 6 20 (4,4,3,3,3,3) - - - - - - - - (A) := I
ld sp,hl 11111001 2 6 (6) - - - - - - - - sp := hl
ld sp,I 11i11101 11111001 3 10 (4,6) - - - - - - - - sp := I
ldd 11101101 10101000 5 16 (4,4,3,5) - - X 0 X C 0 - tmp := (hl), (de) := tmp, de -= 1, hl -= 1,

bc -= 1, f5 := [tmp + a].1, f3 := [tmp + a].3

Load and Decrement
lddr 11101101 10111000 6/5 21/16 (4,4,3,5,5/4,4,3,5) - - X 0 X C 0 - ldd, if bc <> 0 then pc -= 2 Load and Decrement, Repeat
ldi 11101101 10100000 5 16 (4,4,3,5) - - X 0 X C 0 - tmp := (hl), (de) := tmp, de += 1, hl += 1,

bc -= 1, f5 := [tmp + a].1, f3 := [tmp + a].3

Load and Increment
ldir 11101101 10110000 6/5 21/16 (4,4,3,5,5/4,4,3,5) - - X 0 X C 0 - ldi, if bc <> 0 then pc -= 2 Load and Increment, Repeat

Letter N

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
neg 11101101 01***100 2 8 (4,4) + + + + + V 1 + a := 0 - a Negate
nop 00000000 1 4 (4) - - - - - - - - nothing No Operation

Letter O

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
or R 10110rrr 1 4 (4) + + + 0 + P 0 0 a := a OR R Logical Inclusive OR
or J 11i11101 1011010b 2 8 (4,4) + + + 0 + P 0 0 a := a OR J
or N 11110110 nnnnnnnn 2 7 (4,3) + + + 0 + P 0 0 a := a OR N
or (hl) 10110110 2 7 (4,3) + + + 0 + P 0 0 a := a OR (hl)
or (I+D) 11i11101 10110110 dddddddd 5 19 (4,4,3,5,3) + + + 0 + P 0 0 a := a OR (I+D)
out (N),a 11010011 nnnnnnnn 3 11 (4,3,4) - - - - - - - - ((N)) := a I/O Output
out (c),R 11101101 01rrr001 4 12 (4,4,4) - - - - - - - - ((c)) := R
out (c),0 11101101 01110001 4 12 (4,4,4) - - - - - - - - ((c)) := 0 (only on NMOS CPU)
outd 11101101 10101011 5 16 (4,5,3,4) + + + X + X X X tmp := (hl), ((c)) := tmp, hl -= 1,

b -= 1 => flags, nf := tmp.7, tmp2 = tmp + l,

pf := parity of [[tmp2 AND 0x07] XOR b],

hf := cf := tmp2 > 255

I/O Output and Decrement
otdr 11101101 10111011 6/5 21/16 (4,5,3,4,5/4,5,3,4) + + + X + X X X outd, if b <> 0 then pc -= 2 I/O Output and Decrement, Repeat
outi 11101101 10100011 5 16 (4,5,3,4) + + + X + X X X tmp := (hl), ((c)) := tmp, hl += 1,

b -= 1 => flags, nf := tmp.7, tmp2 = tmp + l,

pf := parity of [[tmp2 AND 0x07] XOR b],

hf := cf := tmp2 > 255

I/O Output and Increment
otir 11101101 10110011 6/5 21/16 (4,5,3,4,5/4,5,3,4) + + + X + X X X outi, if b <> 0 then pc -= 2 I/O Output and Increment, Repeat

Letter P

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
pop P 11pp0001 3 10 (4,3,3) - - - - - - - - P := (sp), sp += 2 Pop a value from the stack
pop I 11i11101 11100001 4 14 (4,4,3,3) - - - - - - - - I := (sp), sp += 2
push P 11pp0101 4 11 (5,3,3) - - - - - - - - sp -= 2, (sp) := P Push a value onto the stack
push I 11i11101 11100101 5 15 (4,5,3,3) - - - - - - - - sp -= 2, (sp) := I

Letter R

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
res B,R 11001011 10bbbrrr 2 8 (4,4) - - - - - - - - R := R AND ~[1 << B] Reset Bit
res B,(hl) 11001011 10bbb110 4 15 (4,4,4,3) - - - - - - - - (hl) := (hl) AND ~[1 << B]
res B,(I+D) 11i11101 11001011 dddddddd 10bbb110 7 23 (4,4,3,5,4,3) - - - - - - - - (I+D) := (I+D) AND ~[1 << B]
res B,(I+D)->R 11i11101 11001011 dddddddd 10bbbrrr 7 23 (4,4,3,5,4,3) - - - - - - - - (I+D) := R := (I+D) AND ~[1 << B]
ret 11001001 3 10 (4,3,3) - - - - - - - - pc := (sp), sp += 2 Return
ret C 11ccc000 4/2 11/5 (5,3,3/5) - - - - - - - - if C then pc := (sp), sp += 2 Conditional Return
reti 11101101 01**1101 4 14 (4,4,3,3) - - - - - - - - pc := (sp), sp += 2, iff1 := iff2 Return from Interrupt
retn 11101101 01**0101 4 14 (4,4,3,3) - - - - - - - - pc := (sp), sp += 2, iff1 := iff2 Return from NMI
rla 00010111 1 4 (4) - - + 0 + - 0 X ocf := cf, cf := a.7, a := [a << 1] + ocf Rotate Left Accumulator
rl R 11001011 00010rrr 2 8 (4,4) + + + 0 + P 0 X ocf := cf, cf := R.7, R := [R << 1] + ocf Rotate Left
rl (hl) 11001011 00010110 4 15 (4,4,4,3) + + + 0 + P 0 X ocf := cf, cf := (hl).7, (hl) := [(hl) << 1] + ocf
rl (I+D) 11i11101 11001011 dddddddd 00010110 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X ocf := cf, cf := (I+D).7, (I+D) := [(I+D) << 1] + ocf
rl (I+D)->R 11i11101 11001011 dddddddd 00010rrr 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X ocf := cf, cf := (I+D).7, (I+D) := R := [(I+D) << 1] + ocf
rlca 00000111 1 4 (4) - - + 0 + - 0 X cf := a.7, a := [a << 1] + cf Rotate Left Carry Accumulator
rlc R 11001011 00000rrr 2 8 (4,4) + + + 0 + P 0 X cf := R.7, R := [R << 1] + cf Rotate Left Carry
rlc (hl) 11001011 00000110 4 15 (4,4,4,3) + + + 0 + P 0 X cf := (hl).7, (hl) := [(hl) << 1] + cf
rlc (I+D) 11i11101 11001011 dddddddd 00000110 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X cf := (I+D).7, (I+D) := [(I+D) << 1] + cf
rlc (I+D)->R 11i11101 11001011 dddddddd 00000rrr 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X cf := (I+D).7, (I+D) := R := [(I+D) << 1] + cf
rld 11101101 01101111 5 18 (4,4,3,4,3) + + + 0 + P 0 - tmp := [(hl) << 4] + [a AND 0x0f], (hl) := tmp,

a := [a AND 0xf0] + [tmp >> 8] => flags

Rotate Left Decimal
rra 00011111 1 4 (4) - - + 0 + - 0 X ocf := cf, cf := a.0, a := [a >> 1] + [ocf << 7] Rotate Right Accumulator
rr R 11001011 00011rrr 2 8 (4,4) + + + 0 + P 0 X ocf := cf, cf := R.0, R := [R >> 1] + [ocf << 7] Rotate Right
rr (hl) 11001011 00011110 4 15 (4,4,4,3) + + + 0 + P 0 X ocf := cf, cf := (hl).0, (hl) := [(hl) >> 1] + [ocf << 7]
rr (I+D) 11i11101 11001011 dddddddd 00011110 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X ocf := cf, cf := (I+D).0, (I+D) := [(I+D) >> 1] + [ocf << 7]
rr (I+D)->R 11i11101 11001011 dddddddd 00011rrr 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X ocf := cf, cf := (I+D).0, (I+D) := R := [(I+D) >> 1] + [ocf << 7]
rrca 00001111 1 4 (4) - - + 0 + - 0 X cf := a.0, a := [a >> 1] + [cf << 7] Rotate Right Carry Accumulator
rrc R 11001011 00001rrr 2 8 (4,4) + + + 0 + P 0 X cf := R.0, R := [R >> 1] + [cf << 7] Rotate Right Carry
rrc (hl) 11001011 00001110 4 15 (4,4,4,3) + + + 0 + P 0 X cf := (hl).0, (hl) := [(hl) >> 1] + [cf << 7]
rrc (I+D) 11i11101 11001011 dddddddd 00001110 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X cf := (I+D).0, (I+D) := [(I+D) >> 1] + [cf << 7]
rrc (I+D)->R 11i11101 11001011 dddddddd 00001rrr 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X cf := (I+D).0, (I+D) := R := [(I+D) >> 1] + [cf << 7]
rrd 11101101 01100111 5 18 (4,4,3,4,3) + + + 0 + P 0 - tmp := (hl), (hl) := [tmp >> 4] + [[a AND 0x0f] << 4],

a := [a AND 0xf0] + [tmp AND 0x0f] => flags

Rotate Right Decimal
rst S 11sss111 4 11 (5,3,3) - - - - - - - - sp -= 2, (sp) := pc, pc := S Restart

Letter S

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
sbc a,R 10011rrr 1 4 (4) + + + + + V 1 + a -= R + cf Subtract with Carry
sbc a,J 11i11101 1001110b 2 8 (4,4) + + + + + V 1 + a -= J + cf
sbc a,N 11011110 nnnnnnnn 2 7 (4,3) + + + + + V 1 + a -= N + cf
sbc a,(hl) 10011110 2 7 (4,3) + + + + + V 1 + a -= (hl) + cf
sbc a,(I+D) 11i11101 10011110 dddddddd 5 19 (4,4,3,5,3) + + + + + V 1 + a -= (I+D) + cf
sbc hl,Q 11101101 01qq0010 4 15 (4,4,4,3) + + + + + V 1 + hl -= Q + cf
scf 00110111 1 4 (4) - - A 0 A - 0 1 nothing else Set Carry Flag
set B,R 11001011 11bbbrrr 2 8 (4,4) - - - - - - - - R := R OR [1 << B] Set Bit
set B,(hl) 11001011 11bbb110 4 15 (4,4,4,3) - - - - - - - - (hl) := (hl) OR [1 << B]
set B,(I+D) 11i11101 11001011 dddddddd 11bbb110 7 23 (4,4,3,5,4,3) - - - - - - - - (I+D) := (I+D) OR [1 << B]
set B,(I+D)->R 11i11101 11001011 dddddddd 11bbbrrr 7 23 (4,4,3,5,4,3) - - - - - - - - (I+D) := R := (I+D) OR [1 << B]
sla R 11001011 00100rrr 2 8 (4,4) + + + 0 + P 0 X cf := R.7, R := R << 1 Shift Left Arithmetic
sla (hl) 11001011 00100110 4 15 (4,4,4,3) + + + 0 + P 0 X cf := (hl).7, (hl) := (hl) << 1
sla (I+D) 11i11101 11001011 dddddddd 00100110 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X cf := (I+D).7, (I+D) := (I+D) << 1
sla (I+D)->R 11i11101 11001011 dddddddd 00100rrr 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X cf := (I+D).7, (I+D) := R := (I+D) << 1
sra R 11001011 00101rrr 2 8 (4,4) + + + 0 + P 0 X cf := R.0, R := R >> 1, R.7 := R.6 Shift Right Arithmetic
sra (hl) 11001011 00101110 4 15 (4,4,4,3) + + + 0 + P 0 X cf := (hl).0, (hl) := (hl) >> 1, (hl).7 := (hl).6
sra (I+D) 11i11101 11001011 dddddddd 00101110 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X cf := (I+D).0,

(I+D) := (I+D) >> 1, (I+D).7 := (I+D).6

sra (I+D)->R 11i11101 11001011 dddddddd 00101rrr 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X cf := (I+D).0,

tmp := (I+D) >> 1, tmp.7 := tmp.6,

(I+D) := R := tmp

sll R 11001011 00110rrr 2 8 (4,4) + + + 0 + P 0 X cf := R.7, R := [R << 1] + 1 Shift Left Logical
sll (hl) 11001011 00110110 4 15 (4,4,4,3) + + + 0 + P 0 X cf := (hl).7, (hl) := [(hl) << 1] + 1
sll (I+D) 11i11101 11001011 dddddddd 00110110 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X cf := (I+D).7, (I+D) := [(I+D) << 1] + 1
sll (I+D)->R 11i11101 11001011 dddddddd 00110rrr 7 23 (4,4,3,5,4,3) + + + 0 + P 0 X cf := (I+D).7, (I+D) := R := [(I+D) << 1] + 1
srl R 11001011 00111rrr 2 8 (4,4) 0 + + 0 + P 0 X cf := R.0, R := R >> 1 Shift Right Logical
srl (hl) 11001011 00111110 4 15 (4,4,3) 0 + + 0 + P 0 X cf := (hl).0, (hl) := (hl) >> 1
srl (I+D) 11i11101 11001011 dddddddd 00111110 7 23 (4,4,3,5,4,3) 0 + + 0 + P 0 X cf := (I+D).0, (I+D) := (I+D) >> 1
srl (I+D)->R 11i11101 11001011 dddddddd 00111rrr 7 23 (4,4,3,5,4,3) 0 + + 0 + P 0 X cf := (I+D).0, (I+D) := R := (I+D) >> 1
sub R 10010rrr 1 4 (4) + + + + + V 1 + a -= R Subtract
sub J 11i11101 1001010b 2 8 (4,4) + + + + + V 1 + a -= J
sub N 11010110 nnnnnnnn 2 7 (4,3) + + + + + V 1 + a -= N
sub (hl) 10010110 2 7 (4,3) + + + + + V 1 + a -= (hl)
sub (I+D) 11i11101 10010110 dddddddd 5 19 (4,4,3,5,3) + + + + + V 1 + a -= (I+D)

Letter X

Instruction Opcode NOPs Cycles S Z 5 H 3 P N C Effect Description
xor R 10101rrr 1 4 (4) + + + 0 + P 0 0 a := a XOR R Logical eXclusive OR
xor J 11i11101 1010110b 2 8 (4,4) + + + 0 + P 0 0 a := a XOR J
xor N 11101110 nnnnnnnn 2 7 (4,3) + + + 0 + P 0 0 a := a XOR N
xor (hl) 10101110 2 7 (4,3) + + + 0 + P 0 0 a := a XOR (hl)
xor (I+D) 11i11101 10101110 dddddddd 5 19 (4,4,3,5,3) + + + 0 + P 0 0 a := a XOR (I+D)


Opcodes

Any instruction in bold is undocumented by Zilog.

Standard opcodes

Opcode Mnemonic
00 NOP
01 nn LD BC,nn
02 LD (BC),A
03 INC BC
04 INC B
05 DEC B
06 n LD B,n
07 RLCA
08 EX AF,AF'
09 ADD HL,BC
0A LD A,(BC)
0B DEC BC
0C INC C
0D DEC C
0E n LD C,n
0F RRCA
10 e DJNZ PC+e
11 nn LD DE,nn
12 LD (DE),A
13 INC DE
14 INC D
15 DEC D
16 n LD D,n
17 RLA
18 e JR e
19 ADD HL,DE
1A LD A,(DE)
1B DEC DE
1C INC E
1D DEC E
1E n LD E,n
1F RRA
Opcode Mnemonic
20 e JR NZ,e
21 nn LD HL,nn
22 nn LD (nn),HL
23 INC HL
24 INC H
25 DEC H
26 n LD H,n
27 DAA
28 e JR Z,e
29 ADD HL,HL
2A nn LD HL,(nn)
2B DEC HL
2C INC L
2D DEC L
2E n LD L,n
2F CPL
30 e JR NC,e
31 nn LD SP,nn
32 nn LD (nn),A
33 INC SP
34 INC (HL)
35 DEC (HL)
36 n LD (HL),n
37 SCF
38 e JR C,e
39 ADD HL,SP
3A nn LD A,(nn)
3B DEC SP
3C INC A
3D DEC A
3E n LD A,n
3F CCF
Opcode Mnemonic
40 LD B,B
41 LD B,C
42 LD B,D
43 LD B,E
44 LD B,H
45 LD B,L
46 LD B,(HL)
47 LD B,A
48 LD C,B
49 LD C,C
4A LD C,D
4B LD C,E
4C LD C,H
4D LD C,L
4E LD C,(HL)
4F LD C,A
50 LD D,B
51 LD D,C
52 LD D,D
53 LD D,E
54 LD D,H
55 LD D,L
56 LD D,(HL)
57 LD D,A
58 LD E,B
59 LD E,C
5A LD E,D
5B LD E,E
5C LD E,H
5D LD E,L
5E LD E,(HL)
5F LD E,A
Opcode Mnemonic
60 LD H,B
61 LD H,C
62 LD H,D
63 LD H,E
64 LD H,H
65 LD H,L
66 LD H,(HL)
67 LD H,A
68 LD L,B
69 LD L,C
6A LD L,D
6B LD L,E
6C LD L,H
6D LD L,L
6E LD L,(HL)
6F LD L,A
70 LD (HL),B
71 LD (HL),C
72 LD (HL),D
73 LD (HL),E
74 LD (HL),H
75 LD (HL),L
76 HALT
77 LD (HL),A
78 LD A,B
79 LD A,C
7A LD A,D
7B LD A,E
7C LD A,H
7D LD A,L
7E LD A,(HL)
7F LD A,A
Opcode Mnemonic
80 ADD A,B
81 ADD A,C
82 ADD A,D
83 ADD A,E
84 ADD A,H
85 ADD A,L
86 ADD A,(HL)
87 ADD A,A
88 ADC A,B
89 ADC A,C
8A ADC A,D
8B ADC A,E
8C ADC A,H
8D ADC A,L
8E ADC A,(HL)
8F ADC A,A
90 SUB B
91 SUB C
92 SUB D
93 SUB E
94 SUB H
95 SUB L
96 SUB (HL)
97 SUB A
98 SBC A,B
99 SBC A,C
9A SBC A,D
9B SBC A,E
9C SBC A,H
9D SBC A,L
9E SBC A,(HL)
9F SBC A,A
Opcode Mnemonic
A0 AND B
A1 AND C
A2 AND D
A3 AND E
A4 AND H
A5 AND L
A6 AND (HL)
A7 AND A
A8 XOR B
A9 XOR C
AA XOR D
AB XOR E
AC XOR H
AD XOR L
AE XOR (HL)
AF XOR A
B0 OR B
B1 OR C
B2 OR D
B3 OR E
B4 OR H
B5 OR L
B6 OR (HL)
B7 OR A
B8 CP B
B9 CP C
BA CP D
BB CP E
BC CP H
BD CP L
BE CP (HL)
BF CP A
Opcode Mnemonic
C0 RET NZ
C1 POP BC
C2 nn JP NZ,nn
C3 nn JP nn
C4 nn CALL NZ,nn
C5 PUSH BC
C6 n ADD A,n
C7 RST 0H
C8 RET Z
C9 RET
CA nn JP Z,nn
CB Instruction prefix
CC nn CALL Z,nn
CD nn CALL nn
CE n ADC A,n
CF RST 8H
D0 RET NC
D1 POP DE
D2 nn JP NC,nn
D3 n OUT (n),A
D4 nn CALL NC,nn
D5 PUSH DE
D6 n SUB n
D7 RST 10H
D8 RET C
D9 EXX
DA nn JP C,nn
DB n IN A,(n)
DC nn CALL C,nn
DD Instruction prefix
DE n SBC A,n
DF RST 18H
Opcode Mnemonic
E0 RET PO
E1 POP HL
E2 nn JP PO,nn
E3 EX (SP),HL
E4 nn CALL PO,nn
E5 PUSH HL
E6 n AND n
E7 RST 20H
E8 RET PE
E9 JP (HL)
EA nn JP PE,nn
EB EX DE,HL
EC nn CALL PE,nn
ED Instruction prefix
EE n XOR n
EF RST 28H
F0 RET P
F1 POP AF
F2 nn JP P,nn
F3 DI
F4 nn CALL P,nn
F5 PUSH AF
F6 n OR n
F7 RST 30H
F8 RET M
F9 LD SP,HL
FA nn JP M,nn
FB EI
FC nn CALL M,nn
FD Instruction prefix
FE n CP n
FF RST 38H

CB-prefixed opcodes

Opcode Mnemonic
00 RLC B
01 RLC C
02 RLC D
03 RLC E
04 RLC H
05 RLC L
06 RLC (HL)
07 RLC A
08 RRC B
09 RRC C
0A RRC D
0B RRC E
0C RRC H
0D RRC L
0E RRC (HL)
0F RRC A
10 RL B
11 RL C
12 RL D
13 RL E
14 RL H
15 RL L
16 RL (HL)
17 RL A
18 RR B
19 RR C
1A RR D
1B RR E
1C RR H
1D RR L
1E RR (HL)
1F RR A
Opcode Mnemonic
20 SLA B
21 SLA C
22 SLA D
23 SLA E
24 SLA H
25 SLA L
26 SLA (HL)
27 SLA A
28 SRA B
29 SRA C
2A SRA D
2B SRA E
2C SRA H
2D SRA L
2E SRA (HL)
2F SRA A
30 SLL B
31 SLL C
32 SLL D
33 SLL E
34 SLL H
35 SLL L
36 SLL (HL)
37 SLL A
38 SRL B
39 SRL C
3A SRL D
3B SRL E
3C SRL H
3D SRL L
3E SRL (HL)
3F SRL A
Opcode Mnemonic
40 BIT 0,B
41 BIT 0,C
42 BIT 0,D
43 BIT 0,E
44 BIT 0,H
45 BIT 0,L
46 BIT 0,(HL)
47 BIT 0,A
48 BIT 1,B
49 BIT 1,C
4A BIT 1,D
4B BIT 1,E
4C BIT 1,H
4D BIT 1,L
4E BIT 1,(HL)
4F BIT 1,A
50 BIT 2,B
51 BIT 2,C
52 BIT 2,D
53 BIT 2,E
54 BIT 2,H
55 BIT 2,L
56 BIT 2,(HL)
57 BIT 2,A
58 BIT 3,B
59 BIT 3,C
5A BIT 3,D
5B BIT 3,E
5C BIT 3,H
5D BIT 3,L
5E BIT 3,(HL)
5F BIT 3,A
Opcode Mnemonic
60 BIT 4,B
61 BIT 4,C
62 BIT 4,D
63 BIT 4,E
64 BIT 4,H
65 BIT 4,L
66 BIT 4,(HL)
67 BIT 4,A
68 BIT 5,B
69 BIT 5,C
6A BIT 5,D
6B BIT 5,E
6C BIT 5,H
6D BIT 5,L
6E BIT 5,(HL)
6F BIT 5,A
70 BIT 6,B
71 BIT 6,C
72 BIT 6,D
73 BIT 6,E
74 BIT 6,H
75 BIT 6,L
76 BIT 6,(HL)
77 BIT 6,A
78 BIT 7,B
79 BIT 7,C
7A BIT 7,D
7B BIT 7,E
7C BIT 7,H
7D BIT 7,L
7E BIT 7,(HL)
7F BIT 7,A
Opcode Mnemonic
80 RES 0,B
81 RES 0,C
82 RES 0,D
83 RES 0,E
84 RES 0,H
85 RES 0,L
86 RES 0,(HL)
87 RES 0,A
88 RES 1,B
89 RES 1,C
8A RES 1,D
8B RES 1,E
8C RES 1,H
8D RES 1,L
8E RES 1,(HL)
8F RES 1,A
90 RES 2,B
91 RES 2,C
92 RES 2,D
93 RES 2,E
94 RES 2,H
95 RES 2,L
96 RES 2,(HL)
97 RES 2,A
98 RES 3,B
99 RES 3,C
9A RES 3,D
9B RES 3,E
9C RES 3,H
9D RES 3,L
9E RES 3,(HL)
9F RES 3,A
Opcode Mnemonic
A0 RES 4,B
A1 RES 4,C
A2 RES 4,D
A3 RES 4,E
A4 RES 4,H
A5 RES 4,L
A6 RES 4,(HL)
A7 RES 4,A
A8 RES 5,B
A9 RES 5,C
AA RES 5,D
AB RES 5,E
AC RES 5,H
AD RES 5,L
AE RES 5,(HL)
AF RES 5,A
B0 RES 6,B
B1 RES 6,C
B2 RES 6,D
B3 RES 6,E
B4 RES 6,H
B5 RES 6,L
B6 RES 6,(HL)
B7 RES 6,A
B8 RES 7,B
B9 RES 7,C
BA RES 7,D
BB RES 7,E
BC RES 7,H
BD RES 7,L
BE RES 7,(HL)
BF RES 7,A
Opcode Mnemonic
C0 SET 0,B
C1 SET 0,C
C2 SET 0,D
C3 SET 0,E
C4 SET 0,H
C5 SET 0,L
C6 SET 0,(HL)
C7 SET 0,A
C8 SET 1,B
C9 SET 1,C
CA SET 1,D
CB SET 1,E
CC SET 1,H
CD SET 1,L
CE SET 1,(HL)
CF SET 1,A
D0 SET 2,B
D1 SET 2,C
D2 SET 2,D
D3 SET 2,E
D4 SET 2,H
D5 SET 2,L
D6 SET 2,(HL)
D7 SET 2,A
D8 SET 3,B
D9 SET 3,C
DA SET 3,D
DB SET 3,E
DC SET 3,H
DD SET 3,L
DE SET 3,(HL)
DF SET 3,A
Opcode Mnemonic
E0 SET 4,B
E1 SET 4,C
E2 SET 4,D
E3 SET 4,E
E4 SET 4,H
E5 SET 4,L
E6 SET 4,(HL)
E7 SET 4,A
E8 SET 5,B
E9 SET 5,C
EA SET 5,D
EB SET 5,E
EC SET 5,H
ED SET 5,L
EE SET 5,(HL)
EF SET 5,A
F0 SET 6,B
F1 SET 6,C
F2 SET 6,D
F3 SET 6,E
F4 SET 6,H
F5 SET 6,L
F6 SET 6,(HL)
F7 SET 6,A
F8 SET 7,B
F9 SET 7,C
FA SET 7,D
FB SET 7,E
FC SET 7,H
FD SET 7,L
FE SET 7,(HL)
FF SET 7,A

ED-prefixed opcodes

The opcodes that are not mentioned in the following table are EDNOP (ED-prefixed NOP instruction). Thay have no effect but take 8 cycles and increment the register R two times. A pair of ED prefixes is also an EDNOP.

Opcode Mnemonic
40 IN B,(C)
41 OUT (C),B
42 SBC HL,BC
43 nn LD (nn),BC
44 NEG
45 RETN
46 IM 0
47 LD I,A
48 IN C,(C)
49 OUT (C),C
4A ADC HL,BC
4B nn LD (nn),BC
4C NEG
4D RETI
4E IM 0
4F LD R,A
Opcode Mnemonic
50 IN D,(C)
51 OUT (C),D
52 SBC HL,DE
53 nn LD (nn),DE
54 NEG
55 RETN
56 IM 1
57 LD A,I
58 IN E,(C)
59 OUT (C),E
5A ADC HL,DE
5B nn LD (nn),DE
5C NEG
5D RETN
5E IM 2
5F LD A,R
Opcode Mnemonic
60 IN H,(C)
61 OUT (C),H
62 SBC HL,HL
63 nn LD (nn),HL
64 NEG
65 RETN
66 IM 0
67 RRD
68 IN L,(C)
69 OUT (C),L
6A ADC HL,HL
6B nn LD (nn),HL
6C NEG
6D RETN
6E IM 0
6F RLD
Opcode Mnemonic
70 IN F,(C)
71 OUT (C),0
72 SBC HL,SP
73 nn LD (nn),SP
74 NEG
75 RETN
76 IM 1
78 IN A,(C)
79 OUT (C),A
7A ADC HL,SP
7B nn LD SP,(nn)
7C NEG
7D RETN
7E IM 2
Opcode Mnemonic
A0 LDI
A1 CPI
A2 INI
A3 OUTI
A8 LDD
A9 CPD
AA IND
AB OUTD
B0 LDIR
B1 CPIR
B2 INIR
B3 OTIR
B8 LDDR
B9 CPDR
BA INDR
BB OTDR

Notes:

  • The opcode ED 70 reads the port indicated by the register C without keeping the result but modifies the register F
  • The opcode ED 71 corresponds to the instruction OUT (C),255 on a CMOS Z80

DD or FD-prefixed opcodes

If an opcode is prefixed by DD, the instruction is changed as follows:

  • HL is replaced by IX
  • H is replaced by IXH
  • L is replaced by IXL
  • (HL) is replaced by (IX+d)

Same for the FD prefix but with IY instead of IX.

There are 3 exceptions:

  • In the instruction EX DE,HL, HL will not be replaced with IX or IY. The EXX instruction is not affected either.
  • If (HL) and L or H are used in the same instruction, L and H are not replaced with IXL or IXH. For instance LD L,(IX+d) stores the content of (IX+d) into L, not IXL.
  • If the next byte is a DD, ED or FD prefix, the current DD or FD prefix is ignored (it's equivalent to a NONI) and processing continues with the next byte. ED-prefixed opcodes cannot be altered by DD or FD prefixes.

DDCB or FDCB-prefixed opcodes

When a DD or FD prefix is followed by a CB byte, the CB acts as a second prefix. A mandatory displacement byte comes next, and then the actual opcode.

If the instruction produces output other than in the flags (i.e. all except BIT), then the result gets placed both into (IX+d) or (IY+d) and into the register one would normally expect to be altered.

DDCB and FDCB-prefixed instructions only increment the R register twice. This has been confirmed on Stack Overflow


Oddities

  • All CB-prefixed opcodes and half of the standard opcodes (from &40 to &BF) follow a uniform layout. The exception is the HALT instruction (opcode &76), which replaces the expected LD (HL),(HL) instruction.
  • Despite having different names and opcodes, RETI and RETN are in fact the exact same instruction
  • RST instructions are just a CALL instruction to a fixed address baked in the instruction itself
  • Despite what the syntax of the instructions JP (HL/IX/IY) suggests, PC will be loaded with the contents of the register itself, not the indexed value. Those instructions should be understood as JP HL/IX/IY
  • IN (C) and OUT (C) instructions syntax is misleading as these instructions actually use the full 16-bit port address contained in BC
  • While the syntax of ADD, ADC and SBC instructions all explicitely mention the A register, the SUB instruction does not mention it
  • The 16-bit commands ADD HL,ss, ADC HL,ss and SBC HL,ss exist but not the command SUB HL,ss
  • The NOP instruction takes 4 cycles. This is the minimum amount of cycles an instruction can take.


Manuals


Weblinks