/[gxemul]/trunk/src/cpus/cpu_dyntrans.c
This is repository of my old source code which isn't updated any more. Go to git.rot13.org for current projects!
ViewVC logotype

Annotation of /trunk/src/cpus/cpu_dyntrans.c

Parent Directory Parent Directory | Revision Log Revision Log


Revision 24 - (hide annotations)
Mon Oct 8 16:19:56 2007 UTC (16 years, 6 months ago) by dpavlin
File MIME type: text/plain
File size: 48276 byte(s)
++ trunk/HISTORY	(local)
$Id: HISTORY,v 1.1256 2006/06/23 20:43:44 debug Exp $
20060219	Various minor updates. Removing the old MIPS16 skeleton code,
		because it will need to be rewritten for dyntrans anyway.
20060220-22	Removing the non-working dyntrans backend support.
		Continuing on the 64-bit dyntrans virtual memory generalization.
20060223	More work on the 64-bit vm generalization.
20060225	Beginning on MIPS dyntrans load/store instructions.
		Minor PPC updates (64-bit load/store, etc).
		Fixes for the variable-instruction-length framework, some
		minor AVR updates (a simple Hello World program works!).
		Beginning on a skeleton for automatically generating documen-
		tation (for devices etc.).
20060226	PPC updates (adding some more 64-bit instructions, etc).
		AVR updates (more instructions).
		FINALLY found and fixed the zs bug, making NetBSD/macppc
		accept the serial console.
20060301	Adding more AVR instructions.
20060304	Continuing on AVR-related stuff. Beginning on a framework for
		cycle-accurate device emulation. Adding an experimental "PAL
		TV" device (just a dummy so far).
20060305	Adding more AVR instructions.
		Adding a dummy epcom serial controller (for TS7200 emulation).
20060310	Removing the emul() command from configuration files, so only
		net() and machine() are supported.
		Minor progress on the MIPS dyntrans rewrite.
20060311	Continuing on the MIPS dyntrans rewrite (adding more
		instructions, etc).
20060315	Adding more instructions (sllv, srav, srlv, bgtz[l], blez[l],
		beql, bnel, slti[u], various loads and stores).
20060316	Removing the ALWAYS_SIGNEXTEND_32 option, since it was rarely
		used.
		Adding more MIPS dyntrans instructions, and fixing bugs.
20060318	Implementing fast loads/stores for MIPS dyntrans (big/little
		endian, 32-bit and 64-bit modes).
20060320	Making MIPS dyntrans the default configure option; use
		"--enable-oldmips" to use the old bintrans system.
		Adding MIPS dyntrans dmult[u]; minor updates.
20060322	Continuing... adding some more instructions.
		Adding a simple skeleton for demangling C++ "_ZN" symbols.
20060323	Moving src/debugger.c into a new directory (src/debugger/).
20060324	Fixing the hack used to load PPC ELFs (useful for relocated
		Linux/ppc kernels), and adding a dummy G3 machine mode.
20060325-26	Beginning to experiment with GDB remote serial protocol
		connections; adding a -G command line option for selecting
		which TCP port to listen to.
20060330	Beginning a major cleanup to replace things like "0x%016llx"
		with more correct "0x%016"PRIx64, etc.
		Continuing on the GDB remote serial protocol support.
20060331	More cleanup, and some minor GDB remote progress.
20060402	Adding a hack to the configure script, to allow compilation
		on systems that lack PRIx64 etc.
20060406	Removing the temporary FreeBSD/arm hack in dev_ns16550.c and
		replacing it with a better fix from Olivier Houchard.
20060407	A remote debugger (gdb or ddd) can now start and stop the
		emulator using the GDB remote serial protocol, and registers
		and memory can be read. MIPS only for now.
20060408	More GDB progress: single-stepping also works, and also adding
		support for ARM, PowerPC, and Alpha targets.
		Continuing on the delay-slot-across-page-boundary issue.
20060412	Minor update: beginning to add support for the SPARC target
		to the remote GDB functionality.
20060414	Various MIPS updates: adding more instructions for dyntrans
		(eret, add), and making some exceptions work. Fixing a bug
		in dmult[u].
		Implementing the first SPARC instructions (sethi, or).
20060415	Adding "magic trap" instructions so that PROM calls can be
		software emulated in MIPS dyntrans.
		Adding more MIPS dyntrans instructions (ddiv, dadd) and
		fixing another bug in dmult.
20060416	More MIPS dyntrans progress: adding [d]addi, movn, movz, dsllv,
		rfi, an ugly hack for supporting R2000/R3000 style faked caches,
		preliminary interrupt support, and various other updates and
		bugfixes.
20060417	Adding more SPARC instructions (add, sub, sll[x], sra[x],
		srl[x]), and useful SPARC header definitions.
		Adding the first (trivial) x86/AMD64 dyntrans instructions (nop,
		cli/sti, stc/clc, std/cld, simple mov, inc ax). Various other
		x86 updates related to variable instruction length stuff.
		Adding unaligned loads/stores to the MIPS dyntrans mode (but
		still using the pre-dyntrans (slow) imlementation).
20060419	Fixing a MIPS dyntrans exception-in-delay-slot bug.
		Removing the old "show opcode statistics" functionality, since
		it wasn't really useful and isn't implemented for dyntrans.
		Single-stepping (or running with instruction trace) now looks
		ok with dyntrans with delay-slot architectures.
20060420	Minor hacks (removing the -B command line option when compiled
		for non-bintrans, and some other very minor updates).
		Adding (slow) MIPS dyntrans load-linked/store-conditional.
20060422	Applying fixes for bugs discovered by Nils Weller's nwcc
		(static DEC memmap => now per machine, and adding an extern
		keyword in cpu_arm_instr.c).
		Finally found one of the MIPS dyntrans bugs that I've been
		looking for (copy/paste spelling error BIG vs LITTLE endian in
		cpu_mips_instr_loadstore.c for 16-bit fast stores).
		FINALLY found the major MIPS dyntrans bug: slti vs sltiu
		signed/unsigned code in cpu_mips_instr.c. :-)
		Adding more MIPS dyntrans instructions (lwc1, swc1, bgezal[l],
		ctc1, tlt[u], tge[u], tne, beginning on rdhwr).
		NetBSD/hpcmips can now reach userland when using dyntrans :-)
		Adding some more x86 dyntrans instructions.
		Finally removed the old Alpha-specific virtual memory code,
		and replaced it with the generic 64-bit version.
		Beginning to add disassembly support for SPECIAL3 MIPS opcodes.
20060423	Continuing on the delay-slot-across-page-boundary issue;
		adding an end_of_page2 ic slot (like I had planned before, but
		had removed for some reason).
		Adding a quick-and-dirty fallback to legacy coprocessor 1
		code (i.e. skipping dyntrans implementation for now).
		NetBSD/hpcmips and NetBSD/pmax (when running on an emulated
		R4400) can now be installed and run. :-)  (Many bugs left
		to fix, though.)
		Adding more MIPS dyntrans instructions: madd[u], msub[u].
		Cleaning up the SPECIAL2 vs R5900/TX79/C790 "MMI" opcode
		maps somewhat (disassembly and dyntrans instruction decoding).
20060424	Adding an isa_revision field to mips_cpu_types.h, and making
		sure that SPECIAL3 opcodes cause Reserved Instruction
		exceptions on MIPS32/64 revisions lower than 2.
		Adding the SPARC 'ba', 'call', 'jmpl/retl', 'and', and 'xor'
		instructions.
20060425	Removing the -m command line option ("run at most x 
		instructions") and -T ("single_step_on_bad_addr"), because
		they never worked correctly with dyntrans anyway.
		Freshening up the man page.
20060428	Adding more MIPS dyntrans instructions: bltzal[l], idle.
		Enabling MIPS dyntrans compare interrupts.
20060429	FINALLY found the weird dyntrans bug, causing NetBSD etc. to
		behave strangely: some floating point code (conditional
		coprocessor branches) could not be reused from the old
		non-dyntrans code. The "quick-and-dirty fallback" only appeared
		to work. Fixing by implementing bc1* for MIPS dyntrans.
		More MIPS instructions: [d]sub, sdc1, ldc1, dmtc1, dmfc1, cfc0.
		Freshening up MIPS floating point disassembly appearance.
20060430	Continuing on C790/R5900/TX79 disassembly; implementing 128-bit
		"por" and "pextlw".
20060504	Disabling -u (userland emulation) unless compiled as unstable
		development version.
		Beginning on freshening up the testmachine include files,
		to make it easier to reuse those files (placing them in
		src/include/testmachine/), and beginning on a set of "demos"
		or "tutorials" for the testmachine functionality.
		Minor updates to the MIPS GDB remote protocol stub.
		Refreshing doc/experiments.html and gdb_remote.html.
		Enabling Alpha emulation in the stable release configuration,
		even though no guest OSes for Alpha can run yet.
20060505	Adding a generic 'settings' object, which will contain
		references to settable variables (which will later be possible
		to access using the debugger).
20060506	Updating dev_disk and corresponding demo/documentation (and
		switching from SCSI to IDE disk types, so it actually works
		with current test machines :-).
20060510	Adding a -D_LARGEFILE_SOURCE hack for 64-bit Linux hosts,
		so that fseeko() doesn't give a warning.
		Updating the section about how dyntrans works (the "runnable
		IR") in doc/intro.html.
		Instruction updates (some x64=1 checks, some more R5900
		dyntrans stuff: better mul/mult separation from MIPS32/64,
		adding ei and di).
		Updating MIPS cpuregs.h to a newer one (from NetBSD).
		Adding more MIPS dyntrans instructions: deret, ehb.
20060514	Adding disassembly and beginning implementation of SPARC wr
		and wrpr instructions.
20060515	Adding a SUN SPARC machine mode, with dummy SS20 and Ultra1
		machines. Adding the 32-bit "rd psr" instruction.
20060517	Disassembly support for the general SPARC rd instruction.
		Partial implementation of the cmp (subcc) instruction.
		Some other minor updates (making sure that R5900 processors
		start up with the EIE bit enabled, otherwise Linux/playstation2
		receives no interrupts).
20060519	Minor MIPS updates/cleanups.
20060521	Moving the MeshCube machine into evbmips; this seems to work
		reasonably well with a snapshot of a NetBSD MeshCube kernel.
		Cleanup/fix of MIPS config0 register initialization.
20060529	Minor MIPS fixes, including a sign-extension fix to the
		unaligned load/store code, which makes NetBSD/pmax on R3000
		work better with dyntrans. (Ultrix and Linux/DECstation still
		don't work, though.)
20060530	Minor updates to the Alpha machine mode: adding an AlphaBook
		mode, an LCA bus (forwarding accesses to an ISA bus), etc.
20060531	Applying a bugfix for the MIPS dyntrans sc[d] instruction from
		Ondrej Palkovsky. (Many thanks.)
20060601	Minifix to allow ARM immediate msr instruction to not give
		an error for some valid values.
		More Alpha updates.
20060602	Some minor Alpha updates.
20060603	Adding the Alpha cmpbge instruction. NetBSD/alpha prints its
		first boot messages :-) on an emulated Alphabook 1.
20060612	Minor updates; adding a dev_ether.h include file for the
		testmachine ether device. Continuing the hunt for the dyntrans
		bug which makes Linux and Ultrix on DECstation behave
		strangely... FINALLY found it! It seems to be related to
		invalidation of the translation cache, on tlbw{r,i}. There
		also seems to be some remaining interrupt-related problems.
20060614	Correcting the implementation of ldc1/sdc1 for MIPS dyntrans
		(so that it uses 16 32-bit registers if the FR bit in the
		status register is not set).
20060616	REMOVING BINTRANS COMPLETELY!
		Removing the old MIPS interpretation mode.
		Removing the MFHILO_DELAY and instruction delay stuff, because
		they wouldn't work with dyntrans anyway.
20060617	Some documentation updates (adding "NetBSD-archive" to some
		URLs, and new Debian/DECstation installation screenshots).
		Removing the "tracenull" and "enable-caches" configure options.
		Improving MIPS dyntrans performance somewhat (only invalidate
		translations if necessary, on writes to the entryhi register,
		instead of doing it for all cop0 writes).
20060618	More cleanup after the removal of the old MIPS emulation.
		Trying to fix the MIPS dyntrans performance bugs/bottlenecks;
		only semi-successful so far (for R3000).
20060620	Minor update to allow clean compilation again on Tru64/Alpha.
20060622	MIPS cleanup and fixes (removing the pc_last stuff, which
		doesn't make sense with dyntrans anyway, and fixing a cross-
		page-delay-slot-with-exception case in end_of_page).
		Removing the old max_random_cycles_per_chunk stuff, and the
		concept of cycles vs instructions for MIPS emulation.
		FINALLY found and fixed the bug which caused NetBSD/pmax
		clocks to behave strangely (it was a load to the zero register,
		which was treated as a NOP; now it is treated as a load to a
		dummy scratch register).
20060623	Increasing the dyntrans chunk size back to
		N_SAFE_DYNTRANS_LIMIT, instead of N_SAFE_DYNTRANS_LIMIT/2.
		Preparing for a quick release, even though there are known
		bugs, and performance for non-R3000 MIPS emulation is very
		poor. :-/
		Reverting to half the dyntrans chunk size again, because
		NetBSD/cats seemed less stable with full size chunks. :(
		NetBSD/sgimips 3.0 can now run :-)  (With release 0.3.8, only
		NetBSD/sgimips 2.1 worked, not 3.0.)

==============  RELEASE 0.4.0  ==============


1 dpavlin 14 /*
2 dpavlin 22 * Copyright (C) 2005-2006 Anders Gavare. All rights reserved.
3 dpavlin 14 *
4     * Redistribution and use in source and binary forms, with or without
5     * modification, are permitted provided that the following conditions are met:
6     *
7     * 1. Redistributions of source code must retain the above copyright
8     * notice, this list of conditions and the following disclaimer.
9     * 2. Redistributions in binary form must reproduce the above copyright
10     * notice, this list of conditions and the following disclaimer in the
11     * documentation and/or other materials provided with the distribution.
12     * 3. The name of the author may not be used to endorse or promote products
13     * derived from this software without specific prior written permission.
14     *
15     * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
16     * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
17     * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
18     * ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
19     * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
20     * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
21     * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
22     * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
23     * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
24     * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
25     * SUCH DAMAGE.
26     *
27     *
28 dpavlin 24 * $Id: cpu_dyntrans.c,v 1.99 2006/06/23 20:43:44 debug Exp $
29 dpavlin 14 *
30     * Common dyntrans routines. Included from cpu_*.c.
31     */
32    
33    
34     #ifdef DYNTRANS_CPU_RUN_INSTR
35 dpavlin 22 #if 1 /* IC statistics: */
36 dpavlin 18 static void gather_statistics(struct cpu *cpu)
37     {
38 dpavlin 22 struct DYNTRANS_IC *ic = cpu->cd.DYNTRANS_ARCH.next_ic;
39     static long long n = 0;
40     static FILE *f = NULL;
41    
42     n++;
43     if (n < 100000000)
44     return;
45    
46     if (f == NULL) {
47     f = fopen("instruction_call_statistics.raw", "w");
48     if (f == NULL) {
49     fatal("Unable to open statistics file for output.\n");
50     exit(1);
51     }
52     }
53     fwrite(&ic->f, 1, sizeof(void *), f);
54     }
55     #else /* PC statistics: */
56     static void gather_statistics(struct cpu *cpu)
57     {
58 dpavlin 18 uint64_t a;
59     int low_pc = ((size_t)cpu->cd.DYNTRANS_ARCH.next_ic - (size_t)
60     cpu->cd.DYNTRANS_ARCH.cur_ic_page) / sizeof(struct DYNTRANS_IC);
61     if (low_pc < 0 || low_pc >= DYNTRANS_IC_ENTRIES_PER_PAGE)
62     return;
63    
64 dpavlin 20 #if 0
65 dpavlin 18 /* Use the physical address: */
66     cpu->cd.DYNTRANS_ARCH.cur_physpage = (void *)
67     cpu->cd.DYNTRANS_ARCH.cur_ic_page;
68     a = cpu->cd.DYNTRANS_ARCH.cur_physpage->physaddr;
69     #else
70     /* Use the PC (virtual address): */
71     a = cpu->pc;
72     #endif
73    
74     a &= ~((DYNTRANS_IC_ENTRIES_PER_PAGE-1) <<
75     DYNTRANS_INSTR_ALIGNMENT_SHIFT);
76     a += low_pc << DYNTRANS_INSTR_ALIGNMENT_SHIFT;
77    
78     /*
79     * TODO: Everything below this line should be cleaned up :-)
80     */
81     a &= 0x03ffffff;
82     {
83     static long long *array = NULL;
84     static char *array_16kpage_in_use = NULL;
85     static int n = 0;
86     a >>= DYNTRANS_INSTR_ALIGNMENT_SHIFT;
87     if (array == NULL)
88     array = zeroed_alloc(sizeof(long long) * 16384*1024);
89     if (array_16kpage_in_use == NULL)
90     array_16kpage_in_use = zeroed_alloc(sizeof(char) * 1024);
91     a &= (16384*1024-1);
92     array[a] ++;
93     array_16kpage_in_use[a / 16384] = 1;
94     n++;
95     if ((n & 0x3fffffff) == 0) {
96     FILE *f = fopen("statistics.out", "w");
97     int i, j;
98     printf("Saving statistics... "); fflush(stdout);
99     for (i=0; i<1024; i++)
100     if (array_16kpage_in_use[i]) {
101     for (j=0; j<16384; j++)
102     if (array[i*16384 + j] > 0)
103 dpavlin 24 fprintf(f, "%lli\t"
104     "0x%016"PRIx64"\n",
105     (uint64_t)array[i*16384+j],
106     (uint64_t)((i*16384+j) <<
107     DYNTRANS_INSTR_ALIGNMENT_SHIFT));
108 dpavlin 18 }
109     fclose(f);
110     printf("n=0x%08x\n", n);
111     }
112     }
113     }
114 dpavlin 22 #endif /* PC statistics */
115 dpavlin 18
116 dpavlin 24
117 dpavlin 18 #define S gather_statistics(cpu)
118    
119 dpavlin 24
120 dpavlin 18 #ifdef DYNTRANS_VARIABLE_INSTRUCTION_LENGTH
121 dpavlin 20 #define I ic = cpu->cd.DYNTRANS_ARCH.next_ic; \
122 dpavlin 22 cpu->cd.DYNTRANS_ARCH.next_ic += ic->arg[0]; \
123 dpavlin 20 ic->f(cpu, ic);
124 dpavlin 18 #else
125 dpavlin 24
126     /* The normal instruction execution core: */
127     #define I ic = cpu->cd.DYNTRANS_ARCH.next_ic ++; ic->f(cpu, ic);
128    
129     /* For heavy debugging: */
130     /* #define I ic = cpu->cd.DYNTRANS_ARCH.next_ic ++; \
131     { \
132     int low_pc = ((size_t)cpu->cd.DYNTRANS_ARCH.next_ic - \
133     (size_t)cpu->cd.DYNTRANS_ARCH.cur_ic_page) / \
134     sizeof(struct DYNTRANS_IC); \
135     printf("cur_ic_page=%p ic=%p (low_pc=0x%x)\n", \
136     cpu->cd.DYNTRANS_ARCH.cur_ic_page, \
137     ic, low_pc << DYNTRANS_INSTR_ALIGNMENT_SHIFT); \
138     } \
139     ic->f(cpu, ic); */
140    
141     /* static long long nr_of_I_calls = 0; */
142    
143     /* Temporary hack for finding NULL bugs: */
144     /* #define I ic = cpu->cd.DYNTRANS_ARCH.next_ic ++; \
145     nr_of_I_calls ++; \
146     if (ic->f == NULL) { \
147     int low_pc = ((size_t)cpu->cd.DYNTRANS_ARCH.next_ic - \
148     (size_t)cpu->cd.DYNTRANS_ARCH.cur_ic_page) / \
149     sizeof(struct DYNTRANS_IC); \
150     cpu->pc &= ~((DYNTRANS_IC_ENTRIES_PER_PAGE-1) << \
151     DYNTRANS_INSTR_ALIGNMENT_SHIFT); \
152     cpu->pc += (low_pc << DYNTRANS_INSTR_ALIGNMENT_SHIFT);\
153     printf("Crash at %016"PRIx64"\n", cpu->pc); \
154     printf("nr of I calls: %lli\n", nr_of_I_calls); \
155     printf("Next ic = %p\n", cpu->cd. \
156     DYNTRANS_ARCH.next_ic); \
157     printf("cur ic page = %p\n", cpu->cd. \
158     DYNTRANS_ARCH.cur_ic_page); \
159     cpu->running = 0; \
160     return 0; \
161     } \
162     ic->f(cpu, ic); */
163    
164     /* Temporary hack for MIPS, to hunt for 32-bit/64-bit sign-extension bugs: */
165     /* #define I { int k; for (k=1; k<=31; k++) \
166     cpu->cd.mips.gpr[k] = (int32_t)cpu->cd.mips.gpr[k];\
167     if (cpu->cd.mips.gpr[0] != 0) { \
168     fatal("NOOOOOO\n"); exit(1); \
169     } \
170     ic = cpu->cd.DYNTRANS_ARCH.next_ic ++; ic->f(cpu, ic); }
171     */
172 dpavlin 18 #endif
173    
174    
175 dpavlin 14 /*
176     * XXX_cpu_run_instr():
177     *
178     * Execute one or more instructions on a specific CPU, using dyntrans.
179     *
180     * Return value is the number of instructions executed during this call,
181     * 0 if no instructions were executed.
182     */
183     int DYNTRANS_CPU_RUN_INSTR(struct emul *emul, struct cpu *cpu)
184     {
185 dpavlin 24 /*
186     * TODO: Statistics stuff!
187     */
188     int show_opcode_statistics = 0;
189    
190     #ifdef DYNTRANS_DUALMODE_32
191     uint64_t cached_pc;
192     #else
193 dpavlin 14 uint32_t cached_pc;
194     #endif
195     int low_pc, n_instrs;
196    
197     #ifdef DYNTRANS_DUALMODE_32
198     if (cpu->is_32bit)
199     DYNTRANS_PC_TO_POINTERS32(cpu);
200     else
201     #endif
202     DYNTRANS_PC_TO_POINTERS(cpu);
203    
204     /*
205     * Interrupt assertion? (This is _below_ the initial PC to pointer
206     * conversion; if the conversion caused an exception of some kind
207     * then interrupts are probably disabled, and the exception will get
208     * priority over device interrupts.)
209 dpavlin 24 *
210     * TODO: Turn this into a family-specific function somewhere...
211 dpavlin 14 */
212     #ifdef DYNTRANS_ARM
213     if (cpu->cd.arm.irq_asserted && !(cpu->cd.arm.cpsr & ARM_FLAG_I))
214     arm_exception(cpu, ARM_EXCEPTION_IRQ);
215     #endif
216 dpavlin 24 #ifdef DYNTRANS_MIPS
217     {
218     int enabled, mask;
219     int status = cpu->cd.mips.coproc[0]->reg[COP0_STATUS];
220     if (cpu->cd.mips.cpu_type.exc_model == EXC3K) {
221     /* R3000: */
222     enabled = status & MIPS_SR_INT_IE;
223     } else {
224     /* R4000 and others: */
225     enabled = (status & STATUS_IE)
226     && !(status & STATUS_EXL) && !(status & STATUS_ERL);
227     /* Special case for R5900/C790/TX79: */
228     if (cpu->cd.mips.cpu_type.rev == MIPS_R5900 &&
229     !(status & R5900_STATUS_EIE))
230     enabled = 0;
231     }
232     mask = status & cpu->cd.mips.coproc[0]->reg[COP0_CAUSE]
233     & STATUS_IM_MASK;
234    
235     if (enabled && mask)
236     mips_cpu_exception(cpu, EXCEPTION_INT, 0, 0, 0, 0, 0,0);
237     }
238     #endif
239 dpavlin 20 #ifdef DYNTRANS_PPC
240     if (cpu->cd.ppc.dec_intr_pending && cpu->cd.ppc.msr & PPC_MSR_EE) {
241     ppc_exception(cpu, PPC_EXCEPTION_DEC);
242     cpu->cd.ppc.dec_intr_pending = 0;
243     }
244     if (cpu->cd.ppc.irq_asserted && cpu->cd.ppc.msr & PPC_MSR_EE)
245     ppc_exception(cpu, PPC_EXCEPTION_EI);
246     #endif
247 dpavlin 14
248     cached_pc = cpu->pc;
249    
250     cpu->n_translated_instrs = 0;
251     cpu->running_translated = 1;
252    
253 dpavlin 18 cpu->cd.DYNTRANS_ARCH.cur_physpage = (void *)
254     cpu->cd.DYNTRANS_ARCH.cur_ic_page;
255    
256 dpavlin 24 if (single_step || cpu->machine->instruction_trace
257     || cpu->machine->register_dump) {
258 dpavlin 14 /*
259     * Single-step:
260     */
261 dpavlin 24 struct DYNTRANS_IC *ic = cpu->cd.DYNTRANS_ARCH.next_ic;
262     if (cpu->machine->register_dump) {
263     debug("\n");
264     cpu_register_dump(cpu->machine, cpu, 1, 0x1);
265     }
266 dpavlin 14 if (cpu->machine->instruction_trace) {
267     #ifdef DYNTRANS_X86
268     unsigned char instr[17];
269     cpu->cd.x86.cursegment = X86_S_CS;
270     cpu->cd.x86.seg_override = 0;
271     #else
272     #ifdef DYNTRANS_M68K
273     unsigned char instr[16]; /* TODO: 16? */
274     #else
275     unsigned char instr[4]; /* General case... */
276     #endif
277     #endif
278 dpavlin 24
279 dpavlin 14 if (!cpu->memory_rw(cpu, cpu->mem, cached_pc, &instr[0],
280     sizeof(instr), MEM_READ, CACHE_INSTRUCTION)) {
281     fatal("XXX_cpu_run_instr(): could not read "
282     "the instruction\n");
283 dpavlin 22 } else {
284 dpavlin 14 cpu_disassemble_instr(cpu->machine, cpu,
285 dpavlin 24 instr, 1, 0);
286     #ifdef DYNTRANS_DELAYSLOT
287 dpavlin 22 /* Show the instruction in the delay slot,
288     if any: */
289 dpavlin 24 if (cpu->instruction_has_delayslot == NULL)
290     fatal("WARNING: ihd func not yet"
291     " implemented?\n");
292     else if (cpu->instruction_has_delayslot(cpu,
293     instr)) {
294     int saved_delayslot = cpu->delay_slot;
295     cpu->memory_rw(cpu, cpu->mem, cached_pc
296     + sizeof(instr), &instr[0],
297     sizeof(instr), MEM_READ,
298     CACHE_INSTRUCTION);
299     cpu->delay_slot = DELAYED;
300     cpu->pc += sizeof(instr);
301     cpu_disassemble_instr(cpu->machine,
302     cpu, instr, 1, 0);
303     cpu->delay_slot = saved_delayslot;
304     cpu->pc -= sizeof(instr);
305     }
306 dpavlin 22 #endif
307     }
308 dpavlin 14 }
309    
310     /* When single-stepping, multiple instruction calls cannot
311     be combined into one. This clears all translations: */
312     if (cpu->cd.DYNTRANS_ARCH.cur_physpage->flags & COMBINATIONS) {
313     int i;
314 dpavlin 24 for (i=0; i<DYNTRANS_IC_ENTRIES_PER_PAGE; i++) {
315 dpavlin 14 cpu->cd.DYNTRANS_ARCH.cur_physpage->ics[i].f =
316     #ifdef DYNTRANS_DUALMODE_32
317     cpu->is_32bit?
318     instr32(to_be_translated) :
319     #endif
320     instr(to_be_translated);
321 dpavlin 24 #ifdef DYNTRANS_VARIABLE_INSTRUCTION_LENGTH
322     cpu->cd.DYNTRANS_ARCH.cur_physpage->ics[i].
323     arg[0] = 0;
324     #endif
325     }
326     fatal("[ Note: The translation of physical page 0x%"
327     PRIx64" contained combinations of instructions; "
328     "these are now flushed because we are single-"
329     "stepping. ]\n", (long long)cpu->cd.DYNTRANS_ARCH.
330 dpavlin 14 cur_physpage->physaddr);
331     cpu->cd.DYNTRANS_ARCH.cur_physpage->flags &=
332     ~(COMBINATIONS | TRANSLATIONS);
333     }
334    
335 dpavlin 18 if (show_opcode_statistics)
336     S;
337    
338 dpavlin 14 /* Execute just one instruction: */
339 dpavlin 24 I;
340    
341 dpavlin 14 n_instrs = 1;
342 dpavlin 24 } else if (cpu->machine->cycle_accurate) {
343     /* Executing multiple instructions, and call devices'
344     tick functions: */
345     n_instrs = 0;
346     for (;;) {
347     struct DYNTRANS_IC *ic;
348     /* TODO: continue here */
349     int64_t cycles = cpu->cd.avr.extra_cycles;
350     I;
351     n_instrs += 1;
352     cycles = cpu->cd.avr.extra_cycles - cycles + 1;
353     /* The instruction took 'cycles' cycles. */
354     /* printf("A\n"); */
355     while (cycles-- > 0)
356     cpu->machine->tick_func[1](cpu, cpu->machine->tick_extra[1]);
357     /* printf("B\n"); */
358    
359     if (!cpu->running_translated ||
360     n_instrs + cpu->n_translated_instrs >=
361     N_SAFE_DYNTRANS_LIMIT / 2)
362     break;
363     }
364 dpavlin 18 } else if (show_opcode_statistics) {
365     /* Gather statistics while executing multiple instructions: */
366     n_instrs = 0;
367     for (;;) {
368     struct DYNTRANS_IC *ic;
369    
370     S; I; S; I; S; I; S; I; S; I; S; I;
371     S; I; S; I; S; I; S; I; S; I; S; I;
372     S; I; S; I; S; I; S; I; S; I; S; I;
373     S; I; S; I; S; I; S; I; S; I; S; I;
374    
375     n_instrs += 24;
376    
377     if (!cpu->running_translated ||
378 dpavlin 24 n_instrs + cpu->n_translated_instrs >=
379     N_SAFE_DYNTRANS_LIMIT / 2)
380 dpavlin 18 break;
381     }
382 dpavlin 14 } else {
383     /* Execute multiple instructions: */
384     n_instrs = 0;
385     for (;;) {
386     struct DYNTRANS_IC *ic;
387    
388     I; I; I; I; I; I; I; I; I; I;
389     I; I; I; I; I; I; I; I; I; I;
390     I; I; I; I; I; I; I; I; I; I;
391     I; I; I; I; I; I; I; I; I; I;
392     I; I; I; I; I; I; I; I; I; I;
393    
394     I; I; I; I; I; I; I; I; I; I;
395    
396 dpavlin 18 n_instrs += 60;
397 dpavlin 14
398     if (!cpu->running_translated ||
399 dpavlin 24 n_instrs + cpu->n_translated_instrs >=
400     N_SAFE_DYNTRANS_LIMIT / 2)
401 dpavlin 14 break;
402     }
403     }
404    
405 dpavlin 20 n_instrs += cpu->n_translated_instrs;
406 dpavlin 14
407 dpavlin 20 /* Synchronize the program counter: */
408 dpavlin 14 low_pc = ((size_t)cpu->cd.DYNTRANS_ARCH.next_ic - (size_t)
409     cpu->cd.DYNTRANS_ARCH.cur_ic_page) / sizeof(struct DYNTRANS_IC);
410     if (low_pc >= 0 && low_pc < DYNTRANS_IC_ENTRIES_PER_PAGE) {
411     cpu->pc &= ~((DYNTRANS_IC_ENTRIES_PER_PAGE-1) <<
412     DYNTRANS_INSTR_ALIGNMENT_SHIFT);
413     cpu->pc += (low_pc << DYNTRANS_INSTR_ALIGNMENT_SHIFT);
414     } else if (low_pc == DYNTRANS_IC_ENTRIES_PER_PAGE) {
415     /* Switch to next page: */
416     cpu->pc &= ~((DYNTRANS_IC_ENTRIES_PER_PAGE-1) <<
417     DYNTRANS_INSTR_ALIGNMENT_SHIFT);
418     cpu->pc += (DYNTRANS_IC_ENTRIES_PER_PAGE <<
419     DYNTRANS_INSTR_ALIGNMENT_SHIFT);
420 dpavlin 22 } else if (low_pc == DYNTRANS_IC_ENTRIES_PER_PAGE + 1) {
421     /* Switch to next page and skip an instruction which was
422     already executed (in a delay slot): */
423     cpu->pc &= ~((DYNTRANS_IC_ENTRIES_PER_PAGE-1) <<
424     DYNTRANS_INSTR_ALIGNMENT_SHIFT);
425     cpu->pc += ((DYNTRANS_IC_ENTRIES_PER_PAGE + 1) <<
426     DYNTRANS_INSTR_ALIGNMENT_SHIFT);
427 dpavlin 14 }
428    
429 dpavlin 24 #ifdef DYNTRANS_MIPS
430     /* Update the count register (on everything except EXC3K): */
431     if (cpu->cd.mips.cpu_type.exc_model != EXC3K) {
432     uint32_t old = cpu->cd.mips.coproc[0]->reg[COP0_COUNT];
433     int32_t diff1 = cpu->cd.mips.coproc[0]->reg[COP0_COMPARE] - old;
434     int32_t diff2;
435     cpu->cd.mips.coproc[0]->reg[COP0_COUNT] =
436     (int32_t) (old + n_instrs);
437     diff2 = cpu->cd.mips.coproc[0]->reg[COP0_COMPARE] -
438     cpu->cd.mips.coproc[0]->reg[COP0_COUNT];
439     if (cpu->cd.mips.compare_register_set && diff1>0 && diff2<=0)
440     cpu_interrupt(cpu, 7);
441     }
442     #endif
443 dpavlin 20 #ifdef DYNTRANS_PPC
444     /* Update the Decrementer and Time base registers: */
445     {
446     uint32_t old = cpu->cd.ppc.spr[SPR_DEC];
447     cpu->cd.ppc.spr[SPR_DEC] = (uint32_t) (old - n_instrs);
448 dpavlin 22 if ((old >> 31) == 0 && (cpu->cd.ppc.spr[SPR_DEC] >> 31) == 1
449     && !(cpu->cd.ppc.cpu_type.flags & PPC_NO_DEC))
450 dpavlin 20 cpu->cd.ppc.dec_intr_pending = 1;
451     old = cpu->cd.ppc.spr[SPR_TBL];
452     cpu->cd.ppc.spr[SPR_TBL] += n_instrs;
453     if ((old >> 31) == 1 && (cpu->cd.ppc.spr[SPR_TBL] >> 31) == 0)
454     cpu->cd.ppc.spr[SPR_TBU] ++;
455     }
456     #endif
457    
458     /* Return the nr of instructions executed: */
459     return n_instrs;
460 dpavlin 14 }
461     #endif /* DYNTRANS_CPU_RUN_INSTR */
462    
463    
464    
465     #ifdef DYNTRANS_FUNCTION_TRACE
466     /*
467     * XXX_cpu_functioncall_trace():
468     *
469     * Without this function, the main trace tree function prints something
470     * like <f()> or <0x1234()> on a function call. It is up to this
471     * function to print the arguments passed.
472     */
473     void DYNTRANS_FUNCTION_TRACE(struct cpu *cpu, uint64_t f, int n_args)
474     {
475     char strbuf[50];
476     char *symbol;
477     uint64_t ot;
478     int x, print_dots = 1, n_args_to_print =
479 dpavlin 24 #if defined(DYNTRANS_ALPHA) || defined(DYNTRANS_SPARC)
480 dpavlin 14 6
481     #else
482     #ifdef DYNTRANS_SH
483     8
484     #else
485     4 /* Default value for most archs */
486     #endif
487     #endif
488     ;
489    
490     if (n_args >= 0 && n_args <= n_args_to_print) {
491     print_dots = 0;
492     n_args_to_print = n_args;
493     }
494    
495     /*
496     * TODO: The type of each argument should be taken from the symbol
497     * table, in some way.
498     *
499     * The code here does a kind of "heuristic guess" regarding what the
500     * argument values might mean. Sometimes the output looks weird, but
501     * usually it looks good enough.
502     *
503     * Print ".." afterwards to show that there might be more arguments
504     * than were passed in register.
505     */
506     for (x=0; x<n_args_to_print; x++) {
507     int64_t d;
508     #ifdef DYNTRANS_X86
509     d = 0; /* TODO */
510     #else
511     /* Args in registers: */
512     d = cpu->cd.DYNTRANS_ARCH.
513     #ifdef DYNTRANS_ALPHA
514     r[ALPHA_A0
515     #endif
516     #ifdef DYNTRANS_ARM
517     r[0
518     #endif
519     #ifdef DYNTRANS_AVR
520     /* TODO: 24,25 = first register, but then
521     they go downwards, ie. 22,23 and so on */
522     r[24
523     #endif
524     #ifdef DYNTRANS_HPPA
525     r[0 /* TODO */
526     #endif
527     #ifdef DYNTRANS_I960
528     r[0 /* TODO */
529     #endif
530     #ifdef DYNTRANS_IA64
531     r[0 /* TODO */
532     #endif
533     #ifdef DYNTRANS_M68K
534     d[0 /* TODO */
535     #endif
536     #ifdef DYNTRANS_MIPS
537     gpr[MIPS_GPR_A0
538     #endif
539     #ifdef DYNTRANS_PPC
540     gpr[3
541     #endif
542     #ifdef DYNTRANS_SH
543     r[2
544     #endif
545     #ifdef DYNTRANS_SPARC
546 dpavlin 22 r[24
547 dpavlin 14 #endif
548     + x];
549     #endif
550     symbol = get_symbol_name(&cpu->machine->symbol_context, d, &ot);
551    
552     if (d > -256 && d < 256)
553     fatal("%i", (int)d);
554     else if (memory_points_to_string(cpu, cpu->mem, d, 1))
555     fatal("\"%s\"", memory_conv_to_string(cpu,
556     cpu->mem, d, strbuf, sizeof(strbuf)));
557     else if (symbol != NULL && ot == 0)
558     fatal("&%s", symbol);
559     else {
560     if (cpu->is_32bit)
561 dpavlin 24 fatal("0x%"PRIx32, (uint32_t)d);
562 dpavlin 14 else
563 dpavlin 24 fatal("0x%"PRIx64, (uint64_t)d);
564 dpavlin 14 }
565    
566     if (x < n_args_to_print - 1)
567     fatal(",");
568     }
569    
570     if (print_dots)
571     fatal(",..");
572     }
573     #endif
574    
575    
576    
577     #ifdef DYNTRANS_TC_ALLOCATE_DEFAULT_PAGE
578 dpavlin 22
579 dpavlin 14 /* forward declaration of to_be_translated and end_of_page: */
580     static void instr(to_be_translated)(struct cpu *, struct DYNTRANS_IC *);
581     static void instr(end_of_page)(struct cpu *,struct DYNTRANS_IC *);
582     #ifdef DYNTRANS_DUALMODE_32
583     static void instr32(to_be_translated)(struct cpu *, struct DYNTRANS_IC *);
584     static void instr32(end_of_page)(struct cpu *,struct DYNTRANS_IC *);
585     #endif
586 dpavlin 22
587     #ifdef DYNTRANS_DELAYSLOT
588     static void instr(end_of_page2)(struct cpu *,struct DYNTRANS_IC *);
589     #ifdef DYNTRANS_DUALMODE_32
590     static void instr32(end_of_page2)(struct cpu *,struct DYNTRANS_IC *);
591     #endif
592     #endif
593    
594 dpavlin 14 /*
595     * XXX_tc_allocate_default_page():
596     *
597     * Create a default page (with just pointers to instr(to_be_translated)
598     * at cpu->translation_cache_cur_ofs.
599     */
600     static void DYNTRANS_TC_ALLOCATE_DEFAULT_PAGE(struct cpu *cpu,
601     uint64_t physaddr)
602     {
603     struct DYNTRANS_TC_PHYSPAGE *ppp;
604     int i;
605    
606     /* Create the physpage header: */
607     ppp = (struct DYNTRANS_TC_PHYSPAGE *)(cpu->translation_cache
608     + cpu->translation_cache_cur_ofs);
609     ppp->next_ofs = 0;
610     ppp->physaddr = physaddr;
611    
612     /* TODO: Is this faster than copying an entire template page? */
613 dpavlin 24 for (i=0; i<DYNTRANS_IC_ENTRIES_PER_PAGE; i++) {
614 dpavlin 14 ppp->ics[i].f =
615     #ifdef DYNTRANS_DUALMODE_32
616     cpu->is_32bit? instr32(to_be_translated) :
617     #endif
618     instr(to_be_translated);
619 dpavlin 24 #ifdef DYNTRANS_VARIABLE_INSTRUCTION_LENGTH
620     ppp->ics[i].arg[0] = 0;
621     #endif
622     }
623 dpavlin 14
624 dpavlin 24 /* End-of-page: */
625 dpavlin 22 ppp->ics[DYNTRANS_IC_ENTRIES_PER_PAGE + 0].f =
626 dpavlin 14 #ifdef DYNTRANS_DUALMODE_32
627     cpu->is_32bit? instr32(end_of_page) :
628     #endif
629     instr(end_of_page);
630    
631 dpavlin 24 #ifdef DYNTRANS_VARIABLE_INSTRUCTION_LENGTH
632     ppp->ics[DYNTRANS_IC_ENTRIES_PER_PAGE + 0].arg[0] = 0;
633     #endif
634    
635     /* End-of-page-2, for delay-slot architectures: */
636 dpavlin 22 #ifdef DYNTRANS_DELAYSLOT
637     ppp->ics[DYNTRANS_IC_ENTRIES_PER_PAGE + 1].f =
638     #ifdef DYNTRANS_DUALMODE_32
639     cpu->is_32bit? instr32(end_of_page2) :
640     #endif
641     instr(end_of_page2);
642     #endif
643    
644 dpavlin 14 cpu->translation_cache_cur_ofs += sizeof(struct DYNTRANS_TC_PHYSPAGE);
645 dpavlin 18
646     cpu->translation_cache_cur_ofs --;
647     cpu->translation_cache_cur_ofs |= 63;
648     cpu->translation_cache_cur_ofs ++;
649 dpavlin 14 }
650     #endif /* DYNTRANS_TC_ALLOCATE_DEFAULT_PAGE */
651    
652    
653    
654     #ifdef DYNTRANS_PC_TO_POINTERS_FUNC
655     /*
656     * XXX_pc_to_pointers_generic():
657     *
658     * Generic case. See DYNTRANS_PC_TO_POINTERS_FUNC below.
659     */
660     void DYNTRANS_PC_TO_POINTERS_GENERIC(struct cpu *cpu)
661     {
662     #ifdef MODE32
663     uint32_t
664     #else
665     uint64_t
666     #endif
667 dpavlin 24 cached_pc = cpu->pc, physaddr = 0;
668 dpavlin 14 uint32_t physpage_ofs;
669     int ok, pagenr, table_index;
670     uint32_t *physpage_entryp;
671     struct DYNTRANS_TC_PHYSPAGE *ppp;
672    
673     #ifdef MODE32
674 dpavlin 24 int index = DYNTRANS_ADDR_TO_PAGENR(cached_pc);
675 dpavlin 14 #else
676 dpavlin 24 const uint32_t mask1 = (1 << DYNTRANS_L1N) - 1;
677     const uint32_t mask2 = (1 << DYNTRANS_L2N) - 1;
678     const uint32_t mask3 = (1 << DYNTRANS_L3N) - 1;
679     uint32_t x1, x2, x3;
680     struct DYNTRANS_L2_64_TABLE *l2;
681     struct DYNTRANS_L3_64_TABLE *l3;
682    
683     x1 = (cached_pc >> (64-DYNTRANS_L1N)) & mask1;
684     x2 = (cached_pc >> (64-DYNTRANS_L1N-DYNTRANS_L2N)) & mask2;
685     x3 = (cached_pc >> (64-DYNTRANS_L1N-DYNTRANS_L2N-DYNTRANS_L3N)) & mask3;
686     /* fatal("X3: cached_pc=%016"PRIx64" x1=%x x2=%x x3=%x\n",
687     (uint64_t)cached_pc, (int)x1, (int)x2, (int)x3); */
688     l2 = cpu->cd.DYNTRANS_ARCH.l1_64[x1];
689     /* fatal(" l2 = %p\n", l2); */
690     l3 = l2->l3[x2];
691     /* fatal(" l3 = %p\n", l3); */
692 dpavlin 14 #endif
693    
694     /* Virtual to physical address translation: */
695     ok = 0;
696     #ifdef MODE32
697     if (cpu->cd.DYNTRANS_ARCH.host_load[index] != NULL) {
698     physaddr = cpu->cd.DYNTRANS_ARCH.phys_addr[index];
699     ok = 1;
700     }
701     #else
702 dpavlin 24 if (l3->host_load[x3] != NULL) {
703     physaddr = l3->phys_addr[x3];
704 dpavlin 14 ok = 1;
705     }
706     #endif
707    
708     if (!ok) {
709     uint64_t paddr;
710     if (cpu->translate_address != NULL)
711     ok = cpu->translate_address(cpu, cached_pc,
712     &paddr, FLAG_INSTR);
713     else {
714     paddr = cached_pc;
715     ok = 1;
716     }
717     if (!ok) {
718 dpavlin 24 /* fatal("TODO: instruction vaddr=>paddr translation "
719     "failed. vaddr=0x%"PRIx64"\n", (uint64_t)cached_pc);
720     fatal("!! cpu->pc=0x%"PRIx64"\n", (uint64_t)cpu->pc); */
721 dpavlin 20
722 dpavlin 14 ok = cpu->translate_address(cpu, cpu->pc, &paddr,
723     FLAG_INSTR);
724 dpavlin 20
725     /* printf("EXCEPTION HANDLER: vaddr = 0x%x ==> "
726     "paddr = 0x%x\n", (int)cpu->pc, (int)paddr);
727 dpavlin 24 fatal("!? cpu->pc=0x%"PRIx64"\n", (uint64_t)cpu->pc); */
728 dpavlin 20
729 dpavlin 14 if (!ok) {
730     fatal("FATAL: could not find physical"
731     " address of the exception handler?");
732     exit(1);
733     }
734     }
735 dpavlin 24
736     /* If there was an exception, the PC can have changed.
737     Update cached_pc: */
738 dpavlin 14 cached_pc = cpu->pc;
739 dpavlin 24
740 dpavlin 18 #ifdef MODE32
741     index = DYNTRANS_ADDR_TO_PAGENR(cached_pc);
742 dpavlin 24 #else
743     x1 = (cached_pc >> (64-DYNTRANS_L1N)) & mask1;
744     x2 = (cached_pc >> (64-DYNTRANS_L1N-DYNTRANS_L2N)) & mask2;
745     x3 = (cached_pc >> (64-DYNTRANS_L1N-DYNTRANS_L2N-DYNTRANS_L3N))
746     & mask3;
747 dpavlin 18 #endif
748 dpavlin 24
749 dpavlin 14 physaddr = paddr;
750     }
751    
752 dpavlin 18 #ifdef MODE32
753     if (cpu->cd.DYNTRANS_ARCH.host_load[index] == NULL) {
754 dpavlin 24 #else
755     if (l3->host_load[x3] == NULL) {
756     #endif
757 dpavlin 18 unsigned char *host_page = memory_paddr_to_hostaddr(cpu->mem,
758     physaddr, MEM_READ);
759     if (host_page != NULL) {
760     int q = DYNTRANS_PAGESIZE - 1;
761     host_page += (physaddr &
762     ((1 << BITS_PER_MEMBLOCK) - 1) & ~q);
763     cpu->update_translation_table(cpu, cached_pc & ~q,
764     host_page, TLB_CODE, physaddr & ~q);
765 dpavlin 24 #ifndef MODE32
766     /* Recalculate l2 and l3, since they might have
767     changed now: */
768     l2 = cpu->cd.DYNTRANS_ARCH.l1_64[x1];
769     l3 = l2->l3[x2];
770     #endif
771 dpavlin 18 }
772     }
773    
774     if (cpu->translation_cache_cur_ofs >= DYNTRANS_CACHE_SIZE) {
775 dpavlin 20 debug("[ dyntrans: resetting the translation cache ]\n");
776 dpavlin 14 cpu_create_or_reset_tc(cpu);
777 dpavlin 18 }
778 dpavlin 14
779     pagenr = DYNTRANS_ADDR_TO_PAGENR(physaddr);
780     table_index = PAGENR_TO_TABLE_INDEX(pagenr);
781    
782     physpage_entryp = &(((uint32_t *)cpu->translation_cache)[table_index]);
783     physpage_ofs = *physpage_entryp;
784     ppp = NULL;
785    
786     /* Traverse the physical page chain: */
787     while (physpage_ofs != 0) {
788     ppp = (struct DYNTRANS_TC_PHYSPAGE *)(cpu->translation_cache
789     + physpage_ofs);
790     /* If we found the page in the cache, then we're done: */
791 dpavlin 24 if (DYNTRANS_ADDR_TO_PAGENR(ppp->physaddr) == pagenr)
792 dpavlin 14 break;
793     /* Try the next page in the chain: */
794     physpage_ofs = ppp->next_ofs;
795     }
796    
797     /* If the offset is 0 (or ppp is NULL), then we need to create a
798     new "default" empty translation page. */
799    
800     if (ppp == NULL) {
801 dpavlin 24 /* fatal("CREATING page %lli (physaddr 0x%"PRIx64"), table "
802     "index %i\n", (long long)pagenr, (uint64_t)physaddr,
803 dpavlin 14 (int)table_index); */
804     *physpage_entryp = physpage_ofs =
805     cpu->translation_cache_cur_ofs;
806    
807     /* Allocate a default page, with to_be_translated entries: */
808     DYNTRANS_TC_ALLOCATE(cpu, physaddr);
809    
810     ppp = (struct DYNTRANS_TC_PHYSPAGE *)(cpu->translation_cache
811     + physpage_ofs);
812     }
813    
814     #ifdef MODE32
815     if (cpu->cd.DYNTRANS_ARCH.host_load[index] != NULL)
816     cpu->cd.DYNTRANS_ARCH.phys_page[index] = ppp;
817 dpavlin 24 #else
818     if (l3->host_load[x3] != NULL)
819     l3->phys_page[x3] = ppp;
820 dpavlin 14 #endif
821    
822 dpavlin 20 #ifdef MODE32
823     /* Small optimization: only mark the physical page as non-writable
824     if it did not contain translations. (Because if it does contain
825     translations, it is already non-writable.) */
826     if (!cpu->cd.DYNTRANS_ARCH.phystranslation[pagenr >> 5] &
827     (1 << (pagenr & 31)))
828     #endif
829 dpavlin 18 cpu->invalidate_translation_caches(cpu, physaddr,
830     JUST_MARK_AS_NON_WRITABLE | INVALIDATE_PADDR);
831 dpavlin 14
832     cpu->cd.DYNTRANS_ARCH.cur_ic_page = &ppp->ics[0];
833 dpavlin 18
834 dpavlin 14 cpu->cd.DYNTRANS_ARCH.next_ic = cpu->cd.DYNTRANS_ARCH.cur_ic_page +
835     DYNTRANS_PC_TO_IC_ENTRY(cached_pc);
836    
837 dpavlin 24 /* printf("cached_pc=0x%016"PRIx64" pagenr=%lli table_index=%lli, "
838     "physpage_ofs=0x%016"PRIx64"\n", (uint64_t)cached_pc, (long long)
839     pagenr, (long long)table_index, (uint64_t)physpage_ofs); */
840 dpavlin 14 }
841    
842    
843     /*
844     * XXX_pc_to_pointers():
845     *
846     * This function uses the current program counter (a virtual address) to
847     * find out which physical translation page to use, and then sets the current
848     * translation page pointers to that page.
849     *
850     * If there was no translation page for that physical page, then an empty
851     * one is created.
852     *
853     * NOTE: This is the quick lookup version. See
854     * DYNTRANS_PC_TO_POINTERS_GENERIC above for the generic case.
855     */
856     void DYNTRANS_PC_TO_POINTERS_FUNC(struct cpu *cpu)
857     {
858     #ifdef MODE32
859     uint32_t
860     #else
861     uint64_t
862     #endif
863 dpavlin 22 cached_pc = cpu->pc;
864 dpavlin 14 struct DYNTRANS_TC_PHYSPAGE *ppp;
865    
866     #ifdef MODE32
867     int index;
868 dpavlin 18 index = DYNTRANS_ADDR_TO_PAGENR(cached_pc);
869 dpavlin 14 ppp = cpu->cd.DYNTRANS_ARCH.phys_page[index];
870     if (ppp != NULL)
871     goto have_it;
872     #else
873 dpavlin 24 const uint32_t mask1 = (1 << DYNTRANS_L1N) - 1;
874     const uint32_t mask2 = (1 << DYNTRANS_L2N) - 1;
875     const uint32_t mask3 = (1 << DYNTRANS_L3N) - 1;
876     uint32_t x1, x2, x3;
877     struct DYNTRANS_L2_64_TABLE *l2;
878     struct DYNTRANS_L3_64_TABLE *l3;
879    
880     x1 = (cached_pc >> (64-DYNTRANS_L1N)) & mask1;
881     x2 = (cached_pc >> (64-DYNTRANS_L1N-DYNTRANS_L2N)) & mask2;
882     x3 = (cached_pc >> (64-DYNTRANS_L1N-DYNTRANS_L2N-DYNTRANS_L3N)) & mask3;
883     l2 = cpu->cd.DYNTRANS_ARCH.l1_64[x1];
884     l3 = l2->l3[x2];
885     ppp = l3->phys_page[x3];
886     if (ppp != NULL)
887     goto have_it;
888 dpavlin 14 #endif
889    
890     DYNTRANS_PC_TO_POINTERS_GENERIC(cpu);
891     return;
892    
893     /* Quick return path: */
894     have_it:
895     cpu->cd.DYNTRANS_ARCH.cur_ic_page = &ppp->ics[0];
896     cpu->cd.DYNTRANS_ARCH.next_ic = cpu->cd.DYNTRANS_ARCH.cur_ic_page +
897     DYNTRANS_PC_TO_IC_ENTRY(cached_pc);
898    
899 dpavlin 24 /* printf("cached_pc=0x%016"PRIx64" pagenr=%lli table_index=%lli, "
900     "physpage_ofs=0x%016"PRIx64"\n", (uint64_t)cached_pc, (long long)
901     pagenr, (long long)table_index, (uint64_t)physpage_ofs); */
902 dpavlin 14 }
903     #endif /* DYNTRANS_PC_TO_POINTERS_FUNC */
904    
905    
906    
907 dpavlin 24 #ifdef DYNTRANS_INIT_64BIT_DUMMY_TABLES
908     /*
909     * XXX_init_64bit_dummy_tables():
910     *
911     * Initializes 64-bit dummy tables and pointers.
912     */
913     void DYNTRANS_INIT_64BIT_DUMMY_TABLES(struct cpu *cpu)
914     {
915     struct DYNTRANS_L2_64_TABLE *dummy_l2;
916     struct DYNTRANS_L3_64_TABLE *dummy_l3;
917     int x1, x2;
918    
919     if (cpu->is_32bit)
920     return;
921    
922     dummy_l2 = zeroed_alloc(sizeof(struct DYNTRANS_L2_64_TABLE));
923     dummy_l3 = zeroed_alloc(sizeof(struct DYNTRANS_L3_64_TABLE));
924    
925     cpu->cd.DYNTRANS_ARCH.l2_64_dummy = dummy_l2;
926     cpu->cd.DYNTRANS_ARCH.l3_64_dummy = dummy_l3;
927    
928     for (x1 = 0; x1 < (1 << DYNTRANS_L1N); x1 ++)
929     cpu->cd.DYNTRANS_ARCH.l1_64[x1] = dummy_l2;
930    
931     for (x2 = 0; x2 < (1 << DYNTRANS_L2N); x2 ++)
932     dummy_l2->l3[x2] = dummy_l3;
933     }
934     #endif /* DYNTRANS_INIT_64BIT_DUMMY_TABLES */
935    
936    
937    
938 dpavlin 14 #ifdef DYNTRANS_INVAL_ENTRY
939     /*
940     * XXX_invalidate_tlb_entry():
941     *
942     * Invalidate one translation entry (based on virtual address).
943     *
944     * If the JUST_MARK_AS_NON_WRITABLE flag is set, then the translation entry
945     * is just downgraded to non-writable (ie the host store page is set to
946     * NULL). Otherwise, the entire translation is removed.
947     */
948 dpavlin 18 static void DYNTRANS_INVALIDATE_TLB_ENTRY(struct cpu *cpu,
949 dpavlin 14 #ifdef MODE32
950     uint32_t
951     #else
952     uint64_t
953     #endif
954     vaddr_page, int flags)
955     {
956     #ifdef MODE32
957 dpavlin 18 uint32_t index = DYNTRANS_ADDR_TO_PAGENR(vaddr_page);
958 dpavlin 14
959 dpavlin 18 #ifdef DYNTRANS_ARM
960 dpavlin 20 cpu->cd.DYNTRANS_ARCH.is_userpage[index >> 5] &= ~(1 << (index & 31));
961 dpavlin 18 #endif
962    
963 dpavlin 14 if (flags & JUST_MARK_AS_NON_WRITABLE) {
964     /* printf("JUST MARKING NON-W: vaddr 0x%08x\n",
965     (int)vaddr_page); */
966     cpu->cd.DYNTRANS_ARCH.host_store[index] = NULL;
967     } else {
968 dpavlin 24 int tlbi = cpu->cd.DYNTRANS_ARCH.vaddr_to_tlbindex[index];
969 dpavlin 14 cpu->cd.DYNTRANS_ARCH.host_load[index] = NULL;
970     cpu->cd.DYNTRANS_ARCH.host_store[index] = NULL;
971     cpu->cd.DYNTRANS_ARCH.phys_addr[index] = 0;
972     cpu->cd.DYNTRANS_ARCH.phys_page[index] = NULL;
973 dpavlin 24 if (tlbi > 0)
974     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[tlbi-1].valid = 0;
975 dpavlin 18 cpu->cd.DYNTRANS_ARCH.vaddr_to_tlbindex[index] = 0;
976 dpavlin 14 }
977     #else
978 dpavlin 24 const uint32_t mask1 = (1 << DYNTRANS_L1N) - 1;
979     const uint32_t mask2 = (1 << DYNTRANS_L2N) - 1;
980     const uint32_t mask3 = (1 << DYNTRANS_L3N) - 1;
981     uint32_t x1, x2, x3;
982     struct DYNTRANS_L2_64_TABLE *l2;
983     struct DYNTRANS_L3_64_TABLE *l3;
984 dpavlin 14
985 dpavlin 24 x1 = (vaddr_page >> (64-DYNTRANS_L1N)) & mask1;
986     x2 = (vaddr_page >> (64-DYNTRANS_L1N-DYNTRANS_L2N)) & mask2;
987     x3 = (vaddr_page >> (64-DYNTRANS_L1N-DYNTRANS_L2N-DYNTRANS_L3N))& mask3;
988 dpavlin 14
989 dpavlin 24 l2 = cpu->cd.DYNTRANS_ARCH.l1_64[x1];
990     if (l2 == cpu->cd.DYNTRANS_ARCH.l2_64_dummy)
991     return;
992 dpavlin 14
993 dpavlin 24 l3 = l2->l3[x2];
994     if (l3 == cpu->cd.DYNTRANS_ARCH.l3_64_dummy)
995     return;
996    
997 dpavlin 14 if (flags & JUST_MARK_AS_NON_WRITABLE) {
998 dpavlin 24 l3->host_store[x3] = NULL;
999 dpavlin 14 return;
1000     }
1001 dpavlin 24 l3->host_load[x3] = NULL;
1002     l3->host_store[x3] = NULL;
1003     l3->phys_addr[x3] = 0;
1004     l3->phys_page[x3] = NULL;
1005     l3->refcount --;
1006     if (l3->refcount < 0) {
1007     fatal("xxx_invalidate_tlb_entry(): huh? Refcount bug.\n");
1008 dpavlin 14 exit(1);
1009     }
1010 dpavlin 24 if (l3->refcount == 0) {
1011     l3->next = cpu->cd.DYNTRANS_ARCH.next_free_l3;
1012     cpu->cd.DYNTRANS_ARCH.next_free_l3 = l3;
1013     l2->l3[x2] = cpu->cd.DYNTRANS_ARCH.l3_64_dummy;
1014    
1015     l2->refcount --;
1016     if (l2->refcount < 0) {
1017     fatal("xxx_invalidate_tlb_entry(): Refcount bug L2.\n");
1018     exit(1);
1019     }
1020     if (l2->refcount == 0) {
1021     l2->next = cpu->cd.DYNTRANS_ARCH.next_free_l2;
1022     cpu->cd.DYNTRANS_ARCH.next_free_l2 = l2;
1023     cpu->cd.DYNTRANS_ARCH.l1_64[x1] =
1024     cpu->cd.DYNTRANS_ARCH.l2_64_dummy;
1025     }
1026 dpavlin 14 }
1027     #endif
1028     }
1029     #endif
1030    
1031    
1032 dpavlin 18 #ifdef DYNTRANS_INVALIDATE_TC
1033 dpavlin 14 /*
1034 dpavlin 18 * XXX_invalidate_translation_caches():
1035 dpavlin 14 *
1036     * Invalidate all entries matching a specific physical address, a specific
1037     * virtual address, or ALL entries.
1038     *
1039     * flags should be one of
1040     * INVALIDATE_PADDR INVALIDATE_VADDR or INVALIDATE_ALL
1041     *
1042 dpavlin 22 * In addition, for INVALIDATE_ALL, INVALIDATE_VADDR_UPPER4 may be set and
1043     * bit 31..28 of addr are used to select the virtual addresses to invalidate.
1044     * (This is useful for PowerPC emulation, when segment registers are updated.)
1045     *
1046 dpavlin 14 * In the case when all translations are invalidated, paddr doesn't need
1047     * to be supplied.
1048     *
1049 dpavlin 18 * NOTE/TODO: When invalidating a virtual address, it is only cleared from
1050     * the quick translation array, not from the linear
1051     * vph_tlb_entry[] array. Hopefully this is enough anyway.
1052 dpavlin 14 */
1053 dpavlin 22 void DYNTRANS_INVALIDATE_TC(struct cpu *cpu, uint64_t addr, int flags)
1054 dpavlin 14 {
1055     int r;
1056     #ifdef MODE32
1057     uint32_t
1058     #else
1059     uint64_t
1060     #endif
1061 dpavlin 22 addr_page = addr & ~(DYNTRANS_PAGESIZE - 1);
1062 dpavlin 14
1063 dpavlin 20 /* fatal("invalidate(): "); */
1064    
1065 dpavlin 22 /* Quick case for _one_ virtual addresses: see note above. */
1066 dpavlin 18 if (flags & INVALIDATE_VADDR) {
1067 dpavlin 20 /* fatal("vaddr 0x%08x\n", (int)addr_page); */
1068 dpavlin 18 DYNTRANS_INVALIDATE_TLB_ENTRY(cpu, addr_page, flags);
1069     return;
1070     }
1071    
1072 dpavlin 22 /* Invalidate everything: */
1073     #ifdef DYNTRANS_PPC
1074     if (flags & INVALIDATE_ALL && flags & INVALIDATE_VADDR_UPPER4) {
1075     /* fatal("all, upper4 (PowerPC segment)\n"); */
1076     for (r=0; r<DYNTRANS_MAX_VPH_TLB_ENTRIES; r++) {
1077     if (cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].valid &&
1078     (cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].vaddr_page
1079     & 0xf0000000) == addr_page) {
1080     DYNTRANS_INVALIDATE_TLB_ENTRY(cpu, cpu->cd.
1081     DYNTRANS_ARCH.vph_tlb_entry[r].vaddr_page,
1082     0);
1083     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].valid=0;
1084     }
1085     }
1086     return;
1087     }
1088     #endif
1089 dpavlin 20 if (flags & INVALIDATE_ALL) {
1090     /* fatal("all\n"); */
1091     for (r=0; r<DYNTRANS_MAX_VPH_TLB_ENTRIES; r++) {
1092     if (cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].valid) {
1093     DYNTRANS_INVALIDATE_TLB_ENTRY(cpu, cpu->cd.
1094     DYNTRANS_ARCH.vph_tlb_entry[r].vaddr_page,
1095     0);
1096     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].valid=0;
1097     }
1098     }
1099     return;
1100     }
1101    
1102 dpavlin 22 /* Invalidate a physical page: */
1103 dpavlin 20
1104 dpavlin 22 if (!(flags & INVALIDATE_PADDR))
1105     fatal("HUH? Invalidate: Not vaddr, all, or paddr?\n");
1106    
1107     /* fatal("addr 0x%08x\n", (int)addr_page); */
1108    
1109 dpavlin 14 for (r=0; r<DYNTRANS_MAX_VPH_TLB_ENTRIES; r++) {
1110 dpavlin 22 if (cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].valid && addr_page
1111     == cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].paddr_page) {
1112 dpavlin 14 DYNTRANS_INVALIDATE_TLB_ENTRY(cpu,
1113     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].vaddr_page,
1114     flags);
1115     if (flags & JUST_MARK_AS_NON_WRITABLE)
1116     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r]
1117     .writeflag = 0;
1118     else
1119     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r]
1120     .valid = 0;
1121     }
1122     }
1123     }
1124 dpavlin 18 #endif /* DYNTRANS_INVALIDATE_TC */
1125 dpavlin 14
1126    
1127    
1128     #ifdef DYNTRANS_INVALIDATE_TC_CODE
1129     /*
1130     * XXX_invalidate_code_translation():
1131     *
1132     * Invalidate code translations for a specific physical address, a specific
1133     * virtual address, or for all entries in the cache.
1134     */
1135     void DYNTRANS_INVALIDATE_TC_CODE(struct cpu *cpu, uint64_t addr, int flags)
1136     {
1137     int r;
1138 dpavlin 18 #ifdef MODE32
1139 dpavlin 14 uint32_t
1140     #else
1141     uint64_t
1142     #endif
1143     vaddr_page, paddr_page;
1144    
1145     addr &= ~(DYNTRANS_PAGESIZE-1);
1146    
1147     /* printf("DYNTRANS_INVALIDATE_TC_CODE addr=0x%08x flags=%i\n",
1148     (int)addr, flags); */
1149    
1150     if (flags & INVALIDATE_PADDR) {
1151     int pagenr, table_index;
1152     uint32_t physpage_ofs, *physpage_entryp;
1153 dpavlin 18 struct DYNTRANS_TC_PHYSPAGE *ppp, *prev_ppp;
1154 dpavlin 14
1155     pagenr = DYNTRANS_ADDR_TO_PAGENR(addr);
1156 dpavlin 18
1157     #ifdef MODE32
1158     /* If this page isn't marked as having any translations,
1159     then return immediately. */
1160     if (!(cpu->cd.DYNTRANS_ARCH.phystranslation[pagenr >> 5]
1161     & 1 << (pagenr & 31)))
1162     return;
1163     /* Remove the mark: */
1164     cpu->cd.DYNTRANS_ARCH.phystranslation[pagenr >> 5] &=
1165     ~ (1 << (pagenr & 31));
1166     #endif
1167    
1168 dpavlin 14 table_index = PAGENR_TO_TABLE_INDEX(pagenr);
1169    
1170     physpage_entryp = &(((uint32_t *)cpu->
1171     translation_cache)[table_index]);
1172     physpage_ofs = *physpage_entryp;
1173 dpavlin 18 prev_ppp = ppp = NULL;
1174 dpavlin 14
1175     /* Traverse the physical page chain: */
1176     while (physpage_ofs != 0) {
1177 dpavlin 18 prev_ppp = ppp;
1178 dpavlin 14 ppp = (struct DYNTRANS_TC_PHYSPAGE *)
1179     (cpu->translation_cache + physpage_ofs);
1180     /* If we found the page in the cache,
1181     then we're done: */
1182     if (ppp->physaddr == addr)
1183     break;
1184     /* Try the next page in the chain: */
1185     physpage_ofs = ppp->next_ofs;
1186     }
1187    
1188 dpavlin 18 if (physpage_ofs == 0)
1189     ppp = NULL;
1190    
1191     #if 1
1192     /*
1193     * "Bypass" the page, removing it from the code cache.
1194     *
1195     * NOTE/TODO: This gives _TERRIBLE_ performance with self-
1196     * modifying code, or when a single page is used for both
1197     * code and (writable) data.
1198     */
1199 dpavlin 14 if (ppp != NULL) {
1200 dpavlin 18 if (prev_ppp != NULL)
1201     prev_ppp->next_ofs = ppp->next_ofs;
1202     else
1203     *physpage_entryp = ppp->next_ofs;
1204     }
1205     #else
1206     /*
1207     * Instead of removing the page from the code cache, each
1208     * entry can be set to "to_be_translated". This is slow in
1209     * the general case, but in the case of self-modifying code,
1210     * it might be faster since we don't risk wasting cache
1211     * memory as quickly (which would force unnecessary Restarts).
1212     */
1213     if (ppp != NULL) {
1214 dpavlin 14 /* TODO: Is this faster than copying an entire
1215     template page? */
1216     int i;
1217     for (i=0; i<DYNTRANS_IC_ENTRIES_PER_PAGE; i++)
1218     ppp->ics[i].f =
1219     #ifdef DYNTRANS_DUALMODE_32
1220     cpu->is_32bit? instr32(to_be_translated) :
1221     #endif
1222     instr(to_be_translated);
1223     }
1224 dpavlin 18 #endif
1225 dpavlin 14 }
1226    
1227 dpavlin 18 /* Invalidate entries (NOTE: only code entries) in the VPH table: */
1228     for (r = DYNTRANS_MAX_VPH_TLB_ENTRIES/2;
1229     r < DYNTRANS_MAX_VPH_TLB_ENTRIES; r ++) {
1230 dpavlin 14 if (cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].valid) {
1231     vaddr_page = cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r]
1232     .vaddr_page & ~(DYNTRANS_PAGESIZE-1);
1233     paddr_page = cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r]
1234     .paddr_page & ~(DYNTRANS_PAGESIZE-1);
1235    
1236     if (flags & INVALIDATE_ALL ||
1237     (flags & INVALIDATE_PADDR && paddr_page == addr) ||
1238     (flags & INVALIDATE_VADDR && vaddr_page == addr)) {
1239     #ifdef MODE32
1240 dpavlin 18 uint32_t index =
1241     DYNTRANS_ADDR_TO_PAGENR(vaddr_page);
1242 dpavlin 14 cpu->cd.DYNTRANS_ARCH.phys_page[index] = NULL;
1243 dpavlin 18 /* Remove the mark: */
1244     index = DYNTRANS_ADDR_TO_PAGENR(paddr_page);
1245     cpu->cd.DYNTRANS_ARCH.phystranslation[
1246     index >> 5] &= ~ (1 << (index & 31));
1247 dpavlin 14 #else
1248 dpavlin 24 const uint32_t mask1 = (1 << DYNTRANS_L1N) - 1;
1249     const uint32_t mask2 = (1 << DYNTRANS_L2N) - 1;
1250     const uint32_t mask3 = (1 << DYNTRANS_L3N) - 1;
1251     uint32_t x1, x2, x3;
1252     struct DYNTRANS_L2_64_TABLE *l2;
1253     struct DYNTRANS_L3_64_TABLE *l3;
1254 dpavlin 14
1255 dpavlin 24 x1 = (vaddr_page >> (64-DYNTRANS_L1N)) & mask1;
1256     x2 = (vaddr_page >> (64-DYNTRANS_L1N -
1257     DYNTRANS_L2N)) & mask2;
1258     x3 = (vaddr_page >> (64-DYNTRANS_L1N -
1259     DYNTRANS_L2N - DYNTRANS_L3N)) & mask3;
1260     l2 = cpu->cd.DYNTRANS_ARCH.l1_64[x1];
1261     l3 = l2->l3[x2];
1262     l3->phys_page[x3] = NULL;
1263 dpavlin 14 #endif
1264     }
1265     }
1266     }
1267     }
1268     #endif /* DYNTRANS_INVALIDATE_TC_CODE */
1269    
1270    
1271    
1272     #ifdef DYNTRANS_UPDATE_TRANSLATION_TABLE
1273     /*
1274     * XXX_update_translation_table():
1275     *
1276     * Update the virtual memory translation tables.
1277     */
1278     void DYNTRANS_UPDATE_TRANSLATION_TABLE(struct cpu *cpu, uint64_t vaddr_page,
1279     unsigned char *host_page, int writeflag, uint64_t paddr_page)
1280     {
1281 dpavlin 20 #ifndef MODE32
1282 dpavlin 14 int64_t lowest, highest = -1;
1283 dpavlin 20 #endif
1284 dpavlin 18 int found, r, lowest_index, start, end, useraccess = 0;
1285 dpavlin 14
1286     #ifdef MODE32
1287     uint32_t index;
1288     vaddr_page &= 0xffffffffULL;
1289     paddr_page &= 0xffffffffULL;
1290     /* fatal("update_translation_table(): v=0x%x, h=%p w=%i"
1291     " p=0x%x\n", (int)vaddr_page, host_page, writeflag,
1292     (int)paddr_page); */
1293     #else /* !MODE32 */
1294 dpavlin 24 const uint32_t mask1 = (1 << DYNTRANS_L1N) - 1;
1295     const uint32_t mask2 = (1 << DYNTRANS_L2N) - 1;
1296     const uint32_t mask3 = (1 << DYNTRANS_L3N) - 1;
1297     uint32_t x1, x2, x3;
1298     struct DYNTRANS_L2_64_TABLE *l2;
1299     struct DYNTRANS_L3_64_TABLE *l3;
1300     /* fatal("update_translation_table(): v=0x%"PRIx64", h=%p w=%i"
1301     " p=0x%"PRIx64"\n", (uint64_t)vaddr_page, host_page, writeflag,
1302     (uint64_t)paddr_page); */
1303 dpavlin 14 #endif
1304    
1305 dpavlin 18 if (writeflag & MEMORY_USER_ACCESS) {
1306     writeflag &= ~MEMORY_USER_ACCESS;
1307     useraccess = 1;
1308     }
1309    
1310     start = 0; end = DYNTRANS_MAX_VPH_TLB_ENTRIES / 2;
1311     #if 1
1312     /* Half of the TLB used for data, half for code: */
1313     if (writeflag & TLB_CODE) {
1314     writeflag &= ~TLB_CODE;
1315     start = end; end = DYNTRANS_MAX_VPH_TLB_ENTRIES;
1316     }
1317     #else
1318     /* Data and code entries are mixed. */
1319     end = DYNTRANS_MAX_VPH_TLB_ENTRIES;
1320     #endif
1321    
1322 dpavlin 14 /* Scan the current TLB entries: */
1323 dpavlin 20 lowest_index = start;
1324 dpavlin 18
1325     #ifdef MODE32
1326 dpavlin 20 /*
1327     * NOTE 1: vaddr_to_tlbindex is one more than the index, so that
1328     * 0 becomes -1, which means a miss.
1329     *
1330     * NOTE 2: When a miss occurs, instead of scanning the entire tlb
1331     * for the entry with the lowest time stamp, just choosing
1332     * one at random will work as well.
1333     */
1334     found = (int)cpu->cd.DYNTRANS_ARCH.vaddr_to_tlbindex[
1335 dpavlin 18 DYNTRANS_ADDR_TO_PAGENR(vaddr_page)] - 1;
1336 dpavlin 20 if (found < 0) {
1337     static unsigned int x = 0;
1338     lowest_index = (x % (end-start)) + start;
1339     x ++;
1340     }
1341     #else
1342     lowest = cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[0].timestamp;
1343     found = -1;
1344 dpavlin 18 for (r=start; r<end; r++) {
1345 dpavlin 14 if (cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].timestamp < lowest) {
1346     lowest = cpu->cd.DYNTRANS_ARCH.
1347     vph_tlb_entry[r].timestamp;
1348     lowest_index = r;
1349     }
1350     if (cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].timestamp > highest)
1351     highest = cpu->cd.DYNTRANS_ARCH.
1352     vph_tlb_entry[r].timestamp;
1353     if (cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].valid &&
1354     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].vaddr_page ==
1355     vaddr_page) {
1356     found = r;
1357     break;
1358     }
1359     }
1360 dpavlin 20 #endif
1361 dpavlin 14
1362     if (found < 0) {
1363     /* Create the new TLB entry, overwriting the oldest one: */
1364     r = lowest_index;
1365     if (cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].valid) {
1366     /* This one has to be invalidated first: */
1367     DYNTRANS_INVALIDATE_TLB_ENTRY(cpu,
1368     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].vaddr_page,
1369     0);
1370     }
1371    
1372     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].valid = 1;
1373     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].host_page = host_page;
1374     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].paddr_page = paddr_page;
1375     cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].vaddr_page = vaddr_page;
1376 dpavlin 20 cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].writeflag =
1377     writeflag & MEM_WRITE;
1378     #ifndef MODE32
1379 dpavlin 14 cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].timestamp = highest + 1;
1380 dpavlin 20 #endif
1381 dpavlin 14
1382     /* Add the new translation to the table: */
1383     #ifdef MODE32
1384 dpavlin 18 index = DYNTRANS_ADDR_TO_PAGENR(vaddr_page);
1385 dpavlin 14 cpu->cd.DYNTRANS_ARCH.host_load[index] = host_page;
1386     cpu->cd.DYNTRANS_ARCH.host_store[index] =
1387     writeflag? host_page : NULL;
1388     cpu->cd.DYNTRANS_ARCH.phys_addr[index] = paddr_page;
1389     cpu->cd.DYNTRANS_ARCH.phys_page[index] = NULL;
1390 dpavlin 18 cpu->cd.DYNTRANS_ARCH.vaddr_to_tlbindex[index] = r + 1;
1391     #ifdef DYNTRANS_ARM
1392     if (useraccess)
1393 dpavlin 20 cpu->cd.DYNTRANS_ARCH.is_userpage[index >> 5]
1394     |= 1 << (index & 31);
1395 dpavlin 18 #endif
1396 dpavlin 24 #else /* !MODE32 */
1397     x1 = (vaddr_page >> (64-DYNTRANS_L1N)) & mask1;
1398     x2 = (vaddr_page >> (64-DYNTRANS_L1N-DYNTRANS_L2N)) & mask2;
1399     x3 = (vaddr_page >> (64-DYNTRANS_L1N-DYNTRANS_L2N-DYNTRANS_L3N))
1400     & mask3;
1401     l2 = cpu->cd.DYNTRANS_ARCH.l1_64[x1];
1402     if (l2 == cpu->cd.DYNTRANS_ARCH.l2_64_dummy) {
1403     if (cpu->cd.DYNTRANS_ARCH.next_free_l2 != NULL) {
1404     l2 = cpu->cd.DYNTRANS_ARCH.l1_64[x1] =
1405     cpu->cd.DYNTRANS_ARCH.next_free_l2;
1406     cpu->cd.DYNTRANS_ARCH.next_free_l2 = l2->next;
1407     } else {
1408     int i;
1409     l2 = cpu->cd.DYNTRANS_ARCH.l1_64[x1] =
1410     malloc(sizeof(struct DYNTRANS_L2_64_TABLE));
1411     for (i=0; i<(1 << DYNTRANS_L2N); i++)
1412     l2->l3[i] = cpu->cd.DYNTRANS_ARCH.
1413     l3_64_dummy;
1414     }
1415     }
1416     l3 = l2->l3[x2];
1417     if (l3 == cpu->cd.DYNTRANS_ARCH.l3_64_dummy) {
1418     if (cpu->cd.DYNTRANS_ARCH.next_free_l3 != NULL) {
1419     l3 = l2->l3[x2] =
1420     cpu->cd.DYNTRANS_ARCH.next_free_l3;
1421     cpu->cd.DYNTRANS_ARCH.next_free_l3 = l3->next;
1422     } else {
1423     l3 = l2->l3[x2] = zeroed_alloc(sizeof(
1424     struct DYNTRANS_L3_64_TABLE));
1425     }
1426     l2->refcount ++;
1427     }
1428     l3->host_load[x3] = host_page;
1429     l3->host_store[x3] = writeflag? host_page : NULL;
1430     l3->phys_addr[x3] = paddr_page;
1431     l3->phys_page[x3] = NULL;
1432     l3->vaddr_to_tlbindex[x3] = r + 1;
1433     l3->refcount ++;
1434     #endif /* !MODE32 */
1435 dpavlin 14 } else {
1436     /*
1437     * The translation was already in the TLB.
1438     * Writeflag = 0: Do nothing.
1439     * Writeflag = 1: Make sure the page is writable.
1440 dpavlin 20 * Writeflag = MEM_DOWNGRADE: Downgrade to readonly.
1441 dpavlin 14 */
1442 dpavlin 18 r = found;
1443 dpavlin 20 #ifndef MODE32
1444 dpavlin 18 cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].timestamp = highest + 1;
1445 dpavlin 20 #endif
1446     if (writeflag & MEM_WRITE)
1447 dpavlin 14 cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].writeflag = 1;
1448 dpavlin 20 if (writeflag & MEM_DOWNGRADE)
1449 dpavlin 14 cpu->cd.DYNTRANS_ARCH.vph_tlb_entry[r].writeflag = 0;
1450     #ifdef MODE32
1451 dpavlin 18 index = DYNTRANS_ADDR_TO_PAGENR(vaddr_page);
1452 dpavlin 14 cpu->cd.DYNTRANS_ARCH.phys_page[index] = NULL;
1453 dpavlin 18 #ifdef DYNTRANS_ARM
1454 dpavlin 20 cpu->cd.DYNTRANS_ARCH.is_userpage[index>>5] &= ~(1<<(index&31));
1455 dpavlin 18 if (useraccess)
1456 dpavlin 20 cpu->cd.DYNTRANS_ARCH.is_userpage[index >> 5]
1457     |= 1 << (index & 31);
1458 dpavlin 18 #endif
1459 dpavlin 14 if (cpu->cd.DYNTRANS_ARCH.phys_addr[index] == paddr_page) {
1460 dpavlin 20 if (writeflag & MEM_WRITE)
1461 dpavlin 14 cpu->cd.DYNTRANS_ARCH.host_store[index] =
1462     host_page;
1463 dpavlin 20 if (writeflag & MEM_DOWNGRADE)
1464 dpavlin 14 cpu->cd.DYNTRANS_ARCH.host_store[index] = NULL;
1465     } else {
1466     /* Change the entire physical/host mapping: */
1467     cpu->cd.DYNTRANS_ARCH.host_load[index] = host_page;
1468     cpu->cd.DYNTRANS_ARCH.host_store[index] =
1469     writeflag? host_page : NULL;
1470     cpu->cd.DYNTRANS_ARCH.phys_addr[index] = paddr_page;
1471     }
1472 dpavlin 24 #else /* !MODE32 */
1473     x1 = (vaddr_page >> (64-DYNTRANS_L1N)) & mask1;
1474     x2 = (vaddr_page >> (64-DYNTRANS_L1N-DYNTRANS_L2N)) & mask2;
1475     x3 = (vaddr_page >> (64-DYNTRANS_L1N-DYNTRANS_L2N-DYNTRANS_L3N))
1476     & mask3;
1477     l2 = cpu->cd.DYNTRANS_ARCH.l1_64[x1];
1478     l3 = l2->l3[x2];
1479     if (l3->phys_addr[x3] == paddr_page) {
1480     if (writeflag & MEM_WRITE)
1481     l3->host_store[x3] = host_page;
1482     if (writeflag & MEM_DOWNGRADE)
1483     l3->host_store[x3] = NULL;
1484     } else {
1485     /* Change the entire physical/host mapping: */
1486     l3->host_load[x3] = host_page;
1487     l3->host_store[x3] = writeflag? host_page : NULL;
1488     l3->phys_addr[x3] = paddr_page;
1489     }
1490     #endif /* !MODE32 */
1491 dpavlin 14 }
1492     }
1493     #endif /* DYNTRANS_UPDATE_TRANSLATION_TABLE */
1494    
1495    
1496     /*****************************************************************************/
1497    
1498    
1499     #ifdef DYNTRANS_TO_BE_TRANSLATED_HEAD
1500     /*
1501     * Check for breakpoints.
1502     */
1503     if (!single_step_breakpoint) {
1504 dpavlin 24 MODE_uint_t curpc = cpu->pc;
1505 dpavlin 14 int i;
1506     for (i=0; i<cpu->machine->n_breakpoints; i++)
1507 dpavlin 24 if (curpc == (MODE_uint_t)
1508 dpavlin 14 cpu->machine->breakpoint_addr[i]) {
1509     if (!cpu->machine->instruction_trace) {
1510     int old_quiet_mode = quiet_mode;
1511     quiet_mode = 0;
1512 dpavlin 24 DISASSEMBLE(cpu, ib, 1, 0);
1513 dpavlin 14 quiet_mode = old_quiet_mode;
1514     }
1515 dpavlin 24 fatal("BREAKPOINT: pc = 0x%"PRIx64"\n(The "
1516 dpavlin 14 "instruction has not yet executed.)\n",
1517 dpavlin 24 (uint64_t)cpu->pc);
1518 dpavlin 22 #ifdef DYNTRANS_DELAYSLOT
1519 dpavlin 24 if (cpu->delay_slot != NOT_DELAYED)
1520 dpavlin 22 fatal("ERROR! Breakpoint in a delay"
1521     " slot! Not yet supported.\n");
1522     #endif
1523 dpavlin 14 single_step_breakpoint = 1;
1524     single_step = 1;
1525     goto stop_running_translated;
1526     }
1527     }
1528     #endif /* DYNTRANS_TO_BE_TRANSLATED_HEAD */
1529    
1530    
1531     /*****************************************************************************/
1532    
1533    
1534     #ifdef DYNTRANS_TO_BE_TRANSLATED_TAIL
1535     /*
1536     * If we end up here, then an instruction was translated.
1537 dpavlin 18 * Mark the page as containing a translation.
1538     *
1539     * (Special case for 32-bit mode: set the corresponding bit in the
1540     * phystranslation[] array.)
1541 dpavlin 14 */
1542 dpavlin 24 /* Make sure cur_physpage is in synch: */
1543     cpu->cd.DYNTRANS_ARCH.cur_physpage = (void *)
1544     cpu->cd.DYNTRANS_ARCH.cur_ic_page;
1545 dpavlin 18 #ifdef MODE32
1546     if (!(cpu->cd.DYNTRANS_ARCH.cur_physpage->flags & TRANSLATIONS)) {
1547 dpavlin 22 uint32_t index = DYNTRANS_ADDR_TO_PAGENR((uint32_t)addr);
1548 dpavlin 18 cpu->cd.DYNTRANS_ARCH.phystranslation[index >> 5] |=
1549     (1 << (index & 31));
1550     }
1551     #endif
1552     cpu->cd.DYNTRANS_ARCH.cur_physpage->flags |= TRANSLATIONS;
1553 dpavlin 14
1554 dpavlin 18
1555 dpavlin 14 /*
1556     * Now it is time to check for combinations of instructions that can
1557     * be converted into a single function call.
1558     *
1559     * Note: Single-stepping or instruction tracing doesn't work with
1560 dpavlin 24 * instruction combination. For architectures with delay slots,
1561     * we also ignore combinations if the delay slot is across a page
1562     * boundary.
1563 dpavlin 14 */
1564 dpavlin 24 if (!single_step && !cpu->machine->instruction_trace
1565     #ifdef DYNTRANS_DELAYSLOT
1566     && !in_crosspage_delayslot
1567     #endif
1568     ) {
1569 dpavlin 20 if (cpu->cd.DYNTRANS_ARCH.combination_check != NULL &&
1570 dpavlin 18 cpu->machine->speed_tricks)
1571 dpavlin 20 cpu->cd.DYNTRANS_ARCH.combination_check(cpu, ic,
1572 dpavlin 18 addr & (DYNTRANS_PAGESIZE - 1));
1573     }
1574 dpavlin 14
1575 dpavlin 24 cpu->cd.DYNTRANS_ARCH.combination_check = NULL;
1576    
1577     /* An additional check, to catch some bugs: */
1578     if (ic->f == (
1579     #ifdef DYNTRANS_DUALMODE_32
1580     cpu->is_32bit? instr32(to_be_translated) :
1581     #endif
1582     instr(to_be_translated))) {
1583     fatal("INTERNAL ERROR: ic->f not set!\n");
1584     goto bad;
1585     }
1586     if (ic->f == NULL) {
1587     fatal("INTERNAL ERROR: ic->f == NULL!\n");
1588     goto bad;
1589     }
1590    
1591 dpavlin 14 /* ... and finally execute the translated instruction: */
1592 dpavlin 24 if ((single_step_breakpoint && cpu->delay_slot == NOT_DELAYED)
1593     #ifdef DYNTRANS_DELAYSLOT
1594     || in_crosspage_delayslot
1595     #endif
1596     ) {
1597 dpavlin 14 /*
1598     * Special case when single-stepping: Execute the translated
1599     * instruction, but then replace it with a "to be translated"
1600     * directly afterwards.
1601     */
1602     single_step_breakpoint = 0;
1603 dpavlin 24 #ifdef DYNTRANS_VARIABLE_INSTRUCTION_LENGTH
1604     cpu->cd.DYNTRANS_ARCH.next_ic = ic + ic->arg[0];
1605     #endif
1606 dpavlin 14 ic->f(cpu, ic);
1607     ic->f =
1608     #ifdef DYNTRANS_DUALMODE_32
1609     cpu->is_32bit? instr32(to_be_translated) :
1610     #endif
1611     instr(to_be_translated);
1612 dpavlin 24 #ifdef DYNTRANS_VARIABLE_INSTRUCTION_LENGTH
1613     ic->arg[0] = 0;
1614     #endif
1615     } else {
1616     #ifdef DYNTRANS_VARIABLE_INSTRUCTION_LENGTH
1617     cpu->cd.DYNTRANS_ARCH.next_ic = ic + ic->arg[0];
1618    
1619     /* Additional check, for variable length ISAs: */
1620     if (ic->arg[0] == 0) {
1621     fatal("INTERNAL ERROR: instr len = 0!\n");
1622     goto bad;
1623     }
1624     #endif
1625    
1626     /* Finally finally :-), execute the instruction: */
1627 dpavlin 14 ic->f(cpu, ic);
1628 dpavlin 24 }
1629 dpavlin 14
1630     return;
1631    
1632    
1633     bad: /*
1634     * Nothing was translated. (Unimplemented or illegal instruction.)
1635     */
1636    
1637     quiet_mode = 0;
1638     fatal("to_be_translated(): TODO: unimplemented instruction");
1639    
1640     if (cpu->machine->instruction_trace)
1641     #ifdef MODE32
1642 dpavlin 24 fatal(" at 0x%"PRIx32"\n", (uint32_t)cpu->pc);
1643 dpavlin 14 #else
1644 dpavlin 24 fatal(" at 0x%"PRIx64"\n", (uint64_t)cpu->pc);
1645 dpavlin 14 #endif
1646     else {
1647     fatal(":\n");
1648 dpavlin 24 DISASSEMBLE(cpu, ib, 1, 0);
1649 dpavlin 14 }
1650    
1651     cpu->running = 0;
1652     cpu->dead = 1;
1653     stop_running_translated:
1654     debugger_n_steps_left_before_interaction = 0;
1655     cpu->running_translated = 0;
1656     ic = cpu->cd.DYNTRANS_ARCH.next_ic = &nothing_call;
1657     cpu->cd.DYNTRANS_ARCH.next_ic ++;
1658    
1659     /* Execute the "nothing" instruction: */
1660     ic->f(cpu, ic);
1661     #endif /* DYNTRANS_TO_BE_TRANSLATED_TAIL */
1662    

  ViewVC Help
Powered by ViewVC 1.1.26