; Z80 emulator with CP/M support. The Z80-specific instructions themselves actually aren't ; implemented yet, making this more of an i8080 emulator. ; ; Copyright (C) 2010 Sprite_tm ; ; This program is free software: you can redistribute it and/or modify ; it under the terms of the GNU General Public License as published by ; the Free Software Foundation, either version 3 of the License, or ; (at your option) any later version. ; ; This program is distributed in the hope that it will be useful, ; but WITHOUT ANY WARRANTY; without even the implied warranty of ; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ; GNU General Public License for more details. ; ; You should have received a copy of the GNU General Public License ; along with this program. If not, see . #if defined atmega8 .include "m8def.inc" #elif defined atmega48 .include "m48def.inc" #else /* default */ .include "m88def.inc" ;FUSE_H=0xDF ;FUSE_L=0xF7 #endif #ifndef F_CPU #define F_CPU 20000000 /* system clock in Hz; defaults to 20MHz */ #endif #ifndef BAUD #define BAUD 38400 /* console baud rate */ #endif ; .equ UBRR_VAL = ((F_CPU+BAUD*8)/(BAUD*16)-1) ; clever rounding #define REFR_RATE 64000 /* dram refresh rate. most drams need 1/15.6µs */ #define REFR_PRE 8 /* timer prescale factor */ #define REFR_CS 0x02 /* timer clock select for 1/8 */ #define REFR_CNT F_CPU / REFR_RATE / REFR_PRE #if defined __ATmega8__ .equ refr_vect = OC2addr #else .equ refr_vect = OC2Aaddr #endif .equ MMC_DEBUG = 0 .equ INS_DEBUG = 0 .equ MEMTEST = 0 .equ BOOTWAIT = 0 .equ PORT_DEBUG = 0 .equ DISK_DEBUG = 0 .equ MEMFILL_CB = 1 .equ STACK_DBG = 0 .equ PRINT_PC = 0 ;Port declarations ; Port D .equ rxd = 0 .equ txd = 1 .equ ram_oe = 2 .equ ram_a8 = 3 .equ mmc_cs = 4 .equ ram_a5 = 5 .equ ram_a6 = 6 .equ ram_a7 = 7 ;Port B .equ ram_a4 = 0 .equ ram_a3 = 1 .equ ram_a2 = 2 .equ ram_a1 = 3 .equ mmc_mosi= 3 .equ ram_a0 = 4 .equ mmc_miso= 4 .equ ram_ras= 5 .equ mmc_sck= 5 ;Port C .equ ram_d1 = 0 .equ ram_w = 1 .equ ram_d2 = 2 .equ ram_d4 = 3 .equ ram_d3 = 4 .equ ram_cas= 5 ;Flag bits in z_flags .equ ZFL_S = 7 .equ ZFL_Z = 6 .equ ZFL_H = 4 .equ ZFL_P = 2 .equ ZFL_N = 1 .equ ZFL_C = 0 ;Register definitions .def z_a = r2 .def z_b = r3 .def z_c = r4 .def z_d = r5 .def z_e = r6 .def z_l = r7 .def z_h = r8 .def z_spl = r9 .def z_sph = r10 .def dsk_trk = r11 .def dsk_sec = r12 .def dsk_dmah = r13 .def dsk_dmal = r14 .def parityb = r15 .def temp = R16 ;The temp register .def temp2 = R17 ;Second temp register .def trace = r18 .def opl = r19 .def oph = r20 .def adrl = r21 .def adrh = r22 .def insdecl = r23 .def z_pcl = r24 .def z_pch = r25 .def insdech = r26 .def z_flags = r27 ;SRAM .dseg ;Sector buffer for 512 byte reads/writes from/to SD-card sectbuff: .byte 512 .cseg .org 0 rjmp start ; reset vector .org refr_vect rjmp refrint ; tim2cmpa .org INT_VECTORS_SIZE start: ldi temp,low(RAMEND) ; top of memory out SPL,temp ; init stack pointer ldi temp,high(RAMEND) ; top of memory out SPH,temp ; init stack pointer ; - Kill wdt wdr #if defined __ATmega8__ ldi temp,0 out MCUCSR,temp ldi temp,(1<",0 rcall printhex rcall printstr .db ".",13,0 pop temp pop zh pop zl .endif ret ;Wait till the mmc answers with the response in temp2, or till a timeout happens. mmcWaitResp: ldi zl,0 ldi zh,0 mmcWaitResploop: rcall mmcByteNoSend cpi temp,0xff brne mmcWaitResploopEnd adiw zl,1 cpi zh,255 breq mmcWaitErr rjmp mmcWaitResploop mmcWaitResploopEnd: ret mmcWaitErr: mov temp,temp2 rcall printhex rcall printstr .db ": Error: MMC resp timeout!",13,0 rjmp resetAVR mmcInit: ldi temp,0x53 out SPCR,temp ;Init start: send 80 clocks with cs disabled sbi PORTD,mmc_cs ldi temp2,20 mmcInitLoop: mov temp,temp2 rcall mmcByte dec temp2 brne mmcInitLoop cbi PORTD,mmc_cs rcall mmcByteNoSend rcall mmcByteNoSend rcall mmcByteNoSend rcall mmcByteNoSend rcall mmcByteNoSend rcall mmcByteNoSend sbi PORTD,mmc_cs rcall mmcByteNoSend rcall mmcByteNoSend rcall mmcByteNoSend rcall mmcByteNoSend ;Send init command cbi PORTD,mmc_cs ldi temp,0xff ;dummy rcall mmcByte ldi temp,0xff ;dummy rcall mmcByte ldi temp,0x40 ;cmd rcall mmcByte ldi temp,0 ;pxh rcall mmcByte ldi temp,0 ;pxl rcall mmcByte ldi temp,0 ;pyh rcall mmcByte ldi temp,0 ;pyl rcall mmcByte ldi temp,0x95 ;crc rcall mmcByte ldi temp,0xff ;return byte rcall mmcByte ldi temp2,0 rcall mmcWaitResp sbi PORTD,mmc_cs rcall mmcByteNoSend ;Read OCR till card is ready ldi temp2,150 mmcInitOcrLoop: push temp2 cbi PORTD,mmc_cs ldi temp,0xff ;dummy rcall mmcByte ldi temp,0x41 ;cmd rcall mmcByte ldi temp,0 ;pxh rcall mmcByte ldi temp,0 ;pxl rcall mmcByte ldi temp,0 ;pyh rcall mmcByte ldi temp,0 ;pyl rcall mmcByte ldi temp,0x95 ;crc rcall mmcByte rcall mmcByteNoSend ldi temp2,1 rcall mmcWaitResp cpi temp,0 breq mmcInitOcrLoopDone sbi PORTD,mmc_cs rcall mmcByteNoSend pop temp2 dec temp2 cpi temp2,0 brne mmcInitOcrLoop ldi temp,4 rjmp mmcWaitErr mmcInitOcrLoopDone: pop temp2 sbi PORTD,mmc_cs rcall mmcByteNoSend ldi temp,0 out SPCR,temp ret ;Call this with adrh:adrl = sector number ;16bit lba address means a max reach of 32M. mmcReadSect: ldi temp,0x50 out SPCR,temp cbi PORTD,mmc_cs rcall mmcByteNoSend ldi temp,0x51 ;cmd (read sector) rcall mmcByte ldi temp,0 lsl adrl rol adrh rol temp rcall mmcByte mov temp,adrh ;pxl rcall mmcByte mov temp,adrl ;pyh rcall mmcByte ldi temp,0 ;pyl rcall mmcByte ldi temp,0x95 ;crc rcall mmcByte ldi temp,0xff ;return byte rcall mmcByte ;resp ldi temp2,2 rcall mmcWaitResp ;data token ldi temp2,3 rcall mmcWaitResp ;Read sector to AVR RAM ldi zl,low(sectbuff) ldi zh,high(sectbuff) mmcreadloop: rcall mmcByteNoSend st z+,temp cpi zl,low(sectbuff+512) brne mmcreadloop cpi zh,high(sectbuff+512) brne mmcreadloop ;CRC rcall mmcByteNoSend rcall mmcByteNoSend sbi PORTD,mmc_cs rcall mmcByteNoSend ldi temp,0 out SPCR,temp ret ;Call this with adrh:adrl = sector number ;16bit lba address means a max reach of 32M. mmcWriteSect: ldi temp,0x50 out SPCR,temp cbi PORTD,mmc_cs rcall mmcByteNoSend ldi temp,0x58 ;cmd (write sector) rcall mmcByte ldi temp,0 lsl adrl rol adrh rol temp rcall mmcByte mov temp,adrh ;pxl rcall mmcByte mov temp,adrl ;pyh rcall mmcByte ldi temp,0 ;pyl rcall mmcByte ldi temp,0x95 ;crc rcall mmcByte ldi temp,0xff ;return byte rcall mmcByte ;resp ldi temp2,1 rcall mmcWaitResp ;Send data token ldi temp,0xfe rcall mmcByte ;Write sector from AVR RAM ldi zl,low(sectbuff) ldi zh,high(sectbuff) mmcwriteloop: ld temp,z+ rcall mmcByte cpi zl,low(sectbuff+512) brne mmcwriteloop cpi zh,high(sectbuff+512) brne mmcwriteloop ;CRC rcall mmcByteNoSend rcall mmcByteNoSend ;Status. Ignored for now. rcall mmcByteNoSend ;Wait till the mmc has written everything mmcwaitwritten: rcall mmcByteNoSend cpi temp,0xff brne mmcwaitwritten sbi PORTD,mmc_cs rcall mmcByteNoSend ldi temp,0 out SPCR,temp ret ;Set up wdt to time out after 1 sec. resetAVR: cli #if defined __ATmega8__ ldi temp,(1< Z80 periph stuff ------------------ .equ memReadByte = dram_read .equ memWriteByte = dram_write ;Fetches a char from the uart to temp. If none available, waits till one is. uartgetc: #if defined __ATmega8__ sbis UCSRA,RXC rjmp uartgetc in temp,UDR #else lds temp,UCSR0A sbrs temp,RXC0 rjmp uartgetc lds temp,UDR0 #endif ret ;Sends a char from temp to the uart. uartputc: #if defined __ATmega8__ uartputc_l: sbis UCSRA,UDRE rjmp uartputc_l out UDR,temp #else push temp uartputc_l: lds temp,UCSR0A sbrs temp,UDRE0 rjmp uartputc_l pop temp sts UDR0,temp #endif ret ; ------------ Fetch phase stuff ----------------- .equ FETCH_NOP = (0<<0) .equ FETCH_A = (1<<0) .equ FETCH_B = (2<<0) .equ FETCH_C = (3<<0) .equ FETCH_D = (4<<0) .equ FETCH_E = (5<<0) .equ FETCH_H = (6<<0) .equ FETCH_L = (7<<0) .equ FETCH_AF = (8<<0) .equ FETCH_BC = (9<<0) .equ FETCH_DE = (10<<0) .equ FETCH_HL = (11<<0) .equ FETCH_SP = (12<<0) .equ FETCH_MBC = (13<<0) .equ FETCH_MDE = (14<<0) .equ FETCH_MHL = (15<<0) .equ FETCH_MSP = (16<<0) .equ FETCH_DIR8 = (17<<0) .equ FETCH_DIR16= (18<<0) .equ FETCH_RST = (19<<0) ;Jump table for fetch routines. Make sure to keep this in sync with the .equs! fetchjumps: .dw do_fetch_nop .dw do_fetch_a .dw do_fetch_b .dw do_fetch_c .dw do_fetch_d .dw do_fetch_e .dw do_fetch_h .dw do_fetch_l .dw do_fetch_af .dw do_fetch_bc .dw do_fetch_de .dw do_fetch_hl .dw do_fetch_sp .dw do_fetch_mbc .dw do_fetch_mde .dw do_fetch_mhl .dw do_fetch_msp .dw do_fetch_dir8 .dw do_fetch_dir16 .dw do_fetch_rst do_fetch_nop: ret do_fetch_a: mov opl,z_a ret do_fetch_b: mov opl,z_b ret do_fetch_c: mov opl,z_c ret do_fetch_d: mov opl,z_d ret do_fetch_e: mov opl,z_e ret do_fetch_h: mov opl,z_h ret do_fetch_l: mov opl,z_l ret do_fetch_af: mov opl,z_flags mov oph,z_a rcall do_op_calcparity andi opl,~(1<HL | ;|EX [SP],xx|------|Exchange |[SP]<->xx | ;|EX AF,AF' |------|Exchange |AF<->AF' | ;|EX DE,HL |------|Exchange |DE<->HL | ;|EXX |------|Exchange |qq<->qq' (except AF)| ;|HALT |------|Halt | | ;|IM n |------|Interrupt Mode | (n=0,1,2)| ;|IN A,[n] |------|Input |A=[n] | ;|IN r,[C] |***P0-|Input |r=[C] | ;|INC r |***V0-|Increment |r=r+1 | ;|INC [HL] |***V0-|Increment |[HL]=[HL]+1 | ;|INC xx |------|Increment |xx=xx+1 | ;|INC [xx+d]|***V0-|Increment |[xx+d]=[xx+d]+1 | ;|INC ss |------|Increment |ss=ss+1 | ;|IND |?*??1-|Input and Decrement |[HL]=[C],HL=HL-1,B=B-1| ;|INDR |?1??1-|Input, Dec., Repeat |IND till B=0 | ;|INI |?*??1-|Input and Increment |[HL]=[C],HL=HL+1,B=B-1| ;|INIR |?1??1-|Input, Inc., Repeat |INI till B=0 | ;|JP [HL] |------|Unconditional Jump |PC=[HL] | ;|JP [xx] |------|Unconditional Jump |PC=[xx] | ;|JP nn |------|Unconditional Jump |PC=nn | ;|JP cc,nn |------|Conditional Jump |If cc JP | ;|JR e |------|Unconditional Jump |PC=PC+e | ;|JR cc,e |------|Conditional Jump |If cc JR(cc=C,NC,NZ,Z)| ;|LD dst,src|------|Load |dst=src | ;|LD A,i |**0*0-|Load |A=i (i=I,R)| ;|LDD |--0*0-|Load and Decrement |[DE]=[HL],HL=HL-1,# | ;|LDDR |--000-|Load, Dec., Repeat |LDD till BC=0 | ;|LDI |--0*0-|Load and Increment |[DE]=[HL],HL=HL+1,# | ;|LDIR |--000-|Load, Inc., Repeat |LDI till BC=0 | ;|NEG |***V1*|Negate |A=-A | ;|NOP |------|No Operation | | ;|OR s |***P00|Logical inclusive OR |A=Avs | ;|OTDR |?1??1-|Output, Dec., Repeat |OUTD till B=0 | ;|OTIR |?1??1-|Output, Inc., Repeat |OUTI till B=0 | ;|OUT [C],r |------|Output |[C]=r | ;|OUT [n],A |------|Output |[n]=A | ;|OUTD |?*??1-|Output and Decrement |[C]=[HL],HL=HL-1,B=B-1| ;|OUTI |?*??1-|Output and Increment |[C]=[HL],HL=HL+1,B=B-1| ;|POP xx |------|Pop |xx=[SP]+ | ;|POP qq |------|Pop |qq=[SP]+ | ;|PUSH xx |------|Push |-[SP]=xx | ;|PUSH qq |------|Push |-[SP]=qq | ;|RES b,m |------|Reset bit |m=m&{~2^b} | ;|RET |------|Return |PC=[SP]+ | ;|RET cc |------|Conditional Return |If cc RET | ;|RETI |------|Return from Interrupt|PC=[SP]+ | ;|RETN |------|Return from NMI |PC=[SP]+ | ;|RL m |**0P0*|Rotate Left |m={CY,m}<- | ;|RLA |--0-0*|Rotate Left Acc. |A={CY,A}<- | ;|RLC m |**0P0*|Rotate Left Circular |m=m<- | ;|RLCA |--0-0*|Rotate Left Circular |A=A<- | ;---------------------------------------------------------------- ;---------------------------------------------------------------- ;|Mnemonic |SZHPNC|Description |Notes | ;|----------+------+---------------------+----------------------| ;|RLD |**0P0-|Rotate Left 4 bits |{A,[HL]}={A,[HL]}<- ##| ;|RR m |**0P0*|Rotate Right |m=->{CY,m} | ;|RRA |--0-0*|Rotate Right Acc. |A=->{CY,A} | ;|RRC m |**0P0*|Rotate Right Circular|m=->m | ;|RRCA |--0-0*|Rotate Right Circular|A=->A | ;|RRD |**0P0-|Rotate Right 4 bits |{A,[HL]}=->{A,[HL]} ##| ;|RST p |------|Restart | (p=0H,8H,10H,...,38H)| ;|SBC A,s |***V1*|Subtract with Carry |A=A-s-CY | ;|SBC HL,ss |**?V1*|Subtract with Carry |HL=HL-ss-CY | ;|SCF |--0-01|Set Carry Flag |CY=1 | ;|SET b,m |------|Set bit |m=mv{2^b} | ;|SLA m |**0P0*|Shift Left Arithmetic|m=m*2 | ;|SRA m |**0P0*|Shift Right Arith. |m=m/2 | ;|SRL m |**0P0*|Shift Right Logical |m=->{0,m,CY} | ;|SUB s |***V1*|Subtract |A=A-s | ;|XOR s |***P00|Logical Exclusive OR |A=Axs | ;|----------+------+--------------------------------------------| ;| F |-*01? |Flag unaffected/affected/reset/set/unknown | ;| S |S |Sign flag (Bit 7) | ;| Z | Z |Zero flag (Bit 6) | ;| HC | H |Half Carry flag (Bit 4) | ;| P/V | P |Parity/Overflow flag (Bit 2, V=overflow) | ;| N | N |Add/Subtract flag (Bit 1) | ;| CY | C|Carry flag (Bit 0) | ;|-----------------+--------------------------------------------| ;| n |Immediate addressing | ;| nn |Immediate extended addressing | ;| e |Relative addressing (PC=PC+2+offset) | ;| [nn] |Extended addressing | ;| [xx+d] |Indexed addressing | ;| r |Register addressing | ;| [rr] |Register indirect addressing | ;| |Implied addressing | ;| b |Bit addressing | ;| p |Modified page zero addressing (see RST) | ;|-----------------+--------------------------------------------| ;|DEFB n(,...) |Define Byte(s) | ;|DEFB 'str'(,...) |Define Byte ASCII string(s) | ;|DEFS nn |Define Storage Block | ;|DEFW nn(,...) |Define Word(s) | ;|-----------------+--------------------------------------------| ;| A B C D E |Registers (8-bit) | ;| AF BC DE HL |Register pairs (16-bit) | ;| F |Flag register (8-bit) | ;| I |Interrupt page address register (8-bit) | ;| IX IY |Index registers (16-bit) | ;| PC |Program Counter register (16-bit) | ;| R |Memory Refresh register | ;| SP |Stack Pointer register (16-bit) | ;|-----------------+--------------------------------------------| ;| b |One bit (0 to 7) | ;| cc |Condition (C,M,NC,NZ,P,PE,PO,Z) | ;| d |One-byte expression (-128 to +127) | ;| dst |Destination s, ss, [BC], [DE], [HL], [nn] | ;| e |One-byte expression (-126 to +129) | ;| m |Any register r, [HL] or [xx+d] | ;| n |One-byte expression (0 to 255) | ;| nn |Two-byte expression (0 to 65535) | ;| pp |Register pair BC, DE, IX or SP | ;| qq |Register pair AF, BC, DE or HL | ;| qq' |Alternative register pair AF, BC, DE or HL | ;| r |Register A, B, C, D, E, H or L | ;| rr |Register pair BC, DE, IY or SP | ;| s |Any register r, value n, [HL] or [xx+d] | ;| src |Source s, ss, [BC], [DE], [HL], nn, [nn] | ;| ss |Register pair BC, DE, HL or SP | ;| xx |Index register IX or IY | ;|-----------------+--------------------------------------------| ;| + - * / ^ |Add/subtract/multiply/divide/exponent | ;| & ~ v x |Logical AND/NOT/inclusive OR/exclusive OR | ;| <- -> |Rotate left/right | ;| [ ] |Indirect addressing | ;| [ ]+ -[ ] |Indirect addressing auto-increment/decrement| ;| { } |Combination of operands | ;| # |Also BC=BC-1,DE=DE-1 | ;| ## |Only lower 4 bits of accumulator A used | ;---------------------------------------------------------------- ;ToDo: Parity at more instructions... .equ AVR_H = 5 .equ AVR_S = 4 .equ AVR_V = 3 .equ AVR_N = 2 .equ AVR_Z = 1 .equ AVR_C = 0 do_op_nop: ret ;---------------------------------------------------------------- ;|Mnemonic |SZHPNC|Description |Notes | ;---------------------------------------------------------------- ;|INC r |***V0-|Increment |r=r+1 | ;|INC [HL] |***V0-|Increment |[HL]=[HL]+1 | ;|INC [xx+d]|***V0-|Increment |[xx+d]=[xx+d]+1 | ; ; OK do_op_inc: andi z_flags, (1<A | ; ; OK do_op_rrc: ;Rotate Right Cyclical. All bits move 1 to the ;right, the lsb becomes c and msb. andi z_flags, ~( (1<{CY,A} | ; ; OK do_op_rr: ;Rotate Right. All bits move 1 to the right, the lsb ;becomes c, c becomes msb. clc sbrc z_flags,ZFL_C sec ror opl in temp,sreg andi z_flags,~( (1< todo rcall do_op_inv mov temp,opl ret ;---------------------------------------------------------------- ;|Mnemonic |SZHPNC|Description |Notes | ;---------------------------------------------------------------- ; ; Not yet checked do_op_scf: ori z_flags,(1< (",0 mov temp,opl rcall printhex rcall printstr .db ")",13,0 .endif mov temp,z_a mov temp2,opl rcall portWrite ret ;---------------------------------------------------------------- ;|Mnemonic |SZHPNC|Description |Notes | ;---------------------------------------------------------------- ; ; Not yet checked do_op_in: ; in a,(opl) .if PORT_DEBUG rcall printstr .db 13,"Port read: (",0 mov temp,opl rcall printhex rcall printstr .db ") -> ",0 .endif mov temp2,opl rcall portRead mov opl,temp .if PORT_DEBUG rcall printhex rcall printstr .db 13,0 .endif ret ;---------------------------------------------------------------- do_op_calcparity: ldi temp2,1 sbrc parityb,0 inc temp2 sbrc parityb,1 inc temp2 sbrc parityb,2 inc temp2 sbrc parityb,3 inc temp2 sbrc parityb,4 inc temp2 sbrc parityb,5 inc temp2 sbrc parityb,6 inc temp2 sbrc parityb,7 inc temp2 andi temp2,1 ret ;---------------------------------------------------------------- do_op_inv: rcall printstr .db "Invalid opcode @ PC=",0,0 mov temp,z_pch rcall printhex mov temp,z_pcl rcall printhex ;---------------------------------------------------------------- haltinv: rjmp haltinv ; ----------------------- Opcode decoding ------------------------- ; Lookup table for Z80 opcodes. Translates the first byte of the instruction word into three ; operations: fetch, do something, store. ; The table is made of 256 words. These 16-bit words consist of ; the fetch operation (bit 0-4), the processing operation (bit 10-16) and the store ; operation (bit 5-9). inst_table: .dw (FETCH_NOP | OP_NOP | STORE_NOP) ; 00 NOP .dw (FETCH_DIR16| OP_NOP | STORE_BC ) ; 01 nn nn LD BC,nn .dw (FETCH_A | OP_NOP | STORE_MBC ) ; 02 LD (BC),A .dw (FETCH_BC | OP_INC16 | STORE_BC ) ; 03 INC BC .dw (FETCH_B | OP_INC | STORE_B ) ; 04 INC B .dw (FETCH_B | OP_DEC | STORE_B ) ; 05 DEC B .dw (FETCH_DIR8 | OP_NOP | STORE_B ) ; 06 nn LD B,n .dw (FETCH_A | OP_RLC | STORE_A ) ; 07 RLCA .dw (FETCH_NOP | OP_INV | STORE_NOP) ; 08 EX AF,AF' (Z80) .dw (FETCH_BC | OP_ADDHL | STORE_HL ) ; 09 ADD HL,BC .dw (FETCH_MBC | OP_NOP | STORE_A ) ; 0A LD A,(BC) .dw (FETCH_BC | OP_DEC16 | STORE_BC ) ; 0B DEC BC .dw (FETCH_C | OP_INC | STORE_C ) ; 0C INC C .dw (FETCH_C | OP_DEC | STORE_C ) ; 0D DEC C .dw (FETCH_DIR8 | OP_NOP | STORE_C ) ; 0E nn LD C,n .dw (FETCH_A | OP_RRC | STORE_A ) ; 0F RRCA .dw (FETCH_NOP | OP_INV | STORE_NOP) ; 10 oo DJNZ o (Z80) .dw (FETCH_DIR16| OP_NOP | STORE_DE ) ; 11 nn nn LD DE,nn .dw (FETCH_A | OP_NOP | STORE_MDE) ; 12 LD (DE),A .dw (FETCH_DE | OP_INC16 | STORE_DE ) ; 13 INC DE .dw (FETCH_D | OP_INC | STORE_D ) ; 14 INC D .dw (FETCH_D | OP_DEC | STORE_D ) ; 15 DEC D .dw (FETCH_DIR8 | OP_NOP | STORE_D ) ; 16 nn LD D,n .dw (FETCH_A | OP_RL | STORE_A ) ; 17 RLA .dw (FETCH_NOP | OP_INV | STORE_NOP) ; 18 oo JR o (Z80) .dw (FETCH_DE | OP_ADDHL | STORE_HL ) ; 19 ADD HL,DE .dw (FETCH_MDE | OP_NOP | STORE_A ) ; 1A LD A,(DE) .dw (FETCH_DE | OP_DEC16 | STORE_DE ) ; 1B DEC DE .dw (FETCH_E | OP_INC | STORE_E ) ; 1C INC E .dw (FETCH_E | OP_DEC | STORE_E ) ; 1D DEC E .dw (FETCH_DIR8 | OP_NOP | STORE_E ) ; 1E nn LD E,n .dw (FETCH_A | OP_RR | STORE_A ) ; 1F RRA .dw (FETCH_NOP | OP_INV | STORE_NOP) ; 20 oo JR NZ,o (Z80) .dw (FETCH_DIR16| OP_NOP | STORE_HL ) ; 21 nn nn LD HL,nn .dw (FETCH_DIR16| OP_STHL | STORE_NOP) ; 22 nn nn LD (nn),HL .dw (FETCH_HL | OP_INC16 | STORE_HL ) ; 23 INC HL .dw (FETCH_H | OP_INC | STORE_H ) ; 24 INC H .dw (FETCH_H | OP_DEC | STORE_H ) ; 25 DEC H .dw (FETCH_DIR8 | OP_NOP | STORE_H ) ; 26 nn LD H,n .dw (FETCH_A | OP_DA | STORE_A ) ; 27 DAA .dw (FETCH_NOP | OP_INV | STORE_NOP) ; 28 oo JR Z,o (Z80) .dw (FETCH_HL | OP_ADDHL | STORE_HL ) ; 29 ADD HL,HL .dw (FETCH_DIR16| OP_RMEM16 | STORE_HL ) ; 2A nn nn LD HL,(nn) .dw (FETCH_HL | OP_DEC16 | STORE_HL ) ; 2B DEC HL .dw (FETCH_L | OP_INC | STORE_L ) ; 2C INC L .dw (FETCH_L | OP_DEC | STORE_L ) ; 2D DEC L .dw (FETCH_DIR8 | OP_NOP | STORE_L ) ; 2E nn LD L,n .dw (FETCH_A | OP_CPL | STORE_A ) ; 2F CPL .dw (FETCH_NOP | OP_INV | STORE_NOP) ; 30 oo JR NC,o (Z80) .dw (FETCH_DIR16| OP_NOP | STORE_SP ) ; 31 nn nn LD SP,nn .dw (FETCH_DIR16| OP_NOP | STORE_AM ) ; 32 nn nn LD (nn),A .dw (FETCH_SP | OP_INC16 | STORE_SP ) ; 33 INC SP .dw (FETCH_MHL | OP_INC | STORE_MHL) ; 34 INC (HL) .dw (FETCH_MHL | OP_DEC | STORE_MHL) ; 35 DEC (HL) .dw (FETCH_DIR8 | OP_NOP | STORE_MHL) ; 36 nn LD (HL),n .dw (FETCH_NOP | OP_SCF | STORE_NOP) ; 37 SCF .dw (FETCH_NOP | OP_INV | STORE_NOP) ; 38 oo JR C,o (Z80) .dw (FETCH_SP | OP_ADDHL | STORE_HL ) ; 39 ADD HL,SP .dw (FETCH_DIR16| OP_RMEM8 | STORE_A ) ; 3A nn nn LD A,(nn) .dw (FETCH_SP | OP_DEC16 | STORE_SP ) ; 3B DEC SP .dw (FETCH_A | OP_INC | STORE_A ) ; 3C INC A .dw (FETCH_A | OP_DEC | STORE_A ) ; 3D DEC A .dw (FETCH_DIR8 | OP_NOP | STORE_A ) ; 3E nn LD A,n .dw (FETCH_NOP | OP_CCF | STORE_NOP) ; 3F CCF (Complement Carry Flag, gvd) .dw (FETCH_B | OP_NOP | STORE_B ) ; 40 LD B,r .dw (FETCH_C | OP_NOP | STORE_B ) ; 41 LD B,r .dw (FETCH_D | OP_NOP | STORE_B ) ; 42 LD B,r .dw (FETCH_E | OP_NOP | STORE_B ) ; 43 LD B,r .dw (FETCH_H | OP_NOP | STORE_B ) ; 44 LD B,r .dw (FETCH_L | OP_NOP | STORE_B ) ; 45 LD B,r .dw (FETCH_MHL | OP_NOP | STORE_B ) ; 46 LD B,r .dw (FETCH_A | OP_NOP | STORE_B ) ; 47 LD B,r .dw (FETCH_B | OP_NOP | STORE_C ) ; 48 LD C,r .dw (FETCH_C | OP_NOP | STORE_C ) ; 49 LD C,r .dw (FETCH_D | OP_NOP | STORE_C ) ; 4A LD C,r .dw (FETCH_E | OP_NOP | STORE_C ) ; 4B LD C,r .dw (FETCH_H | OP_NOP | STORE_C ) ; 4C LD C,r .dw (FETCH_L | OP_NOP | STORE_C ) ; 4D LD C,r .dw (FETCH_MHL | OP_NOP | STORE_C ) ; 4E LD C,r .dw (FETCH_A | OP_NOP | STORE_C ) ; 4F LD C,r .dw (FETCH_B | OP_NOP | STORE_D ) ; 50 LD D,r .dw (FETCH_C | OP_NOP | STORE_D ) ; 51 LD D,r .dw (FETCH_D | OP_NOP | STORE_D ) ; 52 LD D,r .dw (FETCH_E | OP_NOP | STORE_D ) ; 53 LD D,r .dw (FETCH_H | OP_NOP | STORE_D ) ; 54 LD D,r .dw (FETCH_L | OP_NOP | STORE_D ) ; 55 LD D,r .dw (FETCH_MHL | OP_NOP | STORE_D ) ; 56 LD D,r .dw (FETCH_A | OP_NOP | STORE_D ) ; 57 LD D,r .dw (FETCH_B | OP_NOP | STORE_E ) ; 58 LD E,r .dw (FETCH_C | OP_NOP | STORE_E ) ; 59 LD E,r .dw (FETCH_D | OP_NOP | STORE_E ) ; 5A LD E,r .dw (FETCH_E | OP_NOP | STORE_E ) ; 5B LD E,r .dw (FETCH_H | OP_NOP | STORE_E ) ; 5C LD E,r .dw (FETCH_L | OP_NOP | STORE_E ) ; 5D LD E,r .dw (FETCH_MHL | OP_NOP | STORE_E ) ; 5E LD E,r .dw (FETCH_A | OP_NOP | STORE_E ) ; 5F LD E,r .dw (FETCH_B | OP_NOP | STORE_H ) ; 60 LD H,r .dw (FETCH_C | OP_NOP | STORE_H ) ; 61 LD H,r .dw (FETCH_D | OP_NOP | STORE_H ) ; 62 LD H,r .dw (FETCH_E | OP_NOP | STORE_H ) ; 63 LD H,r .dw (FETCH_H | OP_NOP | STORE_H ) ; 64 LD H,r .dw (FETCH_L | OP_NOP | STORE_H ) ; 65 LD H,r .dw (FETCH_MHL | OP_NOP | STORE_H ) ; 66 LD H,r .dw (FETCH_A | OP_NOP | STORE_H ) ; 67 LD H,r .dw (FETCH_B | OP_NOP | STORE_L ) ; 68 LD L,r .dw (FETCH_C | OP_NOP | STORE_L ) ; 69 LD L,r .dw (FETCH_D | OP_NOP | STORE_L ) ; 6A LD L,r .dw (FETCH_E | OP_NOP | STORE_L ) ; 6B LD L,r .dw (FETCH_H | OP_NOP | STORE_L ) ; 6C LD L,r .dw (FETCH_L | OP_NOP | STORE_L ) ; 6D LD L,r .dw (FETCH_MHL | OP_NOP | STORE_L ) ; 6E LD L,r .dw (FETCH_A | OP_NOP | STORE_L ) ; 6F LD L,r .dw (FETCH_B | OP_NOP | STORE_MHL) ; 70 LD (HL),r .dw (FETCH_C | OP_NOP | STORE_MHL) ; 71 LD (HL),r .dw (FETCH_D | OP_NOP | STORE_MHL) ; 72 LD (HL),r .dw (FETCH_E | OP_NOP | STORE_MHL) ; 73 LD (HL),r .dw (FETCH_H | OP_NOP | STORE_MHL) ; 74 LD (HL),r .dw (FETCH_L | OP_NOP | STORE_MHL) ; 75 LD (HL),r .dw (FETCH_NOP | OP_NOP | STORE_NOP) ; 76 HALT .dw (FETCH_A | OP_NOP | STORE_MHL) ; 77 LD (HL),r .dw (FETCH_B | OP_NOP | STORE_A ) ; 78 LD A,r .dw (FETCH_C | OP_NOP | STORE_A ) ; 79 LD A,r .dw (FETCH_D | OP_NOP | STORE_A ) ; 7A LD A,r .dw (FETCH_E | OP_NOP | STORE_A ) ; 7B LD A,r .dw (FETCH_H | OP_NOP | STORE_A ) ; 7C LD A,r .dw (FETCH_L | OP_NOP | STORE_A ) ; 7D LD A,r .dw (FETCH_MHL | OP_NOP | STORE_A ) ; 7E LD A,r .dw (FETCH_A | OP_NOP | STORE_A ) ; 7F LD A,r .dw (FETCH_B | OP_ADDA | STORE_A ) ; 80 ADD A,r .dw (FETCH_C | OP_ADDA | STORE_A ) ; 81 ADD A,r .dw (FETCH_D | OP_ADDA | STORE_A ) ; 82 ADD A,r .dw (FETCH_E | OP_ADDA | STORE_A ) ; 83 ADD A,r .dw (FETCH_H | OP_ADDA | STORE_A ) ; 84 ADD A,r .dw (FETCH_L | OP_ADDA | STORE_A ) ; 85 ADD A,r .dw (FETCH_MHL | OP_ADDA | STORE_A ) ; 86 ADD A,r .dw (FETCH_A | OP_ADDA | STORE_A ) ; 87 ADD A,r .dw (FETCH_B | OP_ADCA | STORE_A ) ; 88 ADC A,r .dw (FETCH_C | OP_ADCA | STORE_A ) ; 89 ADC A,r .dw (FETCH_D | OP_ADCA | STORE_A ) ; 8A ADC A,r .dw (FETCH_E | OP_ADCA | STORE_A ) ; 8B ADC A,r .dw (FETCH_H | OP_ADCA | STORE_A ) ; 8C ADC A,r .dw (FETCH_L | OP_ADCA | STORE_A ) ; 8D ADC A,r .dw (FETCH_MHL | OP_ADCA | STORE_A ) ; 8E ADC A,r .dw (FETCH_A | OP_ADCA | STORE_A ) ; 8F ADC A,r .dw (FETCH_B | OP_SUBFA | STORE_A ) ; 90 SUB A,r .dw (FETCH_C | OP_SUBFA | STORE_A ) ; 91 SUB A,r .dw (FETCH_D | OP_SUBFA | STORE_A ) ; 92 SUB A,r .dw (FETCH_E | OP_SUBFA | STORE_A ) ; 93 SUB A,r .dw (FETCH_H | OP_SUBFA | STORE_A ) ; 94 SUB A,r .dw (FETCH_L | OP_SUBFA | STORE_A ) ; 95 SUB A,r .dw (FETCH_MHL | OP_SUBFA | STORE_A ) ; 96 SUB A,r .dw (FETCH_A | OP_SUBFA | STORE_A ) ; 97 SUB A,r .dw (FETCH_B | OP_SBCFA | STORE_A ) ; 98 SBC A,r .dw (FETCH_C | OP_SBCFA | STORE_A ) ; 99 SBC A,r .dw (FETCH_D | OP_SBCFA | STORE_A ) ; 9A SBC A,r .dw (FETCH_E | OP_SBCFA | STORE_A ) ; 9B SBC A,r .dw (FETCH_H | OP_SBCFA | STORE_A ) ; 9C SBC A,r .dw (FETCH_L | OP_SBCFA | STORE_A ) ; 9D SBC A,r .dw (FETCH_MHL | OP_SBCFA | STORE_A ) ; 9E SBC A,r .dw (FETCH_A | OP_SBCFA | STORE_A ) ; 9F SBC A,r .dw (FETCH_B | OP_ANDA | STORE_A ) ; A0 AND A,r .dw (FETCH_C | OP_ANDA | STORE_A ) ; A1 AND A,r .dw (FETCH_D | OP_ANDA | STORE_A ) ; A2 AND A,r .dw (FETCH_E | OP_ANDA | STORE_A ) ; A3 AND A,r .dw (FETCH_H | OP_ANDA | STORE_A ) ; A4 AND A,r .dw (FETCH_L | OP_ANDA | STORE_A ) ; A5 AND A,r .dw (FETCH_MHL | OP_ANDA | STORE_A ) ; A6 AND A,r .dw (FETCH_A | OP_ANDA | STORE_A ) ; A7 AND A,r .dw (FETCH_B | OP_XORA | STORE_A ) ; A8 XOR A,r .dw (FETCH_C | OP_XORA | STORE_A ) ; A9 XOR A,r .dw (FETCH_D | OP_XORA | STORE_A ) ; AA XOR A,r .dw (FETCH_E | OP_XORA | STORE_A ) ; AB XOR A,r .dw (FETCH_H | OP_XORA | STORE_A ) ; AC XOR A,r .dw (FETCH_L | OP_XORA | STORE_A ) ; AD XOR A,r .dw (FETCH_MHL | OP_XORA | STORE_A ) ; AE XOR A,r .dw (FETCH_A | OP_XORA | STORE_A ) ; AF XOR A,r .dw (FETCH_B | OP_ORA | STORE_A ) ; B0 OR A,r .dw (FETCH_C | OP_ORA | STORE_A ) ; B1 OR A,r .dw (FETCH_D | OP_ORA | STORE_A ) ; B2 OR A,r .dw (FETCH_E | OP_ORA | STORE_A ) ; B3 OR A,r .dw (FETCH_H | OP_ORA | STORE_A ) ; B4 OR A,r .dw (FETCH_L | OP_ORA | STORE_A ) ; B5 OR A,r .dw (FETCH_MHL | OP_ORA | STORE_A ) ; B6 OR A,r .dw (FETCH_A | OP_ORA | STORE_A ) ; B7 OR A,r .dw (FETCH_B | OP_SUBFA | STORE_NOP) ; B8 CP A,r .dw (FETCH_C | OP_SUBFA | STORE_NOP) ; B9 CP A,r .dw (FETCH_D | OP_SUBFA | STORE_NOP) ; BA CP A,r .dw (FETCH_E | OP_SUBFA | STORE_NOP) ; BB CP A,r .dw (FETCH_H | OP_SUBFA | STORE_NOP) ; BC CP A,r .dw (FETCH_L | OP_SUBFA | STORE_NOP) ; BD CP A,r .dw (FETCH_MHL | OP_SUBFA | STORE_NOP) ; BE CP A,r .dw (FETCH_A | OP_SUBFA | STORE_NOP) ; BF CP A,r .dw (FETCH_NOP | OP_IFNZ | STORE_RET) ; C0 RET NZ .dw (FETCH_NOP | OP_POP16 | STORE_BC ) ; C1 POP BC .dw (FETCH_DIR16| OP_IFNZ | STORE_PC ) ; C2 nn nn JP NZ,nn .dw (FETCH_DIR16| OP_NOP | STORE_PC ) ; C3 nn nn JP nn .dw (FETCH_DIR16| OP_IFNZ | STORE_CALL) ; C4 nn nn CALL NZ,nn .dw (FETCH_BC | OP_PUSH16 | STORE_NOP) ; C5 PUSH BC .dw (FETCH_DIR8 | OP_ADDA | STORE_A ) ; C6 nn ADD A,n .dw (FETCH_RST | OP_NOP | STORE_CALL) ; C7 RST 0 .dw (FETCH_NOP | OP_IFZ | STORE_RET) ; C8 RET Z .dw (FETCH_NOP | OP_NOP | STORE_RET) ; C9 RET .dw (FETCH_DIR16| OP_IFZ | STORE_PC ) ; CA nn nn JP Z,nn .dw (FETCH_NOP | OP_INV | STORE_NOP) ; CB (Z80 specific) .dw (FETCH_DIR16| OP_IFZ | STORE_CALL) ; CC nn nn CALL Z,nn .dw (FETCH_DIR16| OP_NOP | STORE_CALL) ; CD nn nn CALL nn .dw (FETCH_DIR8 | OP_ADCA | STORE_A ) ; CE nn ADC A,n .dw (FETCH_RST | OP_NOP | STORE_CALL) ; CF RST 8H .dw (FETCH_NOP | OP_IFNC | STORE_RET) ; D0 RET NC .dw (FETCH_NOP | OP_POP16 | STORE_DE ) ; D1 POP DE .dw (FETCH_DIR16| OP_IFNC | STORE_PC ) ; D2 nn nn JP NC,nn .dw (FETCH_DIR8 | OP_OUTA | STORE_NOP) ; D3 nn OUT (n),A .dw (FETCH_DIR16| OP_IFNC | STORE_CALL) ; D4 nn nn CALL NC,nn .dw (FETCH_DE | OP_PUSH16 | STORE_NOP) ; D5 PUSH DE .dw (FETCH_DIR8 | OP_SUBFA | STORE_A ) ; D6 nn SUB n .dw (FETCH_RST | OP_NOP | STORE_CALL) ; D7 RST 10H .dw (FETCH_NOP | OP_IFC | STORE_RET) ; D8 RET C .dw (FETCH_NOP | OP_INV | STORE_NOP) ; D9 EXX (Z80) .dw (FETCH_DIR16| OP_IFC | STORE_PC ) ; DA nn nn JP C,nn .dw (FETCH_DIR8 | OP_IN | STORE_A ) ; DB nn IN A,(n) .dw (FETCH_DIR16| OP_IFC | STORE_CALL) ; DC nn nn CALL C,nn .dw (FETCH_NOP | OP_INV | STORE_NOP) ; DD (Z80) .dw (FETCH_DIR8 | OP_SBCFA | STORE_A ) ; DE nn SBC A,n .dw (FETCH_RST | OP_NOP | STORE_CALL) ; DF RST 18H .dw (FETCH_NOP | OP_IFPO | STORE_RET) ; E0 RET PO .dw (FETCH_NOP | OP_POP16 | STORE_HL ) ; E1 POP HL .dw (FETCH_DIR16| OP_IFPO | STORE_PC ) ; E2 nn nn JP PO,nn .dw (FETCH_MSP | OP_EXHL | STORE_MSP) ; E3 EX (SP),HL .dw (FETCH_DIR16| OP_IFPO | STORE_CALL) ; E4 nn nn CALL PO,nn .dw (FETCH_HL | OP_PUSH16 | STORE_NOP) ; E5 PUSH HL .dw (FETCH_DIR8 | OP_ANDA | STORE_A ) ; E6 nn AND n .dw (FETCH_RST | OP_NOP | STORE_CALL) ; E7 RST 20H .dw (FETCH_NOP | OP_IFPE | STORE_RET) ; E8 RET PE .dw (FETCH_HL | OP_NOP | STORE_PC ) ; E9 JP (HL) .dw (FETCH_DIR16| OP_IFPE | STORE_PC ) ; EA nn nn JP PE,nn .dw (FETCH_DE | OP_EXHL | STORE_DE ) ; EB EX DE,HL .dw (FETCH_DIR16| OP_IFPE | STORE_CALL) ; EC nn nn CALL PE,nn .dw (FETCH_NOP | OP_INV | STORE_NOP) ; ED (Z80 specific) .dw (FETCH_DIR8 | OP_XORA | STORE_A ) ; EE nn XOR n .dw (FETCH_RST | OP_NOP | STORE_CALL) ; EF RST 28H .dw (FETCH_NOP | OP_IFP | STORE_RET) ; F0 RET P .dw (FETCH_NOP | OP_POP16 | STORE_AF ) ; F1 POP AF .dw (FETCH_DIR16| OP_IFP | STORE_PC ) ; F2 nn nn JP P,nn .dw (FETCH_NOP | OP_DI | STORE_NOP) ; F3 DI .dw (FETCH_DIR16| OP_IFP | STORE_CALL) ; F4 nn nn CALL P,nn .dw (FETCH_AF | OP_PUSH16 | STORE_NOP) ; F5 PUSH AF .dw (FETCH_DIR8 | OP_ORA | STORE_A ) ; F6 nn OR n .dw (FETCH_RST | OP_NOP | STORE_CALL) ; F7 RST 30H .dw (FETCH_NOP | OP_IFM | STORE_RET) ; F8 RET M .dw (FETCH_HL | OP_NOP | STORE_SP ) ; F9 LD SP,HL .dw (FETCH_DIR16| OP_IFM | STORE_PC ) ; FA nn nn JP M,nn .dw (FETCH_NOP | OP_EI | STORE_NOP) ; FB EI .dw (FETCH_DIR16| OP_IFM | STORE_CALL) ; FC nn nn CALL M,nn .dw (FETCH_NOP | OP_INV | STORE_NOP) ; FD (Z80 specific) .dw (FETCH_DIR8 | OP_SUBFA | STORE_NOP) ; FE nn CP n .dw (FETCH_RST | OP_NOP | STORE_CALL) ; FF RST 38H