Last modified on 29 April 2025, at 00:14

GBZ80

The GBZ80 (Sharp SM83) is the CPU that powers the original Nintendo Gameboy and Gameboy Color handheld consoles. It is kind of an in-between the Intel 8080 and Z80.

The GBZ80 lacks the alternate register set, the dedicated I/O bus, the R register (thus no M1), the index registers (thus no DD and FD prefixed opcodes), the ED prefixed opcodes (including block transfer), the sign and parity/overflow flags (and all conditional instructions that used them), the undocumented flags (thus no leaking of WZ and Q internal registers). GBZ80 opcodes

The GBZ80 also lacks the NMI pin (thus no IFF2 and no RETN), the IM instructions and the I register. It has a different interrupt system than the Z80. Source

The Nintendo documentation does not mention M-cycles or T-states at all. They only mention CPU cycles, which are always equal to 4 T-states (like NOPs in the CPC world). Also, the GBZ80 has different timings than the Z80. For example:

  • CALL nn takes 6 cycles on the GBZ80, but 5 NOPs on the Z80
  • ADD HL,ss takes 2 cycles on the GBZ80, but 3 NOPs on the Z80
  • JP cc,nn has different timings depending on whether the jump is taken. This is not the case on Z80.

Flags can differ too:

  • RLCA, RRCA, RLA, RRA clear ZF in the GBZ80, but not in the Z80
  • DAA clears HF in the GBZ80, but not in the Z80

Fun fact: Way more GBZ80 cores were produced for Gameboy hardware (118 million Gameboys and 81 million GBA) than all the Z80 chips produced for home computers and game consoles.


Register File

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 - ZF - Zero Flag
  • bit6 - NF - Negate Flag (last ALU op was subtract or compare)
  • bit5 - HF - Half Carry Flag
  • bit4 - CF - Carry Flag
  • bits3..0 - Always 0
NF and HF are used in the DAA algorithm
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


GBZ80 instructions

CPU opcode reference

Legend:

  • r,s: 000=B, 001=C, 010=D, 011=E, 100=H, 101=L, 111=A (110 is treated separately)
  • pp: 00=BC, 01=DE, 10=HL, 11=SP
  • qq: 00=BC, 01=DE, 10=HL, 11=AF
  • cc: 00=NZ, 01=Z, 10=NC, 11=C

Load group

Instruction Opcode Cycles Z N H C Effect Description
ld r,s 01rrrsss 1 - - - - r := s 8-bit Load
ld (hl),r 01110rrr 2 (hl) := r
ld r,(hl) 01rrr110 2 r := (hl)
ld r,n 00rrr110 nnnnnnnn 2 r := n
ld (hl),n 00110110 nnnnnnnn 3 (hl) := n
ld (bc),a 00000010 2 (bc) := a
ld a,(bc) 00001010 2 a := (bc)
ld (de),a 00010010 2 (de) := a
ld a,(de) 00011010 2 a := (de)
ld (hli),a 00100010 2 (hl) := a, hl += 1
ld a,(hli) 00101010 2 a := (hl), hl += 1
ld (hld),a 00110010 2 (hl) := a, hl -= 1
ld a,(hld) 00111010 2 a := (hl), hl -= 1
ld (nn),a 11101010 lolololo hihihihi 4 (nn) := a
ld a,(nn) 11111010 lolololo hihihihi 4 a := (nn)
ld (n),a 11100000 nnnnnnnn 3 - - - - (FF00h + n) := a 8-bit I/O Load
ld a,(n) 11110000 nnnnnnnn 3 a := (FF00h + n)
ld (c),a 11100010 2 (FF00h + c) := a
ld a,(c) 11110010 2 a := (FF00h + c)
ld pp,nn 00pp0001 lolololo hihihihi 3 - - - - pp := nn 16-bit Load
ld (nn),sp 00001000 lolololo hihihihi 5 (nn) := sp
ld sp,hl 11111001 2 sp := hl
pop qq 11qq0001 3 - - - - qq := (sp), sp += 2 Pop a value from the stack
push qq 11qq0101 4 - - - - sp -= 2, (sp) := qq Push a value onto the stack

16-bit Arithmetic group

Instruction Opcode Cycles Z N H C Effect Description
inc pp 00pp0011 2 - - - - pp += 1 Increment
dec pp 00pp1011 2 - - - - pp -= 1 Decrement
add hl,pp 00pp1001 2 - 0 + + hl += pp Add
add sp,e 11101000 eeeeeeee 4 0 0 + + sp += e
ldhl sp,e 11111000 eeeeeeee 3 0 0 + + hl := sp + e

8-bit ALU group

Instruction Opcode Cycles Z N H C Effect Description
inc r 00rrr100 1 + 0 + - r += 1 Increment
inc (hl) 00110100 3 (hl) += 1
dec r 00rrr101 1 + 1 + - r -= 1 Decrement
dec (hl) 00110101 3 (hl) -= 1
add a,r 10000rrr 1 + 0 + + a += r Add
add a,(hl) 10000110 2 a += (hl)
add a,n 11000110 nnnnnnnn 2 a += n
adc a,r 10001rrr 1 + 0 + + a += r + cf Add with Carry
adc a,(hl) 10001110 2 a += (hl) + cf
adc a,n 11001110 nnnnnnnn 2 a += n + cf
sub r 10010rrr 1 + 1 + + a -= r Subtract
sub (hl) 10010110 2 a -= (hl)
sub n 11010110 nnnnnnnn 2 a -= n
sbc a,r 10011rrr 1 + 1 + + a -= r + cf Subtract with Carry
sbc a,(hl) 10011110 2 a -= (hl) + cf
sbc a,n 11011110 nnnnnnnn 2 a -= n + cf
cp r 10111rrr 1 + 1 + + tmp := a - r Compare
cp (hl) 10111110 2 tmp := a - (hl)
cp n 11111110 nnnnnnnn 2 tmp := a - n
and r 10100rrr 1 + 0 1 0 a := a and r Logical AND
and (hl) 10100110 2 a := a and (hl)
and n 11100110 nnnnnnnn 2 a := a and n
xor r 10101rrr 1 + 0 0 0 a := a xor r Logical eXclusive OR
xor (hl) 10101110 2 a := a xor (hl)
xor n 11101110 nnnnnnnn 2 a := a xor n
or r 10110rrr 1 + 0 0 0 a := a or r Logical Inclusive OR
or (hl) 10110110 2 a := a or (hl)
or n 11110110 nnnnnnnn 2 a := a or n
daa 00100111 1 + - 0 X tmp := a,

if nf:

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

else:

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

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

Decimal Adjust Accumulator

ROT group

Instruction Opcode Cycles Z N H C Effect Description
rlca 00000111 1 0 0 0 X cf := a.7, a := [a << 1] + cf Fast Rotate
rrca 00001111 1 cf := a.0, a := [a >> 1] + [cf << 7]
rla 00010111 1 ocf := cf, cf := a.7, a := [a << 1] + ocf
rra 00011111 1 ocf := cf, cf := a.0, a := [a >> 1] + [ocf << 7]
rl r CB 00010rrr 2 + 0 0 X ocf := cf, cf := r.7, r := [r << 1] + ocf Rotate Left
rl (hl) CB 00010110 4 ocf := cf, cf := (hl).7, (hl) := [(hl) << 1] + ocf
rlc r CB 00000rrr 2 + 0 0 X cf := r.7, r := [r << 1] + cf Rotate Left Carry
rlc (hl) CB 00000110 4 cf := (hl).7, (hl) := [(hl) << 1] + cf
rr r CB 00011rrr 2 + 0 0 X ocf := cf, cf := r.0, r := [r >> 1] + [ocf << 7] Rotate Right
rr (hl) CB 00011110 4 ocf := cf, cf := (hl).0, (hl) := [(hl) >> 1] + [ocf << 7]
rrc r CB 00001rrr 2 + 0 0 X cf := r.0, r := [r >> 1] + [cf << 7] Rotate Right Carry
rrc (hl) CB 00001110 4 cf := (hl).0, (hl) := [(hl) >> 1] + [cf << 7]
sla r CB 00100rrr 2 + 0 0 X cf := r.7, r := r << 1 Shift Left Arithmetic
sla (hl) CB 00100110 4 cf := (hl).7, (hl) := (hl) << 1
sra r CB 00101rrr 2 + 0 0 X cf := r.0, r := r >> 1, r.7 := r.6 Shift Right Arithmetic
sra (hl) CB 00101110 4 cf := (hl).0, (hl) := (hl) >> 1, (hl).7 := (hl).6
srl r CB 00111rrr 2 + 0 0 X cf := r.0, r := r >> 1 Shift Right Logical
srl (hl) CB 00111110 4 cf := (hl).0, (hl) := (hl) >> 1
swap r CB 00110rrr 2 + 0 0 0 r := [[r and 0x0f] << 4] + [r >> 4] Swap nibbles
swap (hl) CB 00110110 4 (hl) := [[(hl) and 0x0f] << 4] + [(hl) >> 4]

Bitwise group

Instruction Opcode Cycles Z N H C Effect Description
bit b,r CB 01bbbrrr 2 + 0 1 - tmp := r and [1 << b] Test Bit
bit b,(hl) CB 01bbb110 3 tmp := (hl) and [1 << b]
res b,r CB 10bbbrrr 2 - - - - r := r and ~[1 << b] Reset Bit
res b,(hl) CB 10bbb110 4 (hl) := (hl) and ~[1 << b]
set b,r CB 11bbbrrr 2 - - - - r := r or [1 << b] Set Bit
set b,(hl) CB 11bbb110 4 (hl) := (hl) or [1 << b]
cpl 00101111 1 - 1 1 - a := ~a Complement

Control flow group

Instruction Opcode Cycles Z N H C Effect Description
rst t 11ttt111 4 - - - - sp -= 2, (sp) := pc, pc := t Restart

ttt: 000=#0, 001=#8, 010=#10, 011=#18, 100=#20, 101=#28, 110=#30, 111=#38

call nn 11001101 lolololo hihihihi 6 sp -= 2, (sp) := pc, pc := nn Call
call cc,nn 110cc100 lolololo hihihihi 6/3 if cc then sp -= 2, (sp) := pc, pc := nn
jp nn 11000011 lolololo hihihihi 4 - - - - pc := nn Jump
jp (hl) 11101001 1 pc := hl
jp cc,nn 110cc010 lolololo hihihihi 4/3 if cc then pc := nn
jr e 00011000 eeeeeeee 3 - - - - pc += e Relative jump
jr cc,e 001cc000 eeeeeeee 3/2 if cc then pc += e
ret 11001001 4 - - - - pc := (sp), sp += 2 Return
ret cc 110cc000 5/2 if cc then pc := (sp), sp += 2
reti 11011001 4 pc := (sp), sp += 2, ime := 1 Return from Interrupt

CPU control group

Instruction Opcode Cycles Z N H C Effect Description
di 11110011 1 - - - - ime := 0 Disable Interrupts
ei 11111011 1 - - - - ime := 1 Enable Interrupts
halt 01110110 1 - - - - wait for interrupt Suspends CPU operation
stop 00010000 00000000 1 - - - - wait for reset signal Stops the system clock and LCD controller
nop 00000000 1 - - - - nothing No Operation
scf 00110111 1 - 0 0 1 nothing else Set Carry Flag
ccf 00111111 1 - 0 X X hf := cf, cf := ~cf Complement Carry Flag


Opcodes

Opcode differences with Z80 are in bold. The unused () opcodes will lock up the Game Boy CPU when used. The assembler syntax is from the official Nintendo Gameboy programming manual.

Standard opcodes

Opcode Mnemonic
00 NOP
01 xx xx LD BC,nn
02 LD (BC),A
03 INC BC
04 INC B
05 DEC B
06 xx LD B,n
07 RLCA
Opcode Mnemonic
08 xx xx LD (nn),SP
09 ADD HL,BC
0A LD A,(BC)
0B DEC BC
0C INC C
0D DEC C
0E xx LD C,n
0F RRCA
Opcode Mnemonic
10 xx STOP
11 xx xx LD DE,nn
12 LD (DE),A
13 INC DE
14 INC D
15 DEC D
16 xx LD D,n
17 RLA
Opcode Mnemonic
18 xx JR e
19 ADD HL,DE
1A LD A,(DE)
1B DEC DE
1C INC E
1D DEC E
1E xx LD E,n
1F RRA
Opcode Mnemonic
20 xx JR NZ,e
21 xx xx LD HL,nn
22 LD (HLI),A
23 INC HL
24 INC H
25 DEC H
26 xx LD H,n
27 DAA
Opcode Mnemonic
28 xx JR Z,e
29 ADD HL,HL
2A LD A,(HLI)
2B DEC HL
2C INC L
2D DEC L
2E xx LD L,n
2F CPL
Opcode Mnemonic
30 xx JR NC,e
31 xx xx LD SP,nn
32 LD (HLD),A
33 INC SP
34 INC (HL)
35 DEC (HL)
36 xx LD (HL),n
37 SCF
Opcode Mnemonic
38 xx JR C,e
39 ADD HL,SP
3A LD A,(HLD)
3B DEC SP
3C INC A
3D DEC A
3E xx 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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
90 SUB B
91 SUB C
92 SUB D
93 SUB E
94 SUB H
95 SUB L
96 SUB (HL)
97 SUB A
Opcode Mnemonic
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
Opcode Mnemonic
A8 XOR B
A9 XOR C
AA XOR D
AB XOR E
AC XOR H
AD XOR L
AE XOR (HL)
AF XOR A
Opcode Mnemonic
B0 OR B
B1 OR C
B2 OR D
B3 OR E
B4 OR H
B5 OR L
B6 OR (HL)
B7 OR A
Opcode Mnemonic
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 xx xx JP NZ,nn
C3 xx xx JP nn
C4 xx xx CALL NZ,nn
C5 PUSH BC
C6 xx ADD A,n
C7 RST #0
Opcode Mnemonic
C8 RET Z
C9 RET
CA xx xx JP Z,nn
CB Instruction prefix
CC xx xx CALL Z,nn
CD xx xx CALL nn
CE xx ADC A,n
CF RST #8
Opcode Mnemonic
D0 RET NC
D1 POP DE
D2 xx xx JP NC,nn
D3
D4 xx xx CALL NC,nn
D5 PUSH DE
D6 xx SUB n
D7 RST #10
Opcode Mnemonic
D8 RET C
D9 RETI
DA xx xx JP C,nn
DB
DC xx xx CALL C,nn
DD
DE xx SBC A,n
DF RST #18
Opcode Mnemonic
E0 xx LD (n),A
E1 POP HL
E2 LD (C),A
E3
E4
E5 PUSH HL
E6 xx AND n
E7 RST #20
Opcode Mnemonic
E8 xx ADD SP,e
E9 JP (HL)
EA xx xx LD (nn),A
EB
EC
ED
EE xx XOR n
EF RST #28
Opcode Mnemonic
F0 xx LD A,(n)
F1 POP AF
F2 LD A,(C)
F3 DI
F4
F5 PUSH AF
F6 xx OR n
F7 RST #30
Opcode Mnemonic
F8 xx LDHL SP,e
F9 LD SP,HL
FA xx xx LD A,(nn)
FB EI
FC
FD
FE xx CP n
FF RST #38

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
Opcode Mnemonic
08 RRC B
09 RRC C
0A RRC D
0B RRC E
0C RRC H
0D RRC L
0E RRC (HL)
0F RRC A
Opcode Mnemonic
10 RL B
11 RL C
12 RL D
13 RL E
14 RL H
15 RL L
16 RL (HL)
17 RL A
Opcode Mnemonic
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
Opcode Mnemonic
28 SRA B
29 SRA C
2A SRA D
2B SRA E
2C SRA H
2D SRA L
2E SRA (HL)
2F SRA A
Opcode Mnemonic
30 SWAP B
31 SWAP C
32 SWAP D
33 SWAP E
34 SWAP H
35 SWAP L
36 SWAP (HL)
37 SWAP A
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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
Opcode Mnemonic
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


Oddities

  • On GBZ80, when an interrupt is triggered, the CPU automatically performs a DI before jumping to the interrupt handler. The Z80 does not.
  • On GBZ80, RETI automatically performs an EI. The Z80 does not. Source
  • STOP is normally a 2-byte instruction where the second byte is ignored. Source
  • STOP is used on Gameboy Color to switch between normal speed and double speed CPU modes.
  • 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.
  • The instructions LD A,A, LD B,B, LD C,C, LD D,D, LD E,E, LD H,H and LD L,L are useless. Their existence is just a side effect of how instructions are encoded as opcodes in the CPU. However, some Game Boy emulators (such as BGB) interpret LD B,B as a breakpoint, or LD D,D as a debug message.
  • While the syntax of the 8-bit ADD, ADC and SBC instructions all explicitly mention the A register, the SUB instruction does not mention it.
  • Arithmetic can only really be done on the A register.
  • PUSH and POP instructions utilize a 16-bit operand and the high-order byte is always pushed first and popped last. PUSH HL is PUSH H then L. POP HL is POP L then H.
  • ADD SP,e takes 4 cycles, while LDHL SP,e takes only 3 cycles.


Weblinks