home *** CD-ROM | disk | FTP | other *** search
- ** Main file of the Z80 emulator. Compiles to linkable code, using the
- ** following settings:
-
- ** VERBOSE
- ** Boring Messages During Compilation.
-
- PROCESSOR EQU 68030
- ** Define to any of 68000, 68010, 68020, 68030 or 68040. The 68000 version
- ** uses the Move from Status Register instruction. Presently, the > 68000
- ** versions are all the same.
-
- ** GENERIC_OBJECT SET 1
- ** Define to compile generic Z80 emulator object file, which needs
- ** linking with separately compiled routines for implementation-
- ** dependent instructions. If not defined, macros from "machine_macs.i"
- ** are used and are inline expanded. See the files "extern_instr.a" and
- ** "impldept.i" for more information about this.
-
- Z80_MEMCHECK SET 1
- ** Define to use memory write access checking.
- ** See MemoryHandler below for more information about this.
-
- UPDATECACHE SET 1
- ** Define to update the cache on every write to Z80 memory. This is done
- ** by simply clearing the corresponding word in the cache. If this option
- ** is not used, modified code will never work.
-
- MODIFIEDCODE SET 1
- ** Define to detect (and allow) modified code even in multi-byte opcodes.
- ** Pretty damn useless if UPDATECACHE is not defined. If this option is
- ** not used, then such modifications that only change the second or third
- ** bytes of an opcode, but not the first byte, will not be detected.
-
- ** UNDOCINSTR_UNDEF SET 1
- ** Define if you want the "undocumented" instructions to be considered
- ** as undefined instructions.
-
- BCDFLAGS
- ** Define if you want the arithmetic instructions to store information
- ** so that a following Daa will work correctly (see the file "notes.txt"
- ** for details). BASIC interpreters and other programs that work in
- ** decimal base often use BCD, while most games do not. The main use there
- ** seems to be for score counter displays.
- ** If this flag is not defined, then calling the Daa instruction will
- ** write a nonzero value into the Z80_BCD_OP field, which otherwise will
- ** always be zero. That way it should be easy to see if it is the missing
- ** BCD handling that causes any erroneous behaviour.
-
- ** AFPUSHPOP_CCR
- ** Define if you want the Push/Pop AF instructions to store the F register
- ** on 680x0 CCR form, instead of the real Z80 form. The difference lies in
- ** how the flags are ordered within the byte. For instance, in the 680x0,
- ** bit 3 is the sign flag; in the Z80, it is bit 7. Only programs that
- ** inspect the pushed flags (like a debugger) will ever notice this. The
- ** CCR version is, of course, a bit quicker, and could be used for games.
- ** In neither case are bits in the unused positions (including H and N)
- ** guaranteed to survive an operation that affects any of the flags.
- ** Is IS guaranteed, that a Pop AF with a following Push AF (or vice versa)
- ** and no flag-affecting instructions there inbetween, will preserve all
- ** the transferred bits.
-
- ** AFPUSHPOP_BCD
- ** Define if you want the Push/Pop AF instructions to preserve BCD data.
- ** If used, the information used for BCD will be stored separately in an
- ** internal circular stack that keeps the last 7 pushed data units.
- ** The time penalty is reasonable, but this option is hardly ever needed.
- ** (Interrupts could be a problem. See the file "notes.txt" for details.)
- ** For game-playing only, this should definitely be turned off. Many
- ** games use Push/Pop AF/BC/DE/HL/IX/IY to transfer graphics data quickly.
-
- ** ======================================================================
-
-
- ** Register aliases used (see the file Z80_coding.i for definitions):
-
- ** TableB pointer to TableBase
- ** Work pointer to the Z80_Workspace longword
- ** PPC Pseudo-PC
- ** ZSP Z80 Stack Pointer (only lower word used)
- ** Z0 pointer to Z80 address zero
- ** CacheB pointer to CacheBase (corresponding to Z0)
- ** FlagsB pointer to FlagsBase (corresponding to Z0)
- ** InstrB pointer to InstructionBase
-
- ** Be careful!! Some aliases might stand for the same register!
- ** (TableB and Work are presently the same.)
-
- ** ---------------------------------------------------------------------
-
- Z80_MAIN = -1 ;Tell include file we are compiling the main file.
-
- INCLUDE user.i ;User definitions. ALWAYS included first of all.
-
- INCLUDE Z80.i
-
- INCLUDE Z80_struct.i
-
- INCLUDE Z80_coding.i
-
- INCLUDE tables.i
-
- INCLUDE helpfuncts.i
-
- ** ----------------------------------------------------------------------
-
- ** When calling Z80_Init, Z80_Coldstart or Z80_Continue, a pointer to the
- ** control structure is always passed in a0, and a return value is passed
- ** in d0. All other registers are automatically protected
-
- ProtectedRegs REG d1-d7/a1-a6 ;push/pop these at entry/exit
-
- ** Registers stored at Z80_RegStorage at exit,
- ** and restored upon continuing:
-
- StoredRegs REG d0-d5/a2-a6
- ;a0 (TableB) always comes as a parameter.
- ;a1 (PPC) is recalculated from Real-PC at Continue.
- ;d6 is recalculated from F at Continue.
- ;d7 is garbage anyway.
-
- ** Remember: if you change this, you must also change the labels
- ** in the Z80_RegStorage table in Z80_struct.i.
-
- ** ======================================================================
-
- ** EMULATOR ENTRY POINTS
-
-
- ** Before beginning emulation, the control structure must be initialised
- ** by calling Z80_Init.
- ** a0 must point to the control structure. The fields Z80_Memory and
- ** Z80_Cachemem must be pointing to allocated memory.
- ** If the memory write access checking feature is used, the field
- ** Z80_Flagmem must also be set, and if Z80_MemHandler is nonzero
- ** it is supposed to point to a user memory exception handler. See
- ** MemoryHandler below for details.
- ** The user environment data area is not changed. All other fields
- ** are automatically initialised to zero.
- ** The return value in d0 is nonzero if an error occurred, and zero
- ** otherwise. All other registers are automatically protected.
-
- Z80_Init
- movem.l a0/a1/a2,-(sp) ;temporaries
-
- ;Save the protected control structure entries on the stack:
- move.w #(PROT_SIZE>>1)-1,d0 ;word count
- lea PROT_FIELDS(a0),a2 ;source ptr in a2
- .prot_save move.w (a2)+,-(sp)
- dbf d0,.prot_save
-
- ;Then clear all entries below envdata:
- move.l a0,a1
- move.w #(Z80_Envdata>>1)-1,d0 ;envdata offset is even
- .clr_struct clr.w (a1)+
- dbf d0,.clr_struct
-
- ;and restore the saved entries (a2 has retained its value):
- move.w #(PROT_SIZE>>1)-1,d0 ;word count
- .prot_rest move.w (sp)+,-(a2)
- dbf d0,.prot_rest
-
- ;Set all entries in the cache (skipping the low end buffer)
- ;to 'changed', that is, not decoded:
- move.l Z80_Cachemem(a0),a1
- add.l #Z80_LBUFSIZE,a1
- move.l #Z80_MEMSIZE,d0 ;word count
- .clr_cache clr.w (a1)+
- subq.l #1,d0 ;possibly too large to use dbf
- bne.s .clr_cache
- ;(a1 should now point to the first entry in the high buffer)
-
- ;Set all entries in the high buffer to 'out of bounds':
- move.w #(Z80_HBUFSIZE>>1)-1,d0 ;buffers are even sized
- .set_hibuf move.w #out_of_bounds,(a1)+
- dbf d0,.set_hibuf
-
- ;Now copy the tables to their places in the structure:
-
- ;The parity table
- lea ParityTable(pc),a1
- lea Z80_Parity(a0),a2
- move.w #256-1,d0
- .cp_parity move.b (a1)+,(a2)+
- dbf d0,.cp_parity
-
- ;Calculate the 'address zero' pointers:
-
- move.l Z80_Memory(a0),a1
- add.l #Z80_0_OFFSET,a1
- move.l a1,Z80_zero(a0)
-
- move.l Z80_Cachemem(a0),a1
- add.l #CACHE_0_OFFSET,a1
- move.l a1,Z80_cachezero(a0)
-
- IFD Z80_MEMCHECK
- move.l Z80_Flagmem(a0),a1
- add.l #FLAGS_0_OFFSET,a1
- move.l a1,Z80_flagzero(a0)
- ENDC
-
- ;Create an initial "saved CPU status" frame, so we can
- ;call Z80_Continue without calling Z80_Coldstart first.
- movem.l ProtectedRegs,-(sp)
- bsr InitRegisters ;(only use aliases from now)
- ;Initially look like after a reset.
- move.l CacheB,PPC ;PC = address zero
- move.b #-1,Z80_INTMOD(TableB) ;Intmode 0
- movem.l StoredRegs,Z80_RegStorage(TableB)
- movem.l (sp)+,ProtectedRegs
-
- movem.l (sp)+,a0/a1/a2 ;restore temporaries
-
- moveq #0,d0 ;signal 'no error'
- rts
-
- ** ----------------------------------------------------------------------
-
-
- ** Enter here to start emulation 'from scratch', with a CPU reset.
- ** a0 must point to the control structure, which must be initialised
- ** (see Z80_Init above).
- ** The return value in d0 is nonzero if an error occurred, and zero
- ** otherwise. All other registers are automatically protected.
-
- Z80_Coldstart
- movem.l ProtectedRegs,-(sp)
-
- bsr InitRegisters
-
- ;From this point on, registers may only be referred to
- ;by their aliases.
-
- move.w #-1,Z80_Running(TableB)
-
- bra RESEThandler ;reset and start emulation
-
-
- ;Subroutine common to Z80_Init and Z80_Coldstart.
- ;Initialises the registers that need initialisation.
- InitRegisters
- move.l Z80_zero(TableB),Z0
-
- move.l Z80_cachezero(TableB),CacheB
-
- IFD Z80_MEMCHECK
- move.l Z80_flagzero(TableB),FlagsB
- ELSE
- lea 0.w,FlagsB
- ENDC
-
- lea InstrBase(pc),InstrB
-
- moveq #0,A ;The high byte of the words used to
- moveq #0,B ; hold 8-bit registers must be zero
- moveq #0,C ; for indexing into parity table.
- moveq #0,D
- moveq #0,E
-
- rts
-
- ** ----------------------------------------------------------------------
-
-
- ** Enter here to continue as if nothing happened since last exit
- ** (unless the saved processor status has been manipulated).
- ** Changes to other fields than the CPU status structure entries
- ** are not recommended; calling Z80_Continue does not guarantee
- ** that such changes have any effect (see Z80_NewSettings in helpfuncts.i).
- ** a0 must point to the control structure.
- ** The return value in d0 is the same as for Z80_Coldstart. All other
- ** registers are automatically protected.
-
- Z80_Continue
- movem.l ProtectedRegs,-(sp)
-
- ;Calculate alt_CCR and d6 from F' and F (method from 'Pop AF' routine)
- ;We need a scratch register, so do this before restoring the rest.
- lea Pop_AF_table(pc),a1 ;use a1 as scratch
-
- move.b Z80_alt_F(a0),d6
- rol.b #2,d6 ;SZ-h-VnC -> -h-VnCSZ
- move.b d6,d7
- and.w #$001F,d7 ;d7 = 000VnCSZ
- and.w #%11100000,d6 ;d6 = -h-00000
- or.b (a1,d7.w),d6 ;d6 = -h-XNZVC
- move.w d6,Z80_alt_CCR(a0)
-
- move.b Z80_F(a0),d6
- rol.b #2,d6 ;SZ-h-VnC -> -h-VnCSZ
- move.b d6,d7
- and.w #$001F,d7 ;d7 = 000VnCSZ
- and.w #%11100000,d6 ;d6 = -h-00000
- or.b (a1,d7.w),d6 ;d6 = -h-XNZVC
- ;now d6 holds the active flags on CCR form
-
- ;Restore the other registers, apart from PPC
- movem.l Z80_RegStorage(a0),StoredRegs
-
- ;from here on, we refer to a0 as TableB:
-
- ;Calculate Pseudo-PC from (possibly modified) Real-PC
- move.w Z80_PC(TableB),d7
- makePPC
-
- ;Signal 'emulator running'
- move.w #-1,Z80_Running(TableB)
-
- next ;go on emulating
-
- ** ----------------------------------------------------------------------
-
-
- ** This emulation of processor request lines makes sure that the interrupts
- ** behave as they should. Requests are currently only tested for after flow
- ** control instructions, but that seems to be quite sufficient.
- ** A request overrides those of lower priority. The priority order is:
- ** EXIT, RESET, (BUSRQ), NMI and INT. BUSRQ is currently not implemented.
- ** The status of the requests of lower priority is stored, so no requests
- ** are lost. (The highest priority request of course never needs storing).
- ** The priorities are hard coded; here and in each of the handlers.
-
- ** The requests could be called from hardware interrupts, keypresses,
- ** menus or whatever. They do not affect any registers (apart from CCR),
- ** and return nothing.
- ** a0 must contain a pointer to the control structure.
-
- ;In order of priority:
-
- Z80_EXITreq ;unconditional
- move.w #20,Z80_ReqLvl(a0) ;highest priority
- move.w #EXIThandler-InstrBase,Z80_Request(a0)
- rts
-
- Z80_RESETreq cmpi.w #2,Z80_ReqLvl(a0)
- bge.s .queued
- move.w #2,Z80_ReqLvl(a0)
- move.w #RESEThandler-InstrBase,Z80_Request(a0)
- .queued move.w #RESEThandler-InstrBase,Z80_RES_FF(a0)
- rts
-
- Z80_NMIreq cmpi.w #1,Z80_ReqLvl(a0)
- bge.s .queued
- move.w #1,Z80_ReqLvl(a0)
- move.w #NMIhandler-InstrBase,Z80_Request(a0)
- .queued move.w #NMIhandler-InstrBase,Z80_NMI_FF(a0)
- rts
-
- Z80_INTreq btst #6,Z80_IFF(a0) ;Test IFF1
- beq.s .disabled
- tst.w Z80_ReqLvl(a0)
- bne.s .queued ;any nonzero level is higher
- ;doesn't have to raise the level - this is the lowest
- move.w #INThandler-InstrBase,Z80_Request(a0)
- .queued move.w #INThandler-InstrBase,Z80_INT_FF(a0)
- .disabled rts
-
-
- ** ========================================================================
-
- ** EMULATOR INTERNALS
-
-
- ** The routines between this line and InstrBase are called using a negative
- ** word offset from InstrBase. I do not expect address space problems here.
-
- ** ------------------------------------------------------------------------
-
- ** The following routines handle accepted requests. They are executed
- ** exactly as a z80 instruction routine, which means: don't thrash any
- ** registers but the 'scratch' ones, and end with a "next" macro call.
-
- ** The exception detection is simple. Every now and then, the Z80_Request
- ** word is tested, and if it is nonzero it is taken as offset from
- ** InstrBase to a handler. When the corresponding handler is reached, the
- ** PPC points to the first word of the instruction to execute after
- ** returning from the exception.
-
- ** Any waiting requests have to be considered. The priority levels are hard
- ** coded, which makes testing easier, but you'll have to watch out if you
- ** change any of this.
-
- ** --------------
-
- EXIThandler
-
- ** Returns from emulator call. A nonzero value is returned in d0 if an
- ** error occurred, and zero otherwise.
- ** The registers are stored upon exit, to make it possible to continue
- ** later. PPC is not stored, instead Real PC is stored in Z80_PC, which can
- ** be changed in order to continue at another address.
- ** For instance, assume an instruction patched to cause EXIT, directly
- ** followed by the string 17,'horace.code',0 is reached. Z80_zero+Z80_PC
- ** would after exit point to the number 17, which could mean 'Load, using
- ** the following zero-terminated string as filename'. After loading,
- ** Z80_PC would be set to point to the byte following the zero, and
- ** Z80_Continue would be called. This way, a Z80-program could call host
- ** system services without affecting the processor status (apart from the
- ** Program Counter).
-
- ;Here, any other request could be waiting.
- move.w Z80_RES_FF(TableB),d7
- beq.s .not_reset
-
- ;if RESET:
- move.w d7,Z80_Request(TableB)
- clr.w Z80_RES_FF(TableB)
- move.w #2,Z80_ReqLvl(TableB)
- bra.s .go_on
-
- .not_reset move.w Z80_NMI_FF(TableB),d7
- beq.s .not_nmi
-
- ;if NMI:
- move.w d7,Z80_Request(TableB)
- clr.w Z80_NMI_FF(TableB)
- move.w #1,Z80_ReqLvl(TableB)
- bra.s .go_on
-
- .not_nmi ;then INT is the only one left
- clr.w Z80_ReqLvl(TableB)
- move.w Z80_INT_FF(TableB),Z80_Request(TableB)
- clr.w Z80_INT_FF(TableB)
-
- .go_on
- ;Store registers:
- movem.l StoredRegs,Z80_RegStorage(TableB)
-
- ;Calculate and store Real PC
- getRPC
- move.w d7,Z80_PC(TableB)
-
- ;Calculate and store F and F' (method from 'Push AF' routine)
- ; d6 holds CCR form of F.
- lea Push_AF_table(pc),ZSP ;use ZSP as scratch pointer
-
- move.w d6,d7
- and.w #%11100000,d6 ;d6 = ---00000
- and.w #$001F,d7 ;d7 = 000XNZVC
- or.b (ZSP,d7.w),d6 ;d6 = ---VnCSZ
- ror.b #2,d6 ;d6 = SZ---VnC
- move.b d6,Z80_F(TableB)
-
- move.w Z80_alt_CCR(TableB),d6
- move.w d6,d7
- and.w #%11100000,d6 ;d6 = ---00000
- and.w #$001F,d7 ;d7 = 000XNZVC
- or.b (Work,d7.w),d6 ;d6 = ---VnCSZ
- ror.b #2,d6 ;d6 = SZ---VnC
- move.b d6,Z80_alt_F(TableB)
-
- ;Signal that emulation has stopped
- clr.w Z80_Running(TableB)
-
- ;Restore caller's registers
- movem.l (sp)+,ProtectedRegs
-
- moveq #0,d0 ;signal No Error
- rts
-
- ** --------------
-
- RESEThandler
- ;All waiting requests (of lower priority than RESET)
- ;will be cleared anyway.
-
- ** These are the only well-defined actions at reset:
-
- move.l CacheB,PPC ;PC = address zero
- clr.b Z80_I(TableB) ;I register = 0
- clr.b Z80_R(TableB) ;R register = 0
- clr.b Z80_IFF(TableB) ;clear IFF
- move.b #-1,Z80_INTMOD(TableB) ;Intmode 0
-
- ;and some of my internal flags must be reset:
- clr.w Z80_Request(TableB)
- clr.w Z80_ReqLvl(TableB)
- clr.w Z80_INT_FF(TableB)
- clr.w Z80_NMI_FF(TableB)
- clr.w Z80_RES_FF(TableB)
-
- next
- ** --------------
-
- NMIhandler
-
- ** Nonmaskable interrupt: Call $66
-
- ;Here, the priority level is 1 and only an INT could be waiting.
- clr.w Z80_ReqLvl(TableB)
- move.w Z80_INT_FF(TableB),Z80_Request(TableB)
- clr.w Z80_INT_FF(TableB)
-
- move.b Z80_IFF(TableB),d7
- add.b d7,d7 ;Neverneverland <- IFF2 <- IFF1 <- 0
- move.b d7,Z80_IFF(TableB)
- getRPC
- move.w d7,(Work) ;push PC
- decw ZSP
- putz (Work),ZSP
- decw ZSP
- putz d7,ZSP,2 ;2nd use
- lea 2*$66(CacheB),PPC
- next
- ** -------------
-
- INThandler
-
- ** For faster selection,INTmode holds -1 to 1 instead of 0 to 2.
-
- ;The priority level is 0 and only another INT could be waiting.
- move.w Z80_INT_FF(TableB),Z80_Request(TableB)
- clr.w Z80_INT_FF(TableB)
-
- clr.b Z80_IFF(TableB) ;clear IFF:s
- tst.b Z80_INTMOD(TableB)
- bne.s .not_1
-
- ** Intmode 1: Call $38
-
- getRPC
- move.w d7,(Work) ;push real PC onto Z80 stack
- decw ZSP
- putz (Work),ZSP
- decw ZSP
- putz d7,ZSP,2 ;2nd use
- lea 2*$38(CacheB),PPC
- next
-
- .not_1 bmi.s .mode0
-
- ** Intmode 2:
- ** ( I register * 256 + byte on data bus ) AND $fffe (even address)
- ** forms the pointer to the interrupt vector.
-
- getRPC
- move.w d7,(Work) ;push PC
- decw ZSP
- putz (Work),ZSP,3 ;3rd use
- decw ZSP
- putz d7,ZSP,4 ;4th use
- move.b Z80_I(TableB),(Work)
- move.w (Work),d7 ;get I * 256
- clr.b d7 ;(data bus assumed =00)
- getz d7,1(Work)
- incw d7
- getz d7,(Work) ;get vector
- move.w (Work),d7
- makePPC
- next
-
- ** Intmode 0 is currently not implemented. It should wait for
- ** external hardware to put an instruction on the data bus.
-
- .mode0 next
-
- ** --------------
-
- IFD Z80_MEMCHECK
-
- ** The memory handler is called when a write to a marked address is
- ** detected. (That is, when the corresponding memory flag is nonzero
- ** upon a write to some address.)
- ** The following types of actions are possible:
-
- ** Read-only (writes are ignored)
- ** Access counter increment
- ** Call user-defined handler
-
- ** The user-defined handler call has some overhead, and is not
- ** recommended for memory addresses/areas that are written to very often,
- ** like bit-mapped display memory.
-
- ** When the memory handler is reached, the address (word) and value (byte)
- ** are found on the user stack. The offsets are WRITE_ADDR and WRITE_VAL,
- ** and are defined together with the putz() macro in "Z80_coding.i".
-
- ** The memory handler is called in mid-execution of an instruction. All
- ** registers may contain important information and must be protected
- ** before use. Only the base pointer registers can be assumed to have their
- ** proper values. Not even the Pseudo-PC can be guaranteed to be valid.
- ** Because of this, it is not possible to extract any information about
- ** the current Z80 Cpu status during a memory handler call (I'm sorry).
- ** Single-step procedures _in_combination_with_ memory write access
- ** checking could be used for such purposes.
-
- ;Memory flag values (signed byte):
- ; negative (-1 to -128) read-only
- ; 0 ok to write (no detection)
- ; 1 to Z80_MEM_CNTNUM access counters
- ; Z80_MEM_CNTNUM+1 to Z80_MEM_USR-1 reserved
- ; Z80_MEM_USR to 127 user-defined handler call
- ;The constants are defined in Z80.i, but are fairly hard-coded
- ;in the detection routine below.
-
- MemoryHandler
- ;It is assumed here that a1 and a2 correspond to PPC
- ;and ZSP (the ordering is unimportant) !
-
- movem.l d1/a1,-(sp)
- move.w 8+WRITE_ADDR(sp),a1 ;get Z80 address off stack
- move.b (FlagsB,a1.w),d1 ;get flag. it is never 0.
- bmi.s .ROMexit ;if flag negative, just don't write.
-
- ext.w d1 ;make flag a whole (positive) word.
-
- ;access counters range from 1 to Z80_MEMCNT_NUM
- cmp.w #Z80_MEM_CNTNUM,d1
- bgt.s .notcnt
-
- ;if access counter:
- subq.w #1,d1 ;index from 0
- add.w d1,d1
- add.w d1,d1 ;counters are longword-sized
- addq.l #1,Z80_AccessCnt(TableB,d1.w)
- lsr.w #2,d1 ;get byte-size back
- tst.b Z80_CntType(TableB,d1.w) ;test counter type
- bne.s .ROMexit ;no write if nonzero
-
- .write_exit move.b 8+WRITE_VAL(sp),d1 ;get value
- writemem d1,a1 ;write value to dest
- .ROMexit movem.l (sp)+,d1/a1
- rts
-
- .notcnt cmp.w #Z80_MEM_USR,d1
- blt.s .write_exit ;if 'reserved', treat as 0 flag
-
- ;make exception numbers range from 0 to Z80_MEMUSR_NUM-1
- sub.w #Z80_MEM_USR,d1
-
- ;Call user exception handler:
- ; d1 contains the exception number (word).
- ; d2 contains the value (byte).
- ; a1 contains the Z80 address (word).
- ; a2 is scratch (address of user-def routine).
- ;Handler return values:
- ; d1 zero (longword) if value should be written, nonzero if not.
- ; d2 contains the value (byte).
- ;Changes to a1 and a2 have no effect. All other registers
- ;must be protected before using.
-
- move.l d2,-(sp) ;protect register d2
- movem.l a1/a2,-(sp) ;protect Z80 address and a2
-
- move.l Z80_MemHandler(TableB),d2 ;get handler pointer
- beq.s .usr_nocall ;only if pointer nonzero
-
- movea.l d2,a2 ;use a2 for call
- move.b 8+4+8+WRITE_VAL(sp),d2 ;get value off stack
- jsr (a2) ;make the call
-
- .usr_cont movem.l (sp)+,a1/a2 ;restore Z80 address and a2
- tst.l d1 ;test the returned d1
- bne.s .usr_exit ;no write if nonzero
- writemem d2,a1 ;write value to Z80 address
-
- .usr_exit move.l (sp)+,d2 ;restore d2
- movem.l (sp)+,d1/a1 ;same as .ROMexit above
- rts
-
- .usr_nocall moveq #0,d1 ;signal "write"
- move.b 8+4+8+WRITE_VAL(sp),d2 ;get value off stack
- bra.s .usr_cont ;pretend we did call
-
- ENDC ;IFD Z80_MEMCHECK
- ** --------------
-
- ** End of 'exception handlers'. The following are assorted routines
- ** that are also called using "jmp offset(InstrB)":
-
- ** --------------
-
- ** Offsets and instruction decoding routines for prefixed instructions
-
- INCLUDE prefix_offsets.i
-
- ** --------------
-
- ** This routine is jumped to when a prefix decoding routine detects an
- ** 'out of bounds' pointer. It sets the pointer being updated to
- ** 'changed', to assure a re-decode at next execution. This is necessary
- ** since the modified-code tests cannot handle wrap-around themselves.
- ** Then it moves the PPC to its corresponding location in the lower buffer,
- ** and restarts decoding.
-
- GoLowBuf clr.w -2(PPC) ;clear the current pointer
- sub.l #$20000,PPC ;back 128 K
- bra DecodeInstr ;decode instruction all over again
- ;Note: there should really be a testreq here as well,
- ;or we could end up with an eternal run-around-memory loop.
- ** --------------
-
- ** This label is jumped to when a modified multi-byte instruction is
- ** found. PPC is pointing to the word after the one just executed. Any
- ** instruction whose opcode bytes cross the 7fff border will always be
- ** redecoded before execution. The actual wrap-around handling is done by
- ** the decoding routines.
-
- StalePtr
- ;Fall through into 'decode instruction':
-
- ** --------------
-
- ** This routine corresponds to the negative cache pointer used to mark an
- ** address as read, used, and unchanged since, but not itself decoded.
-
- NotDecoded Nop ;Fastest way to get a negative offset.
- ;Fall through straight into 'decode instruction':
-
- ** --------------
-
- ** All routines not handling normal Z80 instructions, but which will still
- ** be jumped to using "jmp offset(InstrB)" should have a negative offset,
- ** and thus be placed on this side of InstrBase. This is to save address
- ** space for positive offsets.
- ** Presently, the only negative pointer that may occur in the cache is
- ** the 'unchanged' offset used with prefixed instructions.
-
- ** ==============
-
- InstrBase
-
- base = InstrBase ;An abbreviation used by the offset tables.
-
- ** ==============
-
- ** It is assumed throughout the program that the 'decode instruction'
- ** routine is placed here, and so corresponds to a zero word in the
- ** cache. Upon entry, PPC points to the (word corresponding to the) byte
- ** following the first opcode byte of the instruction.
-
- DecodeInstr
- getRPC
- decw d7 ;get first byte
- getz d7,d7
- and.w #$00ff,d7
- add.w d7,d7
- move.w offsets(PC,d7.w),d7
- move.w d7,-2(PPC)
- jmp (InstrB,d7.w)
-
- ** In case the read byte was a prefix, the jump will be straight to the
- ** corresponding prefixed instruction decoding routine, which will
- ** overwrite the same cache address with a new pointer.
-
- ** The unprefixed instruction offsets are placed here for the PC-relative
- ** addressing mode above.
-
- INCLUDE std_offsets.i
-
- ** --------------
-
- ** This routine does wrap-around, if it is executed. A pointer to it pads
- ** the end of the cache memory, and should be detected as invalid by the
- ** 'modified opcode?' tests of the prefixed instructions. Presently, this
- ** means it has a nonnegative pointer. PPC points to the word after the
- ** one that was just executed.
-
- OutOfBounds sub.l #$20002,PPC ;back 128K and one word
- testreq ;so we can EXITreq even if memory is all non-jumps
-
- ** --------------
-
- ** This is the normal case of undefined opcode: a 2-byte no-op.
-
- Undef_Opcode_2 opcode_2_bytes
- skip 1
- next
-
- ** And a more rare form: a 3-byte opcode no-op with an unused offset
- ** byte, giving a total of 4 bytes.
-
- Undef_Opcode_3 opcode_3_bytes
- skip 3
- next
-
- ** --------------
-
- ** Calculate the standard offsets:
-
- unchanged = NotDecoded-InstrBase
- stale_ptr = StalePtr-InstrBase
- go_low_buf = GoLowBuf-InstrBase
- out_of_bounds = OutOfBounds-InstrBase
- undef = Undef_Opcode_2-InstrBase
- undef_3byte = Undef_Opcode_3-InstrBase
- IFD Z80_MEMCHECK
- memhandler = MemoryHandler-InstrBase
- ENDC
-
- ** If a 'generic object' is compiled, some of these _constants_
- ** could be referred to externally, and must thus be exported.
-
- IFD GENERIC_OBJECT
- XDEF unchanged
- XDEF stale_ptr
- XDEF go_low_buf
- XDEF out_of_bounds
- IFD Z80_MEMCHECK
- XDEF memhandler
- ENDC
- ENDC
-
- ** --------------
-
- INCLUDE std_instr.i ;Non-implementation-dependent instructions
-
- INCLUDE impldept.i ;Implementation-dependent instructions
-
- INCLUDE undoc_instr.i ;The "undocumented" instructions. Refers
- ;to labels in impldept.i
- EVEN
- endrange ;Actually the address after the last routine, but if
- ;margins are that small, you'd want to rewrite some
- ;stuff anyway. Perhaps move it to distant.i.
-
- IFD VERBOSE
- LIST
- ** Offset of (the address after) the last "near" instruction routine.
- maxoffset = endrange-InstrBase
- NOLIST
- ELSE
- maxoffset = endrange-InstrBase
- ENDC
-
- IFNE maxoffset>$7FFF
- FAIL Not enough address space for instruction routines.
- ENDC
-
- ** --------------
-
- INCLUDE distant.i ;Routines removed from the 0-7FFF range.
- ;The instruction labels must be within the
- ;range, but jump (absolute long) straight
- ;on to these labels, named "d_<instr>".
-
-
- ** ========================================================================
-