/[gxemul]/trunk/src/cpus/cpu_mips.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_mips.c

Parent Directory Parent Directory | Revision Log Revision Log


Revision 14 - (hide annotations)
Mon Oct 8 16:18:51 2007 UTC (16 years, 6 months ago) by dpavlin
File MIME type: text/plain
File size: 119314 byte(s)
++ trunk/HISTORY	(local)
$Id: HISTORY,v 1.982 2005/10/07 22:45:32 debug Exp $
20050816	Some success in decoding the way the SGI O2 PROM draws graphics
		during bootup; lines/rectangles and bitmaps work, enough to
		show the bootlogo etc. :-)
		Adding more PPC instructions, and (dummy) BAT registers.
20050817	Updating the pckbc to support scancode type 3 keyboards
		(required in order to interact with the SGI O2 PROM).
		Adding more PPC instructions.
20050818	Adding more ARM instructions; general register forms.
		Importing armreg.h from NetBSD (ARM cpu ids). Adding a (dummy)
		CATS machine mode (using SA110 as the default CPU).
		Continuing on general dyntrans related stuff.
20050819	Register forms for ARM load/stores. Gaah! The Compaq C Compiler
		bug is triggered for ARM loads as well, not just PPC :-(
		Adding full support for ARM PC-relative load/stores, and load/
		stores where the PC register is the destination register.
		Adding support for ARM a.out binaries.
20050820	Continuing to add more ARM instructions, and correcting some
		bugs. Continuing on CATS emulation.
		More work on the PPC stuff.
20050821	Minor PPC and ARM updates. Adding more machine types.
20050822	All ARM "data processing instructions" are now generated
		automatically.
20050824	Beginning the work on the ARM system control coprocessor.
		Adding support for ARM halfword load/stores, and signed loads.
20050825	Fixing an important bug related to the ARM condition codes.
		OpenBSD/zaurus and NetBSD/netwinder now print some boot
		messages. :)
		Adding a dummy SH (Hitachi SuperH) cpu family.
		Beginning to add some ARM virtual address translation.
		MIPS bugfixes: unaligned PC now cause an ADEL exception (at
		least for non-bintrans execution), and ADEL/ADES (not
		TLBL/TLBS) are used if userland tries to access kernel space.
		(Thanks to Joshua Wise for making me aware of these bugs.)
20050827	More work on the ARM emulation, and various other updates.
20050828	More ARM updates.
		Finally taking the time to work on translation invalidation
		(i.e. invalidating translated code mappings when memory is
		written to). Hopefully this doesn't break anything.
20050829	Moving CPU related files from src/ to a new subdir, src/cpus/.
		Moving PROM emulation stuff from src/ to src/promemul/.
		Better debug instruction trace for ARM loads and stores.
20050830	Various ARM updates (correcting CMP flag calculation, etc).
20050831	PPC instruction updates. (Flag fixes, etc.)
20050901	Various minor PPC and ARM instruction emulation updates.
		Minor OpenFirmware emulation updates.
20050903	Adding support for adding arbitrary ARM coprocessors (with
		the i80321 I/O coprocessor as a first test).
		Various other ARM and PPC updates.
20050904	Adding some SHcompact disassembly routines.
20050907	(Re)adding a dummy HPPA CPU module, and a dummy i960 module.
20050908	Began hacking on some Apple Partition Table support.
20050909	Adding support for loading Mach-O (Darwin PPC) binaries.
20050910	Fixing an ARM bug (Carry flag was incorrectly updated for some
		data processing instructions); OpenBSD/cats and NetBSD/
		netwinder get quite a bit further now.
		Applying a patch to dev_wdc, and a one-liner to dev_pcic, to
		make them work better when emulating new versions of OpenBSD.
		(Thanks to Alexander Yurchenko for the patches.)
		Also doing some other minor updates to dev_wdc. (Some cleanup,
		and finally converting to devinit, etc.)
20050912	IRIX doesn't have u_int64_t by default (noticed by Andreas
		<avr@gnulinux.nl>); configure updated to reflect this.
		Working on ARM register bank switching, CPSR vs SPSR issues,
		and beginning the work on interrupt/exception support.
20050913	Various minor ARM updates (speeding up load/store multiple,
		and fixing a ROR bug in R(); NetBSD/cats now boots as far as
		OpenBSD/cats).
20050917	Adding a dummy Atmel AVR (8-bit) cpu family skeleton.
20050918	Various minor updates.
20050919	Symbols are now loaded from Mach-O executables.
		Continuing the work on adding ARM exception support.
20050920	More work on ARM stuff: OpenBSD/cats and NetBSD/cats reach
		userland! :-)
20050921	Some more progress on ARM interrupt specifics.
20050923	Fixing linesize for VR4121 (patch by Yurchenko). Also fixing
		linesizes/cachesizes for some other VR4xxx.
		Adding a dummy Acer Labs M1543 PCI-ISA bridge (for CATS) and a
		dummy Symphony Labs 83C553 bridge (for Netwinder), usable by 
		dev_footbridge.
20050924	Some PPC progress.
20050925	More PPC progress.
20050926	PPC progress (fixing some bugs etc); Darwin's kernel gets
		slightly further than before.
20050928	Various updates: footbridge/ISA/pciide stuff, and finally
		fixing the VGA text scroll-by-changing-the-base-offset bug.
20050930	Adding a dummy S3 ViRGE pci card for CATS emulation, which
		both NetBSD and OpenBSD detects as VGA.
		Continuing on Footbridge (timers, ISA interrupt stuff).
20051001	Continuing... there are still bugs, probably interrupt-
		related.
20051002	More work on the Footbridge (interrupt stuff).
20051003	Various minor updates. (Trying to find the bug(s).)
20051004	Continuing on the ARM stuff.
20051005	More ARM-related fixes.
20051007	FINALLY! Found and fixed 2 ARM bugs: 1 memory related, and the
		other was because of an error in the ARM manual (load multiple
		with the S-bit set should _NOT_ load usermode registers, as the
		manual says, but it should load saved registers, which may or
		may not happen to be usermode registers).
		NetBSD/cats and OpenBSD/cats seem to install fine now :-)
		except for a minor bug at the end of the OpenBSD/cats install.
		Updating the documentation, preparing for the next release.
20051008	Continuing with release testing and cleanup.

1 dpavlin 14 /*
2     * Copyright (C) 2003-2005 Anders Gavare. All rights reserved.
3     *
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     * $Id: cpu_mips.c,v 1.3 2005/09/19 20:10:57 debug Exp $
29     *
30     * MIPS core CPU emulation.
31     */
32    
33     #include <stdio.h>
34     #include <stdlib.h>
35     #include <string.h>
36     #include <sys/types.h>
37     #include <ctype.h>
38    
39     #include "../../config.h"
40    
41    
42     #ifndef ENABLE_MIPS
43    
44    
45     #include "cpu_mips.h"
46    
47     /*
48     * mips_cpu_family_init():
49     *
50     * Bogus function.
51     */
52     int mips_cpu_family_init(struct cpu_family *fp)
53     {
54     return 0;
55     }
56    
57    
58     /* TODO: Maybe it isn't very nice to have these global like this... */
59     void mips_cpu_exception(struct cpu *cpu, int exccode, int tlb, uint64_t vaddr,
60     int coproc_nr, uint64_t vaddr_vpn2, int vaddr_asid, int x_64) { }
61    
62    
63     #else /* ENABLE_MIPS */
64    
65    
66     #include "arcbios.h"
67     #include "bintrans.h"
68     #include "cop0.h"
69     #include "cpu.h"
70     #include "cpu_mips.h"
71     #include "debugger.h"
72     #include "devices.h"
73     #include "emul.h"
74     #include "machine.h"
75     #include "memory.h"
76     #include "mips_cpu_types.h"
77     #include "opcodes_mips.h"
78     #include "symbol.h"
79    
80    
81     extern volatile int single_step;
82     extern int show_opcode_statistics;
83     extern int old_show_trace_tree;
84     extern int old_instruction_trace;
85     extern int old_quiet_mode;
86     extern int quiet_mode;
87    
88     static char *exception_names[] = EXCEPTION_NAMES;
89    
90     static char *hi6_names[] = HI6_NAMES;
91     static char *regimm_names[] = REGIMM_NAMES;
92     static char *special_names[] = SPECIAL_NAMES;
93     static char *special2_names[] = SPECIAL2_NAMES;
94    
95     static char *regnames[] = MIPS_REGISTER_NAMES;
96     static char *cop0_names[] = COP0_NAMES;
97    
98     #include "cpu_mips16.c"
99    
100    
101     /*
102     * regname():
103     *
104     * Convert a register number into either 'r0', 'r31' etc, or a symbolic
105     * name, depending on machine->show_symbolic_register_names.
106     *
107     * NOTE: _NOT_ reentrant.
108     */
109     static char *regname(struct machine *machine, int r)
110     {
111     static char ch[4];
112     ch[3] = ch[2] = '\0';
113    
114     if (r<0 || r>=32)
115     strlcpy(ch, "xx", sizeof(ch));
116     else if (machine->show_symbolic_register_names)
117     strlcpy(ch, regnames[r], sizeof(ch));
118     else
119     snprintf(ch, sizeof(ch), "r%i", r);
120    
121     return ch;
122     }
123    
124    
125     /*
126     * mips_cpu_new():
127     *
128     * Create a new MIPS cpu object.
129     *
130     * Returns 1 on success, 0 if there was no valid MIPS processor with
131     * a matching name.
132     */
133     int mips_cpu_new(struct cpu *cpu, struct memory *mem, struct machine *machine,
134     int cpu_id, char *cpu_type_name)
135     {
136     int i, found, j, tags_size, n_cache_lines, size_per_cache_line;
137     struct mips_cpu_type_def cpu_type_defs[] = MIPS_CPU_TYPE_DEFS;
138     int64_t secondary_cache_size;
139     int x, linesize;
140    
141     /* Scan the cpu_type_defs list for this cpu type: */
142     i = 0;
143     found = -1;
144     while (i >= 0 && cpu_type_defs[i].name != NULL) {
145     if (strcasecmp(cpu_type_defs[i].name, cpu_type_name) == 0) {
146     found = i;
147     break;
148     }
149     i++;
150     }
151    
152     if (found == -1)
153     return 0;
154    
155     cpu->memory_rw = mips_memory_rw;
156     cpu->cd.mips.cpu_type = cpu_type_defs[found];
157     cpu->name = cpu->cd.mips.cpu_type.name;
158     cpu->byte_order = EMUL_LITTLE_ENDIAN;
159     cpu->cd.mips.gpr[MIPS_GPR_SP] = INITIAL_STACK_POINTER;
160     cpu->update_translation_table = mips_update_translation_table;
161     cpu->invalidate_translation_caches_paddr =
162     mips_invalidate_translation_caches_paddr;
163    
164     if (cpu->cd.mips.cpu_type.isa_level <= 2 ||
165     cpu->cd.mips.cpu_type.isa_level == 32)
166     cpu->is_32bit = 1;
167    
168     if (cpu_id == 0)
169     debug("%s", cpu->cd.mips.cpu_type.name);
170    
171     /*
172     * CACHES:
173     *
174     * 1) Use DEFAULT_PCACHE_SIZE and DEFAULT_PCACHE_LINESIZE etc.
175     * 2) If there are specific values defined for this type of cpu,
176     * in its cpu_type substruct, then let's use those.
177     * 3) Values in the emul struct override both of the above.
178     *
179     * Once we've decided which values to use, they are stored in
180     * the emul struct so they can be used from src/machine.c etc.
181     */
182    
183     x = DEFAULT_PCACHE_SIZE;
184     if (cpu->cd.mips.cpu_type.pdcache)
185     x = cpu->cd.mips.cpu_type.pdcache;
186     if (machine->cache_pdcache == 0)
187     machine->cache_pdcache = x;
188    
189     x = DEFAULT_PCACHE_SIZE;
190     if (cpu->cd.mips.cpu_type.picache)
191     x = cpu->cd.mips.cpu_type.picache;
192     if (machine->cache_picache == 0)
193     machine->cache_picache = x;
194    
195     if (machine->cache_secondary == 0)
196     machine->cache_secondary = cpu->cd.mips.cpu_type.scache;
197    
198     linesize = DEFAULT_PCACHE_LINESIZE;
199     if (cpu->cd.mips.cpu_type.pdlinesize)
200     linesize = cpu->cd.mips.cpu_type.pdlinesize;
201     if (machine->cache_pdcache_linesize == 0)
202     machine->cache_pdcache_linesize = linesize;
203    
204     linesize = DEFAULT_PCACHE_LINESIZE;
205     if (cpu->cd.mips.cpu_type.pilinesize)
206     linesize = cpu->cd.mips.cpu_type.pilinesize;
207     if (machine->cache_picache_linesize == 0)
208     machine->cache_picache_linesize = linesize;
209    
210     linesize = 0;
211     if (cpu->cd.mips.cpu_type.slinesize)
212     linesize = cpu->cd.mips.cpu_type.slinesize;
213     if (machine->cache_secondary_linesize == 0)
214     machine->cache_secondary_linesize = linesize;
215    
216    
217     /*
218     * Primary Data and Instruction caches:
219     */
220     for (i=CACHE_DATA; i<=CACHE_INSTRUCTION; i++) {
221     switch (i) {
222     case CACHE_DATA:
223     x = 1 << machine->cache_pdcache;
224     linesize = 1 << machine->cache_pdcache_linesize;
225     break;
226     case CACHE_INSTRUCTION:
227     x = 1 << machine->cache_picache;
228     linesize = 1 << machine->cache_picache_linesize;
229     break;
230     }
231    
232     /* Primary cache size and linesize: */
233     cpu->cd.mips.cache_size[i] = x;
234     cpu->cd.mips.cache_linesize[i] = linesize;
235    
236     switch (cpu->cd.mips.cpu_type.rev) {
237     case MIPS_R2000:
238     case MIPS_R3000:
239     size_per_cache_line = sizeof(struct r3000_cache_line);
240     break;
241     default:
242     size_per_cache_line = sizeof(struct r4000_cache_line);
243     }
244    
245     cpu->cd.mips.cache_mask[i] = cpu->cd.mips.cache_size[i] - 1;
246     cpu->cd.mips.cache_miss_penalty[i] = 10; /* TODO ? */
247    
248     cpu->cd.mips.cache[i] = malloc(cpu->cd.mips.cache_size[i]);
249     if (cpu->cd.mips.cache[i] == NULL) {
250     fprintf(stderr, "out of memory\n");
251     }
252    
253     n_cache_lines = cpu->cd.mips.cache_size[i] /
254     cpu->cd.mips.cache_linesize[i];
255     tags_size = n_cache_lines * size_per_cache_line;
256    
257     cpu->cd.mips.cache_tags[i] = malloc(tags_size);
258     if (cpu->cd.mips.cache_tags[i] == NULL) {
259     fprintf(stderr, "out of memory\n");
260     }
261    
262     /* Initialize the cache tags: */
263     switch (cpu->cd.mips.cpu_type.rev) {
264     case MIPS_R2000:
265     case MIPS_R3000:
266     for (j=0; j<n_cache_lines; j++) {
267     struct r3000_cache_line *rp;
268     rp = (struct r3000_cache_line *)
269     cpu->cd.mips.cache_tags[i];
270     rp[j].tag_paddr = 0;
271     rp[j].tag_valid = 0;
272     }
273     break;
274     default:
275     ;
276     }
277    
278     /* Set cache_last_paddr to something "impossible": */
279     cpu->cd.mips.cache_last_paddr[i] = IMPOSSIBLE_PADDR;
280     }
281    
282     /*
283     * Secondary cache:
284     */
285     secondary_cache_size = 0;
286     if (machine->cache_secondary)
287     secondary_cache_size = 1 << machine->cache_secondary;
288     /* TODO: linesize... */
289    
290     if (cpu_id == 0) {
291     debug(" (I+D = %i+%i KB",
292     (int)(cpu->cd.mips.cache_size[CACHE_INSTRUCTION] / 1024),
293     (int)(cpu->cd.mips.cache_size[CACHE_DATA] / 1024));
294    
295     if (secondary_cache_size != 0) {
296     debug(", L2 = ");
297     if (secondary_cache_size >= 1048576)
298     debug("%i MB", (int)
299     (secondary_cache_size / 1048576));
300     else
301     debug("%i KB", (int)
302     (secondary_cache_size / 1024));
303     }
304    
305     debug(")");
306     }
307    
308     /* System coprocessor (0), and FPU (1): */
309     cpu->cd.mips.coproc[0] = mips_coproc_new(cpu, 0);
310     cpu->cd.mips.coproc[1] = mips_coproc_new(cpu, 1);
311    
312     /*
313     * Initialize the cpu->cd.mips.pc_last_* cache (a 1-entry cache of the
314     * last program counter value). For pc_last_virtual_page, any
315     * "impossible" value will do. The pc should never ever get this
316     * value. (The other pc_last* variables do not need initialization,
317     * as they are not used before pc_last_virtual_page.)
318     */
319     cpu->cd.mips.pc_last_virtual_page = PC_LAST_PAGE_IMPOSSIBLE_VALUE;
320    
321     switch (cpu->cd.mips.cpu_type.mmu_model) {
322     case MMU3K:
323     cpu->translate_address = translate_address_mmu3k;
324     break;
325     case MMU8K:
326     cpu->translate_address = translate_address_mmu8k;
327     break;
328     case MMU10K:
329     cpu->translate_address = translate_address_mmu10k;
330     break;
331     default:
332     if (cpu->cd.mips.cpu_type.rev == MIPS_R4100)
333     cpu->translate_address = translate_address_mmu4100;
334     else
335     cpu->translate_address = translate_address_generic;
336     }
337    
338     /* Testing: */
339     cpu->cd.mips.host_load = zeroed_alloc(1048576 *
340     sizeof(unsigned char *));
341     cpu->cd.mips.host_store = zeroed_alloc(1048576 *
342     sizeof(unsigned char *));
343     cpu->cd.mips.host_load_orig = cpu->cd.mips.host_load;
344     cpu->cd.mips.host_store_orig = cpu->cd.mips.host_store;
345    
346     return 1;
347     }
348    
349    
350     /*
351     * mips_cpu_show_full_statistics():
352     *
353     * Show detailed statistics on opcode usage on each cpu.
354     */
355     void mips_cpu_show_full_statistics(struct machine *m)
356     {
357     int i, s1, s2, iadd = 4;
358    
359     if (m->bintrans_enable)
360     fatal("NOTE: Dynamic binary translation is used; this list"
361     " of opcode usage\n only includes instructions that"
362     " were interpreted manually!\n");
363    
364     for (i=0; i<m->ncpus; i++) {
365     fatal("cpu%i opcode statistics:\n", i);
366     debug_indentation(iadd);
367    
368     for (s1=0; s1<N_HI6; s1++) {
369     if (m->cpus[i]->cd.mips.stats_opcode[s1] > 0)
370     fatal("opcode %02x (%7s): %li\n", s1,
371     hi6_names[s1],
372     m->cpus[i]->cd.mips.stats_opcode[s1]);
373    
374     debug_indentation(iadd);
375     if (s1 == HI6_SPECIAL)
376     for (s2=0; s2<N_SPECIAL; s2++)
377     if (m->cpus[i]->cd.mips.stats__special[
378     s2] > 0)
379     fatal("special %02x (%7s): "
380     "%li\n", s2, special_names[
381     s2], m->cpus[i]->cd.mips.
382     stats__special[s2]);
383     if (s1 == HI6_REGIMM)
384     for (s2=0; s2<N_REGIMM; s2++)
385     if (m->cpus[i]->cd.mips.stats__regimm[
386     s2] > 0)
387     fatal("regimm %02x (%7s): "
388     "%li\n", s2, regimm_names[
389     s2], m->cpus[i]->cd.mips.
390     stats__regimm[s2]);
391     if (s1 == HI6_SPECIAL2)
392     for (s2=0; s2<N_SPECIAL; s2++)
393     if (m->cpus[i]->cd.mips.stats__special2
394     [s2] > 0)
395     fatal("special2 %02x (%7s): "
396     "%li\n", s2,
397     special2_names[s2], m->
398     cpus[i]->cd.mips.
399     stats__special2[s2]);
400     debug_indentation(-iadd);
401     }
402    
403     debug_indentation(-iadd);
404     }
405     }
406    
407    
408     /*
409     * mips_cpu_tlbdump():
410     *
411     * Called from the debugger to dump the TLB in a readable format.
412     * x is the cpu number to dump, or -1 to dump all CPUs.
413     *
414     * If rawflag is nonzero, then the TLB contents isn't formated nicely,
415     * just dumped.
416     */
417     void mips_cpu_tlbdump(struct machine *m, int x, int rawflag)
418     {
419     int i, j;
420    
421     /* Nicely formatted output: */
422     if (!rawflag) {
423     for (i=0; i<m->ncpus; i++) {
424     int pageshift = 12;
425    
426     if (x >= 0 && i != x)
427     continue;
428    
429     if (m->cpus[i]->cd.mips.cpu_type.rev == MIPS_R4100)
430     pageshift = 10;
431    
432     /* Print index, random, and wired: */
433     printf("cpu%i: (", i);
434     switch (m->cpus[i]->cd.mips.cpu_type.isa_level) {
435     case 1:
436     case 2:
437     printf("index=0x%x random=0x%x",
438     (int) ((m->cpus[i]->cd.mips.coproc[0]->
439     reg[COP0_INDEX] & R2K3K_INDEX_MASK)
440     >> R2K3K_INDEX_SHIFT),
441     (int) ((m->cpus[i]->cd.mips.coproc[0]->
442     reg[COP0_RANDOM] & R2K3K_RANDOM_MASK)
443     >> R2K3K_RANDOM_SHIFT));
444     break;
445     default:
446     printf("index=0x%x random=0x%x",
447     (int) (m->cpus[i]->cd.mips.coproc[0]->
448     reg[COP0_INDEX] & INDEX_MASK),
449     (int) (m->cpus[i]->cd.mips.coproc[0]->
450     reg[COP0_RANDOM] & RANDOM_MASK));
451     printf(" wired=0x%llx", (long long)
452     m->cpus[i]->cd.mips.coproc[0]->
453     reg[COP0_WIRED]);
454     }
455    
456     printf(")\n");
457    
458     for (j=0; j<m->cpus[i]->cd.mips.cpu_type.
459     nr_of_tlb_entries; j++) {
460     uint64_t hi,lo0,lo1,mask;
461     hi = m->cpus[i]->cd.mips.coproc[0]->tlbs[j].hi;
462     lo0 = m->cpus[i]->cd.mips.coproc[0]->tlbs[j].lo0;
463     lo1 = m->cpus[i]->cd.mips.coproc[0]->tlbs[j].lo1;
464     mask = m->cpus[i]->cd.mips.coproc[0]->tlbs[j].mask;
465    
466     printf("%3i: ", j);
467     switch (m->cpus[i]->cd.mips.cpu_type.mmu_model) {
468     case MMU3K:
469     if (!(lo0 & R2K3K_ENTRYLO_V)) {
470     printf("(invalid)\n");
471     continue;
472     }
473     printf("vaddr=0x%08x ",
474     (int) (hi&R2K3K_ENTRYHI_VPN_MASK));
475     if (lo0 & R2K3K_ENTRYLO_G)
476     printf("(global), ");
477     else
478     printf("(asid %02x),",
479     (int) ((hi & R2K3K_ENTRYHI_ASID_MASK)
480     >> R2K3K_ENTRYHI_ASID_SHIFT));
481     printf(" paddr=0x%08x ",
482     (int) (lo0&R2K3K_ENTRYLO_PFN_MASK));
483     if (lo0 & R2K3K_ENTRYLO_N)
484     printf("N");
485     if (lo0 & R2K3K_ENTRYLO_D)
486     printf("D");
487     printf("\n");
488     break;
489     default:
490     switch (m->cpus[i]->cd.mips.cpu_type.mmu_model) {
491     case MMU10K:
492     printf("vaddr=0x%1x..%011llx ",
493     (int) (hi >> 60),
494     (long long) (hi&ENTRYHI_VPN2_MASK_R10K));
495     break;
496     case MMU32:
497     printf("vaddr=0x%08x ", (int)(hi&ENTRYHI_VPN2_MASK));
498     break;
499     default:/* R4000 etc. */
500     printf("vaddr=0x%1x..%010llx ",
501     (int) (hi >> 60),
502     (long long) (hi&ENTRYHI_VPN2_MASK));
503     }
504     if (hi & TLB_G)
505     printf("(global): ");
506     else
507     printf("(asid %02x):",
508     (int) (hi & ENTRYHI_ASID));
509    
510     /* TODO: Coherency bits */
511    
512     if (!(lo0 & ENTRYLO_V))
513     printf(" p0=(invalid) ");
514     else
515     printf(" p0=0x%09llx ", (long long)
516     (((lo0&ENTRYLO_PFN_MASK) >> ENTRYLO_PFN_SHIFT) << pageshift));
517     printf(lo0 & ENTRYLO_D? "D" : " ");
518    
519     if (!(lo1 & ENTRYLO_V))
520     printf(" p1=(invalid) ");
521     else
522     printf(" p1=0x%09llx ", (long long)
523     (((lo1&ENTRYLO_PFN_MASK) >> ENTRYLO_PFN_SHIFT) << pageshift));
524     printf(lo1 & ENTRYLO_D? "D" : " ");
525     mask |= (1 << (pageshift+1)) - 1;
526     switch (mask) {
527     case 0x7ff: printf(" (1KB)"); break;
528     case 0x1fff: printf(" (4KB)"); break;
529     case 0x7fff: printf(" (16KB)"); break;
530     case 0x1ffff: printf(" (64KB)"); break;
531     case 0x7ffff: printf(" (256KB)"); break;
532     case 0x1fffff: printf(" (1MB)"); break;
533     case 0x7fffff: printf(" (4MB)"); break;
534     case 0x1ffffff: printf(" (16MB)"); break;
535     case 0x7ffffff: printf(" (64MB)"); break;
536     default:
537     printf(" (mask=%08x?)", (int)mask);
538     }
539     printf("\n");
540     }
541     }
542     }
543    
544     return;
545     }
546    
547     /* Raw output: */
548     for (i=0; i<m->ncpus; i++) {
549     if (x >= 0 && i != x)
550     continue;
551    
552     /* Print index, random, and wired: */
553     printf("cpu%i: (", i);
554    
555     if (m->cpus[i]->is_32bit)
556     printf("index=0x%08x random=0x%08x",
557     (int)m->cpus[i]->cd.mips.coproc[0]->reg[COP0_INDEX],
558     (int)m->cpus[i]->cd.mips.coproc[0]->reg[COP0_RANDOM]);
559     else
560     printf("index=0x%016llx random=0x%016llx", (long long)
561     m->cpus[i]->cd.mips.coproc[0]->reg[COP0_INDEX],
562     (long long)m->cpus[i]->cd.mips.coproc[0]->reg
563     [COP0_RANDOM]);
564    
565     if (m->cpus[i]->cd.mips.cpu_type.isa_level >= 3)
566     printf(" wired=0x%llx", (long long)
567     m->cpus[i]->cd.mips.coproc[0]->reg[COP0_WIRED]);
568    
569     printf(")\n");
570    
571     for (j=0; j<m->cpus[i]->cd.mips.cpu_type.nr_of_tlb_entries; j++) {
572     if (m->cpus[i]->cd.mips.cpu_type.mmu_model == MMU3K)
573     printf("%3i: hi=0x%08x lo=0x%08x\n",
574     j,
575     (int)m->cpus[i]->cd.mips.coproc[0]->tlbs[j].hi,
576     (int)m->cpus[i]->cd.mips.coproc[0]->tlbs[j].lo0);
577     else if (m->cpus[i]->is_32bit)
578     printf("%3i: hi=0x%08x mask=0x%08x "
579     "lo0=0x%08x lo1=0x%08x\n", j,
580     (int)m->cpus[i]->cd.mips.coproc[0]->tlbs[j].hi,
581     (int)m->cpus[i]->cd.mips.coproc[0]->tlbs[j].mask,
582     (int)m->cpus[i]->cd.mips.coproc[0]->tlbs[j].lo0,
583     (int)m->cpus[i]->cd.mips.coproc[0]->tlbs[j].lo1);
584     else
585     printf("%3i: hi=0x%016llx mask=0x%016llx "
586     "lo0=0x%016llx lo1=0x%016llx\n", j,
587     (long long)m->cpus[i]->cd.mips.coproc[0]->tlbs[j].hi,
588     (long long)m->cpus[i]->cd.mips.coproc[0]->tlbs[j].mask,
589     (long long)m->cpus[i]->cd.mips.coproc[0]->tlbs[j].lo0,
590     (long long)m->cpus[i]->cd.mips.coproc[0]->tlbs[j].lo1);
591     }
592     }
593     }
594    
595    
596     /*
597     * mips_cpu_register_match():
598     */
599     void mips_cpu_register_match(struct machine *m, char *name,
600     int writeflag, uint64_t *valuep, int *match_register)
601     {
602     int cpunr = 0;
603    
604     /* CPU number: */
605    
606     /* TODO */
607    
608     /* Register name: */
609     if (strcasecmp(name, "pc") == 0) {
610     if (writeflag) {
611     m->cpus[cpunr]->pc = *valuep;
612     if (m->cpus[cpunr]->cd.mips.delay_slot) {
613     printf("NOTE: Clearing the delay slot"
614     " flag! (It was set before.)\n");
615     m->cpus[cpunr]->cd.mips.delay_slot = 0;
616     }
617     if (m->cpus[cpunr]->cd.mips.nullify_next) {
618     printf("NOTE: Clearing the nullify-ne"
619     "xt flag! (It was set before.)\n");
620     m->cpus[cpunr]->cd.mips.nullify_next = 0;
621     }
622     } else
623     *valuep = m->cpus[cpunr]->pc;
624     *match_register = 1;
625     } else if (strcasecmp(name, "hi") == 0) {
626     if (writeflag)
627     m->cpus[cpunr]->cd.mips.hi = *valuep;
628     else
629     *valuep = m->cpus[cpunr]->cd.mips.hi;
630     *match_register = 1;
631     } else if (strcasecmp(name, "lo") == 0) {
632     if (writeflag)
633     m->cpus[cpunr]->cd.mips.lo = *valuep;
634     else
635     *valuep = m->cpus[cpunr]->cd.mips.lo;
636     *match_register = 1;
637     } else if (name[0] == 'r' && isdigit((int)name[1])) {
638     int nr = atoi(name + 1);
639     if (nr >= 0 && nr < N_MIPS_GPRS) {
640     if (writeflag) {
641     if (nr != 0)
642     m->cpus[cpunr]->cd.mips.gpr[nr] = *valuep;
643     else
644     printf("WARNING: Attempt to modify r0.\n");
645     } else
646     *valuep = m->cpus[cpunr]->cd.mips.gpr[nr];
647     *match_register = 1;
648     }
649     } else {
650     /* Check for a symbolic name such as "t6" or "at": */
651     int nr;
652     for (nr=0; nr<N_MIPS_GPRS; nr++)
653     if (strcmp(name, regnames[nr]) == 0) {
654     if (writeflag) {
655     if (nr != 0)
656     m->cpus[cpunr]->cd.mips.gpr[nr] = *valuep;
657     else
658     printf("WARNING: Attempt to modify r0.\n");
659     } else
660     *valuep = m->cpus[cpunr]->cd.mips.gpr[nr];
661     *match_register = 1;
662     }
663     }
664    
665     if (!(*match_register)) {
666     /* Check for a symbolic coproc0 name: */
667     int nr;
668     for (nr=0; nr<32; nr++)
669     if (strcmp(name, cop0_names[nr]) == 0) {
670     if (writeflag) {
671     coproc_register_write(m->cpus[cpunr],
672     m->cpus[cpunr]->cd.mips.coproc[0], nr,
673     valuep, 1, 0);
674     } else {
675     /* TODO: Use coproc_register_read instead? */
676     *valuep = m->cpus[cpunr]->cd.mips.coproc[0]->reg[nr];
677     }
678     *match_register = 1;
679     }
680     }
681    
682     /* TODO: Coprocessor 1,2,3 registers. */
683     }
684    
685    
686     /*
687     * cpu_flags():
688     *
689     * Returns a pointer to a string containing "(d)" "(j)" "(dj)" or "",
690     * depending on the cpu's current delay_slot and last_was_jumptoself
691     * flags.
692     */
693     static const char *cpu_flags(struct cpu *cpu)
694     {
695     if (cpu->cd.mips.delay_slot) {
696     if (cpu->cd.mips.last_was_jumptoself)
697     return " (dj)";
698     else
699     return " (d)";
700     } else {
701     if (cpu->cd.mips.last_was_jumptoself)
702     return " (j)";
703     else
704     return "";
705     }
706     }
707    
708    
709     /*
710     * mips_cpu_disassemble_instr():
711     *
712     * Convert an instruction word into human readable format, for instruction
713     * tracing.
714     *
715     * If running is 1, cpu->pc should be the address of the instruction.
716     *
717     * If running is 0, things that depend on the runtime environment (eg.
718     * register contents) will not be shown, and addr will be used instead of
719     * cpu->pc for relative addresses.
720     *
721     * NOTE 2: coprocessor instructions are not decoded nicely yet (TODO)
722     */
723     int mips_cpu_disassemble_instr(struct cpu *cpu, unsigned char *originstr,
724     int running, uint64_t dumpaddr, int bintrans)
725     {
726     int hi6, special6, regimm5;
727     int rt, rd, rs, sa, imm, copz, cache_op, which_cache, showtag;
728     uint64_t addr, offset;
729     uint32_t instrword;
730     unsigned char instr[4];
731     char *symbol;
732    
733     if (running)
734     dumpaddr = cpu->pc;
735    
736     if ((dumpaddr & 3) != 0)
737     printf("WARNING: Unaligned address!\n");
738    
739     symbol = get_symbol_name(&cpu->machine->symbol_context,
740     dumpaddr, &offset);
741     if (symbol != NULL && offset==0)
742     debug("<%s>\n", symbol);
743    
744     if (cpu->machine->ncpus > 1 && running)
745     debug("cpu%i: ", cpu->cpu_id);
746    
747     if (cpu->is_32bit)
748     debug("%08x", (int)dumpaddr);
749     else
750     debug("%016llx", (long long)dumpaddr);
751    
752     *((uint32_t *)&instr[0]) = *((uint32_t *)&originstr[0]);
753    
754     /*
755     * The rest of the code is written for little endian,
756     * so swap if necessary:
757     */
758     if (cpu->byte_order == EMUL_BIG_ENDIAN) {
759     int tmp = instr[0]; instr[0] = instr[3];
760     instr[3] = tmp;
761     tmp = instr[1]; instr[1] = instr[2];
762     instr[2] = tmp;
763     }
764    
765     debug(": %02x%02x%02x%02x",
766     instr[3], instr[2], instr[1], instr[0]);
767    
768     if (running)
769     debug("%s", cpu_flags(cpu));
770    
771     debug("\t");
772    
773     if (bintrans && running) {
774     debug("(bintrans)");
775     goto disasm_ret;
776     }
777    
778     /*
779     * Decode the instruction:
780     */
781    
782     if (cpu->cd.mips.nullify_next && running) {
783     debug("(nullified)");
784     goto disasm_ret;
785     }
786    
787     hi6 = (instr[3] >> 2) & 0x3f;
788    
789     switch (hi6) {
790     case HI6_SPECIAL:
791     special6 = instr[0] & 0x3f;
792     switch (special6) {
793     case SPECIAL_SLL:
794     case SPECIAL_SRL:
795     case SPECIAL_SRA:
796     case SPECIAL_DSLL:
797     case SPECIAL_DSRL:
798     case SPECIAL_DSRA:
799     case SPECIAL_DSLL32:
800     case SPECIAL_DSRL32:
801     case SPECIAL_DSRA32:
802     rt = instr[2] & 31;
803     rd = (instr[1] >> 3) & 31;
804     sa = ((instr[1] & 7) << 2) + ((instr[0] >> 6) & 3);
805    
806     if (rd == 0 && special6 == SPECIAL_SLL) {
807     if (sa == 0)
808     debug("nop");
809     else if (sa == 1)
810     debug("ssnop");
811     else
812     debug("nop (weird, sa=%i)", sa);
813     goto disasm_ret;
814     } else
815     debug("%s\t%s,",
816     special_names[special6],
817     regname(cpu->machine, rd));
818     debug("%s,%i", regname(cpu->machine, rt), sa);
819     break;
820     case SPECIAL_DSRLV:
821     case SPECIAL_DSRAV:
822     case SPECIAL_DSLLV:
823     case SPECIAL_SLLV:
824     case SPECIAL_SRAV:
825     case SPECIAL_SRLV:
826     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
827     rt = instr[2] & 31;
828     rd = (instr[1] >> 3) & 31;
829     debug("%s\t%s",
830     special_names[special6], regname(cpu->machine, rd));
831     debug(",%s", regname(cpu->machine, rt));
832     debug(",%s", regname(cpu->machine, rs));
833     break;
834     case SPECIAL_JR:
835     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
836     symbol = get_symbol_name(&cpu->machine->symbol_context,
837     cpu->cd.mips.gpr[rs], &offset);
838     debug("jr\t%s", regname(cpu->machine, rs));
839     if (running && symbol != NULL)
840     debug("\t<%s>", symbol);
841     break;
842     case SPECIAL_JALR:
843     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
844     rd = (instr[1] >> 3) & 31;
845     symbol = get_symbol_name(&cpu->machine->symbol_context,
846     cpu->cd.mips.gpr[rs], &offset);
847     debug("jalr\t%s", regname(cpu->machine, rd));
848     debug(",%s", regname(cpu->machine, rs));
849     if (running && symbol != NULL)
850     debug("\t<%s>", symbol);
851     break;
852     case SPECIAL_MFHI:
853     case SPECIAL_MFLO:
854     rd = (instr[1] >> 3) & 31;
855     debug("%s\t%s", special_names[special6],
856     regname(cpu->machine, rd));
857     break;
858     case SPECIAL_MTLO:
859     case SPECIAL_MTHI:
860     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
861     debug("%s\t%s", special_names[special6],
862     regname(cpu->machine, rs));
863     break;
864     case SPECIAL_ADD:
865     case SPECIAL_ADDU:
866     case SPECIAL_SUB:
867     case SPECIAL_SUBU:
868     case SPECIAL_AND:
869     case SPECIAL_OR:
870     case SPECIAL_XOR:
871     case SPECIAL_NOR:
872     case SPECIAL_SLT:
873     case SPECIAL_SLTU:
874     case SPECIAL_DADD:
875     case SPECIAL_DADDU:
876     case SPECIAL_DSUB:
877     case SPECIAL_DSUBU:
878     case SPECIAL_MOVZ:
879     case SPECIAL_MOVN:
880     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
881     rt = instr[2] & 31;
882     rd = (instr[1] >> 3) & 31;
883     if ((special6 == SPECIAL_ADDU ||
884     special6 == SPECIAL_DADDU ||
885     special6 == SPECIAL_SUBU ||
886     special6 == SPECIAL_DSUBU) && rt == 0) {
887     /* Special case 1: addu/daddu/subu/dsubu with
888     rt = the zero register ==> move */
889     debug("move\t%s", regname(cpu->machine, rd));
890     debug(",%s", regname(cpu->machine, rs));
891     } else if ((special6 == SPECIAL_ADDU ||
892     special6 == SPECIAL_DADDU) && rs == 0) {
893     /* Special case 2: addu/daddu with
894     rs = the zero register ==> move */
895     debug("move\t%s", regname(cpu->machine, rd));
896     debug(",%s", regname(cpu->machine, rt));
897     } else {
898     debug("%s\t%s", special_names[special6],
899     regname(cpu->machine, rd));
900     debug(",%s", regname(cpu->machine, rs));
901     debug(",%s", regname(cpu->machine, rt));
902     }
903     break;
904     case SPECIAL_MULT:
905     case SPECIAL_MULTU:
906     case SPECIAL_DMULT:
907     case SPECIAL_DMULTU:
908     case SPECIAL_DIV:
909     case SPECIAL_DIVU:
910     case SPECIAL_DDIV:
911     case SPECIAL_DDIVU:
912     case SPECIAL_TGE:
913     case SPECIAL_TGEU:
914     case SPECIAL_TLT:
915     case SPECIAL_TLTU:
916     case SPECIAL_TEQ:
917     case SPECIAL_TNE:
918     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
919     rt = instr[2] & 31;
920     rd = (instr[1] >> 3) & 31;
921     if (special6 == SPECIAL_MULT) {
922     if (rd != 0) {
923     debug("mult_xx\t%s",
924     regname(cpu->machine, rd));
925     debug(",%s", regname(cpu->machine, rs));
926     debug(",%s", regname(cpu->machine, rt));
927     goto disasm_ret;
928     }
929     }
930     debug("%s\t%s", special_names[special6],
931     regname(cpu->machine, rs));
932     debug(",%s", regname(cpu->machine, rt));
933     break;
934     case SPECIAL_SYNC:
935     imm = ((instr[1] & 7) << 2) + (instr[0] >> 6);
936     debug("sync\t0x%02x", imm);
937     break;
938     case SPECIAL_SYSCALL:
939     imm = (((instr[3] << 24) + (instr[2] << 16) +
940     (instr[1] << 8) + instr[0]) >> 6) & 0xfffff;
941     if (imm != 0)
942     debug("syscall\t0x%05x", imm);
943     else
944     debug("syscall");
945     break;
946     case SPECIAL_BREAK:
947     imm = (((instr[3] << 24) + (instr[2] << 16) +
948     (instr[1] << 8) + instr[0]) >> 6) & 0xfffff;
949     if (imm != 0)
950     debug("break\t0x%05x", imm);
951     else
952     debug("break");
953     break;
954     case SPECIAL_MFSA:
955     rd = (instr[1] >> 3) & 31;
956     debug("mfsa\t%s", regname(cpu->machine, rd));
957     break;
958     case SPECIAL_MTSA:
959     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
960     debug("mtsa\t%s", regname(cpu->machine, rs));
961     break;
962     default:
963     debug("unimplemented special6 = 0x%02x", special6);
964     }
965     break;
966     case HI6_BEQ:
967     case HI6_BEQL:
968     case HI6_BNE:
969     case HI6_BNEL:
970     case HI6_BGTZ:
971     case HI6_BGTZL:
972     case HI6_BLEZ:
973     case HI6_BLEZL:
974     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
975     rt = instr[2] & 31;
976     imm = (instr[1] << 8) + instr[0];
977     if (imm >= 32768)
978     imm -= 65536;
979     addr = (dumpaddr + 4) + (imm << 2);
980     debug("%s\t", hi6_names[hi6]);
981    
982     switch (hi6) {
983     case HI6_BEQ:
984     case HI6_BEQL:
985     case HI6_BNE:
986     case HI6_BNEL:
987     debug("%s,", regname(cpu->machine, rt));
988     }
989    
990     debug("%s,", regname(cpu->machine, rs));
991    
992     if (cpu->is_32bit)
993     debug("0x%08x", (int)addr);
994     else
995     debug("0x%016llx", (long long)addr);
996    
997     symbol = get_symbol_name(&cpu->machine->symbol_context,
998     addr, &offset);
999     if (symbol != NULL && offset != addr)
1000     debug("\t<%s>", symbol);
1001     break;
1002     case HI6_ADDI:
1003     case HI6_ADDIU:
1004     case HI6_DADDI:
1005     case HI6_DADDIU:
1006     case HI6_SLTI:
1007     case HI6_SLTIU:
1008     case HI6_ANDI:
1009     case HI6_ORI:
1010     case HI6_XORI:
1011     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
1012     rt = instr[2] & 31;
1013     imm = (instr[1] << 8) + instr[0];
1014     if (imm >= 32768)
1015     imm -= 65536;
1016     debug("%s\t%s,", hi6_names[hi6], regname(cpu->machine, rt));
1017     debug("%s,", regname(cpu->machine, rs));
1018     if (hi6 == HI6_ANDI || hi6 == HI6_ORI || hi6 == HI6_XORI)
1019     debug("0x%04x", imm & 0xffff);
1020     else
1021     debug("%i", imm);
1022     break;
1023     case HI6_LUI:
1024     rt = instr[2] & 31;
1025     imm = (instr[1] << 8) + instr[0];
1026     debug("lui\t%s,0x%x", regname(cpu->machine, rt), imm);
1027     break;
1028     case HI6_LB:
1029     case HI6_LBU:
1030     case HI6_LH:
1031     case HI6_LHU:
1032     case HI6_LW:
1033     case HI6_LWU:
1034     case HI6_LD:
1035     case HI6_LQ_MDMX:
1036     case HI6_LWC1:
1037     case HI6_LWC2:
1038     case HI6_LWC3:
1039     case HI6_LDC1:
1040     case HI6_LDC2:
1041     case HI6_LL:
1042     case HI6_LLD:
1043     case HI6_SB:
1044     case HI6_SH:
1045     case HI6_SW:
1046     case HI6_SD:
1047     case HI6_SQ:
1048     case HI6_SC:
1049     case HI6_SCD:
1050     case HI6_SWC1:
1051     case HI6_SWC2:
1052     case HI6_SWC3:
1053     case HI6_SDC1:
1054     case HI6_SDC2:
1055     case HI6_LWL:
1056     case HI6_LWR:
1057     case HI6_LDL:
1058     case HI6_LDR:
1059     case HI6_SWL:
1060     case HI6_SWR:
1061     case HI6_SDL:
1062     case HI6_SDR:
1063     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
1064     rt = instr[2] & 31;
1065     imm = (instr[1] << 8) + instr[0];
1066     if (imm >= 32768)
1067     imm -= 65536;
1068     symbol = get_symbol_name(&cpu->machine->symbol_context,
1069     cpu->cd.mips.gpr[rs] + imm, &offset);
1070    
1071     /* LWC3 is PREF in the newer ISA levels: */
1072     /* TODO: Which ISAs? IV? V? 32? 64? */
1073     if (cpu->cd.mips.cpu_type.isa_level >= 4 && hi6 == HI6_LWC3) {
1074     debug("pref\t0x%x,%i(%s)",
1075     rt, imm, regname(cpu->machine, rs));
1076    
1077     if (running) {
1078     debug("\t[0x%016llx = %s]",
1079     (long long)(cpu->cd.mips.gpr[rs] + imm));
1080     if (symbol != NULL)
1081     debug(" = %s", symbol);
1082     debug("]");
1083     }
1084     goto disasm_ret;
1085     }
1086    
1087     debug("%s\t", hi6_names[hi6]);
1088    
1089     if (hi6 == HI6_SWC1 || hi6 == HI6_SWC2 || hi6 == HI6_SWC3 ||
1090     hi6 == HI6_SDC1 || hi6 == HI6_SDC2 ||
1091     hi6 == HI6_LWC1 || hi6 == HI6_LWC2 || hi6 == HI6_LWC3 ||
1092     hi6 == HI6_LDC1 || hi6 == HI6_LDC2)
1093     debug("r%i", rt);
1094     else
1095     debug("%s", regname(cpu->machine, rt));
1096    
1097     debug(",%i(%s)", imm, regname(cpu->machine, rs));
1098    
1099     if (running) {
1100     debug("\t[");
1101    
1102     if (cpu->is_32bit)
1103     debug("0x%08x", (int)(cpu->cd.mips.gpr[rs] + imm));
1104     else
1105     debug("0x%016llx",
1106     (long long)(cpu->cd.mips.gpr[rs] + imm));
1107    
1108     if (symbol != NULL)
1109     debug(" = %s", symbol);
1110    
1111     debug(", data=");
1112     } else
1113     break;
1114     /* NOTE: No break here (if we are running) as it is up
1115     to the caller to print 'data'. */
1116     return sizeof(instrword);
1117     case HI6_J:
1118     case HI6_JAL:
1119     imm = (((instr[3] & 3) << 24) + (instr[2] << 16) +
1120     (instr[1] << 8) + instr[0]) << 2;
1121     addr = (dumpaddr + 4) & ~((1 << 28) - 1);
1122     addr |= imm;
1123     symbol = get_symbol_name(&cpu->machine->symbol_context,
1124     addr, &offset);
1125     debug("%s\t0x", hi6_names[hi6]);
1126     if (cpu->is_32bit)
1127     debug("%08x", (int)addr);
1128     else
1129     debug("%016llx", (long long)addr);
1130     if (symbol != NULL)
1131     debug("\t<%s>", symbol);
1132     break;
1133     case HI6_COP0:
1134     case HI6_COP1:
1135     case HI6_COP2:
1136     case HI6_COP3:
1137     imm = (instr[3] << 24) + (instr[2] << 16) +
1138     (instr[1] << 8) + instr[0];
1139     imm &= ((1 << 26) - 1);
1140    
1141     /* Call coproc_function(), but ONLY disassembly, no exec: */
1142     coproc_function(cpu, cpu->cd.mips.coproc[hi6 - HI6_COP0],
1143     hi6 - HI6_COP0, imm, 1, running);
1144     return sizeof(instrword);
1145     case HI6_CACHE:
1146     rt = ((instr[3] & 3) << 3) + (instr[2] >> 5); /* base */
1147     copz = instr[2] & 31;
1148     imm = (instr[1] << 8) + instr[0];
1149     cache_op = copz >> 2;
1150     which_cache = copz & 3;
1151     showtag = 0;
1152     debug("cache\t0x%02x,0x%04x(%s)", copz, imm,
1153     regname(cpu->machine, rt));
1154     if (which_cache==0) debug(" [ primary I-cache");
1155     if (which_cache==1) debug(" [ primary D-cache");
1156     if (which_cache==2) debug(" [ secondary I-cache");
1157     if (which_cache==3) debug(" [ secondary D-cache");
1158     debug(", ");
1159     if (cache_op==0) debug("index invalidate");
1160     if (cache_op==1) debug("index load tag");
1161     if (cache_op==2) debug("index store tag"), showtag=1;
1162     if (cache_op==3) debug("create dirty exclusive");
1163     if (cache_op==4) debug("hit invalidate");
1164     if (cache_op==5) debug("fill OR hit writeback invalidate");
1165     if (cache_op==6) debug("hit writeback");
1166     if (cache_op==7) debug("hit set virtual");
1167     if (running)
1168     debug(", addr 0x%016llx",
1169     (long long)(cpu->cd.mips.gpr[rt] + imm));
1170     if (showtag)
1171     debug(", taghi=%08lx lo=%08lx",
1172     (long)cpu->cd.mips.coproc[0]->reg[COP0_TAGDATA_HI],
1173     (long)cpu->cd.mips.coproc[0]->reg[COP0_TAGDATA_LO]);
1174     debug(" ]");
1175     break;
1176     case HI6_SPECIAL2:
1177     special6 = instr[0] & 0x3f;
1178     instrword = (instr[3] << 24) + (instr[2] << 16) +
1179     (instr[1] << 8) + instr[0];
1180     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
1181     rt = instr[2] & 31;
1182     rd = (instr[1] >> 3) & 31;
1183     if ((instrword & 0xfc0007ffULL) == 0x70000000) {
1184     debug("madd\t%s", regname(cpu->machine, rd));
1185     debug(",%s", regname(cpu->machine, rs));
1186     debug(",%s", regname(cpu->machine, rt));
1187     } else if (special6 == SPECIAL2_MUL) {
1188     /* TODO: this is just a guess, I don't have the
1189     docs in front of me */
1190     debug("mul\t%s", regname(cpu->machine, rd));
1191     debug(",%s", regname(cpu->machine, rs));
1192     debug(",%s", regname(cpu->machine, rt));
1193     } else if (special6 == SPECIAL2_CLZ) {
1194     debug("clz\t%s", regname(cpu->machine, rd));
1195     debug(",%s", regname(cpu->machine, rs));
1196     } else if (special6 == SPECIAL2_CLO) {
1197     debug("clo\t%s", regname(cpu->machine, rd));
1198     debug(",%s", regname(cpu->machine, rs));
1199     } else if (special6 == SPECIAL2_DCLZ) {
1200     debug("dclz\t%s", regname(cpu->machine, rd));
1201     debug(",%s", regname(cpu->machine, rs));
1202     } else if (special6 == SPECIAL2_DCLO) {
1203     debug("dclo\t%s", regname(cpu->machine, rd));
1204     debug(",%s", regname(cpu->machine, rs));
1205     } else if ((instrword & 0xffff07ffULL) == 0x70000209
1206     || (instrword & 0xffff07ffULL) == 0x70000249) {
1207     if (instr[0] == 0x49) {
1208     debug("pmflo\t%s", regname(cpu->machine, rd));
1209     debug(" (rs=%s)", regname(cpu->machine, rs));
1210     } else {
1211     debug("pmfhi\t%s", regname(cpu->machine, rd));
1212     debug(" (rs=%s)", regname(cpu->machine, rs));
1213     }
1214     } else if ((instrword & 0xfc1fffff) == 0x70000269
1215     || (instrword & 0xfc1fffff) == 0x70000229) {
1216     if (instr[0] == 0x69) {
1217     debug("pmtlo\t%s", regname(cpu->machine, rs));
1218     } else {
1219     debug("pmthi\t%s", regname(cpu->machine, rs));
1220     }
1221     } else if ((instrword & 0xfc0007ff) == 0x700004a9) {
1222     debug("por\t%s", regname(cpu->machine, rd));
1223     debug(",%s", regname(cpu->machine, rs));
1224     debug(",%s", regname(cpu->machine, rt));
1225     } else if ((instrword & 0xfc0007ff) == 0x70000488) {
1226     debug("pextlw\t%s", regname(cpu->machine, rd));
1227     debug(",%s", regname(cpu->machine, rs));
1228     debug(",%s", regname(cpu->machine, rt));
1229     } else {
1230     debug("unimplemented special2 = 0x%02x", special6);
1231     }
1232     break;
1233     case HI6_REGIMM:
1234     regimm5 = instr[2] & 0x1f;
1235     switch (regimm5) {
1236     case REGIMM_BLTZ:
1237     case REGIMM_BGEZ:
1238     case REGIMM_BLTZL:
1239     case REGIMM_BGEZL:
1240     case REGIMM_BLTZAL:
1241     case REGIMM_BLTZALL:
1242     case REGIMM_BGEZAL:
1243     case REGIMM_BGEZALL:
1244     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
1245     imm = (instr[1] << 8) + instr[0];
1246     if (imm >= 32768)
1247     imm -= 65536;
1248    
1249     debug("%s\t%s,", regimm_names[regimm5],
1250     regname(cpu->machine, rs));
1251    
1252     addr = (dumpaddr + 4) + (imm << 2);
1253    
1254     if (cpu->is_32bit)
1255     debug("0x%08x", (int)addr);
1256     else
1257     debug("0x%016llx", (long long)addr);
1258     break;
1259     default:
1260     debug("unimplemented regimm5 = 0x%02x", regimm5);
1261     }
1262     break;
1263     default:
1264     debug("unimplemented hi6 = 0x%02x", hi6);
1265     }
1266    
1267     disasm_ret:
1268     debug("\n");
1269     return sizeof(instrword);
1270     }
1271    
1272    
1273     /*
1274     * mips_cpu_register_dump():
1275     *
1276     * Dump cpu registers in a relatively readable format.
1277     *
1278     * gprs: set to non-zero to dump GPRs and hi/lo/pc
1279     * coprocs: set bit 0..3 to dump registers in coproc 0..3.
1280     */
1281     void mips_cpu_register_dump(struct cpu *cpu, int gprs, int coprocs)
1282     {
1283     int coprocnr, i, bits32;
1284     uint64_t offset;
1285     char *symbol;
1286    
1287     bits32 = cpu->is_32bit;
1288    
1289     if (gprs) {
1290     /* Special registers (pc, hi/lo) first: */
1291     symbol = get_symbol_name(&cpu->machine->symbol_context,
1292     cpu->pc, &offset);
1293    
1294     if (bits32)
1295     debug("cpu%i: pc = %08x", cpu->cpu_id, (int)cpu->pc);
1296     else
1297     debug("cpu%i: pc = 0x%016llx",
1298     cpu->cpu_id, (long long)cpu->pc);
1299    
1300     debug(" <%s>\n", symbol != NULL? symbol :
1301     " no symbol ");
1302    
1303     if (bits32)
1304     debug("cpu%i: hi = %08x lo = %08x\n",
1305     cpu->cpu_id, (int)cpu->cd.mips.hi, (int)cpu->cd.mips.lo);
1306     else
1307     debug("cpu%i: hi = 0x%016llx lo = 0x%016llx\n",
1308     cpu->cpu_id, (long long)cpu->cd.mips.hi,
1309     (long long)cpu->cd.mips.lo);
1310    
1311     /* General registers: */
1312     if (cpu->cd.mips.cpu_type.rev == MIPS_R5900) {
1313     /* 128-bit: */
1314     for (i=0; i<32; i++) {
1315     if ((i & 1) == 0)
1316     debug("cpu%i:", cpu->cpu_id);
1317     debug(" %3s=%016llx%016llx",
1318     regname(cpu->machine, i),
1319     (long long)cpu->cd.mips.gpr_quadhi[i],
1320     (long long)cpu->cd.mips.gpr[i]);
1321     if ((i & 1) == 1)
1322     debug("\n");
1323     }
1324     } else if (bits32) {
1325     /* 32-bit: */
1326     for (i=0; i<32; i++) {
1327     if ((i & 3) == 0)
1328     debug("cpu%i:", cpu->cpu_id);
1329     if (i == MIPS_GPR_ZERO)
1330     debug(" ");
1331     else
1332     debug(" %3s = %08x", regname(cpu->machine, i), (int)cpu->cd.mips.gpr[i]);
1333     if ((i & 3) == 3)
1334     debug("\n");
1335     }
1336     } else {
1337     /* 64-bit: */
1338     for (i=0; i<32; i++) {
1339     int r = (i >> 1) + ((i & 1) << 4);
1340     if ((i & 1) == 0)
1341     debug("cpu%i:", cpu->cpu_id);
1342     if (r == MIPS_GPR_ZERO)
1343     debug(" ");
1344     else
1345     debug(" %3s = 0x%016llx", regname(cpu->machine, r), (long long)cpu->cd.mips.gpr[r]);
1346     if ((i & 1) == 1)
1347     debug("\n");
1348     }
1349     }
1350     }
1351    
1352     for (coprocnr=0; coprocnr<4; coprocnr++) {
1353     int nm1 = 1;
1354    
1355     if (bits32)
1356     nm1 = 3;
1357    
1358     if (!(coprocs & (1<<coprocnr)))
1359     continue;
1360     if (cpu->cd.mips.coproc[coprocnr] == NULL) {
1361     debug("cpu%i: no coprocessor %i\n",
1362     cpu->cpu_id, coprocnr);
1363     continue;
1364     }
1365    
1366     /* Coprocessor registers: */
1367     /* TODO: multiple selections per register? */
1368     for (i=0; i<32; i++) {
1369     /* 32-bit: */
1370     if ((i & nm1) == 0)
1371     debug("cpu%i:", cpu->cpu_id);
1372    
1373     if (cpu->machine->show_symbolic_register_names &&
1374     coprocnr == 0)
1375     debug(" %8s", cop0_names[i]);
1376     else
1377     debug(" c%i,%02i", coprocnr, i);
1378    
1379     if (bits32)
1380     debug("=%08x", (int)cpu->cd.mips.coproc[coprocnr]->reg[i]);
1381     else {
1382     if (coprocnr == 0 && (i == COP0_COUNT
1383     || i == COP0_COMPARE || i == COP0_INDEX
1384     || i == COP0_RANDOM || i == COP0_WIRED))
1385     debug(" = 0x%08x", (int)cpu->cd.mips.coproc[coprocnr]->reg[i]);
1386     else
1387     debug(" = 0x%016llx", (long long)
1388     cpu->cd.mips.coproc[coprocnr]->reg[i]);
1389     }
1390    
1391     if ((i & nm1) == nm1)
1392     debug("\n");
1393    
1394     /* Skip the last 16 cop0 registers on R3000 etc. */
1395     if (coprocnr == 0 && cpu->cd.mips.cpu_type.isa_level < 3
1396     && i == 15)
1397     i = 31;
1398     }
1399    
1400     if (coprocnr == 0 && cpu->cd.mips.cpu_type.isa_level >= 32) {
1401     debug("cpu%i: ", cpu->cpu_id);
1402     debug("config_select1 = 0x");
1403     if (cpu->is_32bit)
1404     debug("%08x", (int)cpu->cd.mips.cop0_config_select1);
1405     else
1406     debug("%016llx", (long long)cpu->cd.mips.cop0_config_select1);
1407     debug("\n");
1408     }
1409    
1410     /* Floating point control registers: */
1411     if (coprocnr == 1) {
1412     for (i=0; i<32; i++)
1413     switch (i) {
1414     case 0: printf("cpu%i: fcr0 (fcir) = 0x%08x\n",
1415     cpu->cpu_id, (int)cpu->cd.mips.coproc[coprocnr]->fcr[i]);
1416     break;
1417     case 25:printf("cpu%i: fcr25 (fccr) = 0x%08x\n",
1418     cpu->cpu_id, (int)cpu->cd.mips.coproc[coprocnr]->fcr[i]);
1419     break;
1420     case 31:printf("cpu%i: fcr31 (fcsr) = 0x%08x\n",
1421     cpu->cpu_id, (int)cpu->cd.mips.coproc[coprocnr]->fcr[i]);
1422     break;
1423     }
1424     }
1425     }
1426     }
1427    
1428    
1429     #define DYNTRANS_FUNCTION_TRACE mips_cpu_functioncall_trace
1430     #define DYNTRANS_MIPS
1431     #define DYNTRANS_ARCH mips
1432     #include "cpu_dyntrans.c"
1433     #undef DYNTRANS_MIPS
1434     #undef DYNTRANS_ARCH
1435     #undef DYNTRANS_FUNCTION_TRACE
1436    
1437    
1438     /*
1439     * mips_cpu_interrupt():
1440     *
1441     * Cause an interrupt. If irq_nr is 2..7, then it is a MIPS hardware
1442     * interrupt. 0 and 1 are ignored (software interrupts).
1443     *
1444     * If irq_nr is >= 8, then this function calls md_interrupt().
1445     */
1446     int mips_cpu_interrupt(struct cpu *cpu, uint64_t irq_nr)
1447     {
1448     if (irq_nr >= 8) {
1449     if (cpu->machine->md_interrupt != NULL)
1450     cpu->machine->md_interrupt(cpu->machine, cpu, irq_nr, 1);
1451     else
1452     fatal("mips_cpu_interrupt(): irq_nr = %i, but md_interrupt = NULL ?\n", irq_nr);
1453     return 1;
1454     }
1455    
1456     if (irq_nr < 2)
1457     return 0;
1458    
1459     cpu->cd.mips.coproc[0]->reg[COP0_CAUSE] |= ((1 << irq_nr) << STATUS_IM_SHIFT);
1460     cpu->cd.mips.cached_interrupt_is_possible = 1;
1461     return 1;
1462     }
1463    
1464    
1465     /*
1466     * mips_cpu_interrupt_ack():
1467     *
1468     * Acknowledge an interrupt. If irq_nr is 2..7, then it is a MIPS hardware
1469     * interrupt. Interrupts 0..1 are ignored (software interrupts).
1470     *
1471     * If irq_nr is >= 8, then it is machine dependant, and md_interrupt() is
1472     * called.
1473     */
1474     int mips_cpu_interrupt_ack(struct cpu *cpu, uint64_t irq_nr)
1475     {
1476     if (irq_nr >= 8) {
1477     if (cpu->machine->md_interrupt != NULL)
1478     cpu->machine->md_interrupt(cpu->machine, cpu, irq_nr, 0);
1479     else
1480     fatal("mips_cpu_interrupt_ack(): irq_nr = %i, but md_interrupt = NULL ?\n", irq_nr);
1481     return 1;
1482     }
1483    
1484     if (irq_nr < 2)
1485     return 0;
1486    
1487     cpu->cd.mips.coproc[0]->reg[COP0_CAUSE] &= ~((1 << irq_nr) << STATUS_IM_SHIFT);
1488     if (!(cpu->cd.mips.coproc[0]->reg[COP0_CAUSE] & STATUS_IM_MASK))
1489     cpu->cd.mips.cached_interrupt_is_possible = 0;
1490    
1491     return 1;
1492     }
1493    
1494    
1495     /*
1496     * mips_cpu_exception():
1497     *
1498     * Cause an exception in a CPU. This sets a couple of coprocessor 0
1499     * registers, and the program counter.
1500     *
1501     * exccode the exception code
1502     * tlb set to non-zero if the exception handler at
1503     * 0x80000000 should be used. (normal = 0x80000180)
1504     * vaddr virtual address (for some exceptions)
1505     * coproc_nr coprocessor number (for some exceptions)
1506     * vaddr_vpn2 vpn2 (for some exceptions)
1507     * vaddr_asid asid (for some exceptions)
1508     * x_64 non-zero for 64-bit mode for R4000-style tlb misses
1509     */
1510     void mips_cpu_exception(struct cpu *cpu, int exccode, int tlb, uint64_t vaddr,
1511     int coproc_nr, uint64_t vaddr_vpn2, int vaddr_asid, int x_64)
1512     {
1513     uint64_t base;
1514     uint64_t *reg = &cpu->cd.mips.coproc[0]->reg[0];
1515     int exc_model = cpu->cd.mips.cpu_type.exc_model;
1516    
1517     if (!quiet_mode) {
1518     uint64_t offset;
1519     int x;
1520     char *symbol = get_symbol_name(&cpu->machine->symbol_context,
1521     cpu->cd.mips.pc_last, &offset);
1522    
1523     debug("[ ");
1524     if (cpu->machine->ncpus > 1)
1525     debug("cpu%i: ", cpu->cpu_id);
1526    
1527     debug("exception %s%s",
1528     exception_names[exccode], tlb? " <tlb>" : "");
1529    
1530     switch (exccode) {
1531     case EXCEPTION_INT:
1532     debug(" cause_im=0x%02x", (int)((reg[COP0_CAUSE] & CAUSE_IP_MASK) >> CAUSE_IP_SHIFT));
1533     break;
1534     case EXCEPTION_SYS:
1535     debug(" v0=%i", (int)cpu->cd.mips.gpr[MIPS_GPR_V0]);
1536     for (x=0; x<4; x++) {
1537     int64_t d = cpu->cd.mips.gpr[MIPS_GPR_A0 + x];
1538     char strbuf[30];
1539    
1540     if (d > -256 && d < 256)
1541     debug(" a%i=%i", x, (int)d);
1542     else if (memory_points_to_string(cpu, cpu->mem, d, 1))
1543     debug(" a%i=\"%s\"", x, memory_conv_to_string(cpu, cpu->mem, d, strbuf, sizeof(strbuf)));
1544     else
1545     debug(" a%i=0x%llx", x, (long long)d);
1546     }
1547     break;
1548     default:
1549     if (cpu->is_32bit)
1550     debug(" vaddr=0x%08x", (int)vaddr);
1551     else
1552     debug(" vaddr=0x%016llx", (long long)vaddr);
1553     }
1554    
1555     if (cpu->is_32bit)
1556     debug(" pc=0x%08x ", (int)cpu->cd.mips.pc_last);
1557     else
1558     debug(" pc=0x%016llx ", (long long)cpu->cd.mips.pc_last);
1559    
1560     if (symbol != NULL)
1561     debug("<%s> ]\n", symbol);
1562     else
1563     debug("]\n");
1564     }
1565    
1566     if (tlb && vaddr < 0x1000) {
1567     uint64_t offset;
1568     char *symbol = get_symbol_name(&cpu->machine->symbol_context,
1569     cpu->cd.mips.pc_last, &offset);
1570     fatal("[ ");
1571     if (cpu->machine->ncpus > 1)
1572     fatal("cpu%i: ", cpu->cpu_id);
1573     fatal("warning: LOW reference: vaddr=");
1574     if (cpu->is_32bit)
1575     fatal("0x%08x", (int)vaddr);
1576     else
1577     fatal("0x%016llx", (long long)vaddr);
1578     fatal(", exception %s, pc=", exception_names[exccode]);
1579     if (cpu->is_32bit)
1580     fatal("0x%08x", (int)cpu->cd.mips.pc_last);
1581     else
1582     fatal("0x%016llx", (long long)cpu->cd.mips.pc_last);
1583     fatal(" <%s> ]\n", symbol? symbol : "(no symbol)");
1584    
1585     #ifdef TRACE_NULL_CRASHES
1586     /* This can be useful for debugging kernel bugs: */
1587     {
1588     int i = cpu->trace_null_index;
1589     do {
1590     fatal("TRACE: 0x%016llx\n",
1591     cpu->trace_null_addr[i]);
1592     i ++;
1593     i %= TRACE_NULL_N_ENTRIES;
1594     } while (i != cpu->trace_null_index);
1595     }
1596     cpu->running = 0;
1597     cpu->dead = 1;
1598     #endif
1599     }
1600    
1601     /* Clear the exception code bits of the cause register... */
1602     if (exc_model == EXC3K)
1603     reg[COP0_CAUSE] &= ~R2K3K_CAUSE_EXCCODE_MASK;
1604     else
1605     reg[COP0_CAUSE] &= ~CAUSE_EXCCODE_MASK;
1606    
1607     /* ... and OR in the exception code: */
1608     reg[COP0_CAUSE] |= (exccode << CAUSE_EXCCODE_SHIFT);
1609    
1610     /* Always set CE (according to the R5000 manual): */
1611     reg[COP0_CAUSE] &= ~CAUSE_CE_MASK;
1612     reg[COP0_CAUSE] |= (coproc_nr << CAUSE_CE_SHIFT);
1613    
1614     if (tlb || (exccode >= EXCEPTION_MOD && exccode <= EXCEPTION_ADES) ||
1615     exccode == EXCEPTION_VCEI || exccode == EXCEPTION_VCED) {
1616     reg[COP0_BADVADDR] = vaddr;
1617     #if 1
1618     /* TODO: This should be removed. */
1619     /* sign-extend vaddr, if it is 32-bit */
1620     if ((vaddr >> 32) == 0 && (vaddr & 0x80000000ULL))
1621     reg[COP0_BADVADDR] |=
1622     0xffffffff00000000ULL;
1623     #endif
1624     if (exc_model == EXC3K) {
1625     reg[COP0_CONTEXT] &= ~R2K3K_CONTEXT_BADVPN_MASK;
1626     reg[COP0_CONTEXT] |= ((vaddr_vpn2 << R2K3K_CONTEXT_BADVPN_SHIFT) & R2K3K_CONTEXT_BADVPN_MASK);
1627    
1628     reg[COP0_ENTRYHI] = (vaddr & R2K3K_ENTRYHI_VPN_MASK)
1629     | (vaddr_asid << R2K3K_ENTRYHI_ASID_SHIFT);
1630    
1631     /* Sign-extend: */
1632     reg[COP0_CONTEXT] = (int64_t)(int32_t)reg[COP0_CONTEXT];
1633     reg[COP0_ENTRYHI] = (int64_t)(int32_t)reg[COP0_ENTRYHI];
1634     } else {
1635     if (cpu->cd.mips.cpu_type.rev == MIPS_R4100) {
1636     reg[COP0_CONTEXT] &= ~CONTEXT_BADVPN2_MASK_R4100;
1637     reg[COP0_CONTEXT] |= ((vaddr_vpn2 << CONTEXT_BADVPN2_SHIFT) & CONTEXT_BADVPN2_MASK_R4100);
1638    
1639     /* TODO: fix these */
1640     reg[COP0_XCONTEXT] &= ~XCONTEXT_R_MASK;
1641     reg[COP0_XCONTEXT] &= ~XCONTEXT_BADVPN2_MASK;
1642     reg[COP0_XCONTEXT] |= (vaddr_vpn2 << XCONTEXT_BADVPN2_SHIFT) & XCONTEXT_BADVPN2_MASK;
1643     reg[COP0_XCONTEXT] |= ((vaddr >> 62) & 0x3) << XCONTEXT_R_SHIFT;
1644    
1645     /* reg[COP0_PAGEMASK] = cpu->cd.mips.coproc[0]->tlbs[0].mask & PAGEMASK_MASK; */
1646    
1647     reg[COP0_ENTRYHI] = (vaddr & (ENTRYHI_R_MASK | ENTRYHI_VPN2_MASK | 0x1800)) | vaddr_asid;
1648     } else {
1649     reg[COP0_CONTEXT] &= ~CONTEXT_BADVPN2_MASK;
1650     reg[COP0_CONTEXT] |= ((vaddr_vpn2 << CONTEXT_BADVPN2_SHIFT) & CONTEXT_BADVPN2_MASK);
1651    
1652     reg[COP0_XCONTEXT] &= ~XCONTEXT_R_MASK;
1653     reg[COP0_XCONTEXT] &= ~XCONTEXT_BADVPN2_MASK;
1654     reg[COP0_XCONTEXT] |= (vaddr_vpn2 << XCONTEXT_BADVPN2_SHIFT) & XCONTEXT_BADVPN2_MASK;
1655     reg[COP0_XCONTEXT] |= ((vaddr >> 62) & 0x3) << XCONTEXT_R_SHIFT;
1656    
1657     /* reg[COP0_PAGEMASK] = cpu->cd.mips.coproc[0]->tlbs[0].mask & PAGEMASK_MASK; */
1658    
1659     if (cpu->cd.mips.cpu_type.mmu_model == MMU10K)
1660     reg[COP0_ENTRYHI] = (vaddr & (ENTRYHI_R_MASK | ENTRYHI_VPN2_MASK_R10K)) | vaddr_asid;
1661     else
1662     reg[COP0_ENTRYHI] = (vaddr & (ENTRYHI_R_MASK | ENTRYHI_VPN2_MASK)) | vaddr_asid;
1663     }
1664     }
1665     }
1666    
1667     if (exc_model == EXC4K && reg[COP0_STATUS] & STATUS_EXL) {
1668     /*
1669     * Don't set EPC if STATUS_EXL is set, for R4000 and up.
1670     * This actually happens when running IRIX and Ultrix, when
1671     * they handle interrupts and/or tlb updates, I think, so
1672     * printing this with debug() looks better than with fatal().
1673     */
1674     /* debug("[ warning: cpu%i exception while EXL is set, not setting EPC ]\n", cpu->cpu_id); */
1675     } else {
1676     if (cpu->cd.mips.delay_slot || cpu->cd.mips.nullify_next) {
1677     reg[COP0_EPC] = cpu->cd.mips.pc_last - 4;
1678     reg[COP0_CAUSE] |= CAUSE_BD;
1679    
1680     /* TODO: Should the BD flag actually be set
1681     on nullified slots? */
1682     } else {
1683     reg[COP0_EPC] = cpu->cd.mips.pc_last;
1684     reg[COP0_CAUSE] &= ~CAUSE_BD;
1685     }
1686     }
1687    
1688     cpu->cd.mips.delay_slot = NOT_DELAYED;
1689     cpu->cd.mips.nullify_next = 0;
1690    
1691     /* TODO: This is true for MIPS64, but how about others? */
1692     if (reg[COP0_STATUS] & STATUS_BEV)
1693     base = 0xffffffffbfc00200ULL;
1694     else
1695     base = 0xffffffff80000000ULL;
1696    
1697     switch (exc_model) {
1698     case EXC3K:
1699     /* Userspace tlb, vs others: */
1700     if (tlb && !(vaddr & 0x80000000ULL) &&
1701     (exccode == EXCEPTION_TLBL || exccode == EXCEPTION_TLBS) )
1702     cpu->pc = base + 0x000;
1703     else
1704     cpu->pc = base + 0x080;
1705     break;
1706     default:
1707     /*
1708     * These offsets are according to the MIPS64 manual, but
1709     * should work with R4000 and the rest too (I hope).
1710     *
1711     * 0x000 TLB refill, if EXL=0
1712     * 0x080 64-bit XTLB refill, if EXL=0
1713     * 0x100 cache error (not implemented yet)
1714     * 0x180 general exception
1715     * 0x200 interrupt (if CAUSE_IV is set)
1716     */
1717     if (tlb && (exccode == EXCEPTION_TLBL ||
1718     exccode == EXCEPTION_TLBS) &&
1719     !(reg[COP0_STATUS] & STATUS_EXL)) {
1720     if (x_64)
1721     cpu->pc = base + 0x080;
1722     else
1723     cpu->pc = base + 0x000;
1724     } else {
1725     if (exccode == EXCEPTION_INT &&
1726     (reg[COP0_CAUSE] & CAUSE_IV))
1727     cpu->pc = base + 0x200;
1728     else
1729     cpu->pc = base + 0x180;
1730     }
1731     }
1732    
1733     if (exc_model == EXC3K) {
1734     /* R2000/R3000: Shift the lowest 6 bits to the left two steps: */
1735     reg[COP0_STATUS] =
1736     (reg[COP0_STATUS] & ~0x3f) +
1737     ((reg[COP0_STATUS] & 0xf) << 2);
1738     } else {
1739     /* R4000: */
1740     reg[COP0_STATUS] |= STATUS_EXL;
1741     }
1742    
1743     /* Sign-extend: */
1744     reg[COP0_CAUSE] = (int64_t)(int32_t)reg[COP0_CAUSE];
1745     reg[COP0_STATUS] = (int64_t)(int32_t)reg[COP0_STATUS];
1746     }
1747    
1748    
1749     #ifdef BINTRANS
1750     /*
1751     * mips_cpu_cause_simple_exception():
1752     *
1753     * Useful for causing raw exceptions from bintrans, for example
1754     * SYSCALL or BREAK.
1755     */
1756     void mips_cpu_cause_simple_exception(struct cpu *cpu, int exc_code)
1757     {
1758     mips_cpu_exception(cpu, exc_code, 0, 0, 0, 0, 0, 0);
1759     }
1760     #endif
1761    
1762    
1763     /* Included here for better cache characteristics: */
1764     #include "memory_mips.c"
1765    
1766    
1767     /*
1768     * mips_cpu_run_instr():
1769     *
1770     * Execute one instruction on a cpu.
1771     *
1772     * If we are in a delay slot, set cpu->pc to cpu->cd.mips.delay_jmpaddr
1773     * after the instruction is executed.
1774     *
1775     * Return value is the number of instructions executed during this call,
1776     * 0 if no instruction was executed.
1777     */
1778     int mips_cpu_run_instr(struct emul *emul, struct cpu *cpu)
1779     {
1780     int quiet_mode_cached = quiet_mode;
1781     int instruction_trace_cached = cpu->machine->instruction_trace;
1782     struct mips_coproc *cp0 = cpu->cd.mips.coproc[0];
1783     int i, tmp, ninstrs_executed;
1784     unsigned char instr[4];
1785     uint32_t instrword;
1786     uint64_t cached_pc;
1787     int hi6, special6, regimm5, rd, rs, rt, sa, imm;
1788     int copz, which_cache, cache_op;
1789    
1790     int cond, likely, and_link;
1791    
1792     /* for unaligned load/store */
1793     uint64_t dir, is_left, reg_ofs, reg_dir;
1794    
1795     uint64_t tmpvalue, tmpaddr;
1796    
1797     int cpnr; /* coprocessor nr */
1798    
1799     /* for load/store */
1800     uint64_t addr, value, value_hi, result_value;
1801     int wlen, st, signd, linked;
1802     unsigned char d[16]; /* room for at most 128 bits */
1803    
1804    
1805     /*
1806     * Update Coprocessor 0 registers:
1807     *
1808     * The COUNT register needs to be updated on every [other] instruction.
1809     * The RANDOM register should decrease for every instruction.
1810     */
1811    
1812     if (cpu->cd.mips.cpu_type.exc_model == EXC3K) {
1813     int r = (cp0->reg[COP0_RANDOM] & R2K3K_RANDOM_MASK) >> R2K3K_RANDOM_SHIFT;
1814     r --;
1815     if (r >= cp0->nr_of_tlbs || r < 8)
1816     r = cp0->nr_of_tlbs-1;
1817     cp0->reg[COP0_RANDOM] = r << R2K3K_RANDOM_SHIFT;
1818     } else {
1819     cp0->reg[COP0_RANDOM] --;
1820     if ((int64_t)cp0->reg[COP0_RANDOM] >= cp0->nr_of_tlbs ||
1821     (int64_t)cp0->reg[COP0_RANDOM] < (int64_t) cp0->reg[COP0_WIRED])
1822     cp0->reg[COP0_RANDOM] = cp0->nr_of_tlbs-1;
1823    
1824     /*
1825     * TODO: only increase count every other instruction,
1826     * according to the R4000 manual. But according to the
1827     * R5000 manual: increment every other clock cycle.
1828     * Which one is it? :-)
1829     */
1830     cp0->reg[COP0_COUNT] = (int64_t)(int32_t)(cp0->reg[COP0_COUNT] + 1);
1831    
1832     if (cpu->cd.mips.compare_register_set &&
1833     cp0->reg[COP0_COUNT] == cp0->reg[COP0_COMPARE]) {
1834     mips_cpu_interrupt(cpu, 7);
1835     cpu->cd.mips.compare_register_set = 0;
1836     }
1837     }
1838    
1839    
1840     #ifdef ENABLE_INSTRUCTION_DELAYS
1841     if (cpu->cd.mips.instruction_delay > 0) {
1842     cpu->cd.mips.instruction_delay --;
1843     return 1;
1844     }
1845     #endif
1846    
1847     /* Cache the program counter in a local variable: */
1848     cached_pc = cpu->pc;
1849    
1850     #ifdef TRACE_NULL_CRASHES
1851     cpu->trace_null_addr[cpu->trace_null_index] = cached_pc;
1852     cpu->trace_null_index ++;
1853     cpu->trace_null_index %= TRACE_NULL_N_ENTRIES;
1854     #endif
1855    
1856     /* Hardwire the zero register to 0: */
1857     cpu->cd.mips.gpr[MIPS_GPR_ZERO] = 0;
1858    
1859     if (cpu->cd.mips.delay_slot) {
1860     if (cpu->cd.mips.delay_slot == DELAYED) {
1861     cached_pc = cpu->pc = cpu->cd.mips.delay_jmpaddr;
1862     cpu->cd.mips.delay_slot = NOT_DELAYED;
1863     } else /* if (cpu->cd.mips.delay_slot == TO_BE_DELAYED) */ {
1864     /* next instruction will be delayed */
1865     cpu->cd.mips.delay_slot = DELAYED;
1866     }
1867     }
1868    
1869     if (cpu->cd.mips.last_was_jumptoself > 0)
1870     cpu->cd.mips.last_was_jumptoself --;
1871    
1872     /* Check PC against breakpoints: */
1873     if (!single_step)
1874     for (i=0; i<cpu->machine->n_breakpoints; i++)
1875     if (cached_pc == cpu->machine->breakpoint_addr[i]) {
1876     fatal("Breakpoint reached, pc=0x");
1877     if (cpu->is_32bit)
1878     fatal("%08x", (int)cached_pc);
1879     else
1880     fatal("%016llx", (long long)cached_pc);
1881     fatal("\n");
1882     single_step = 1;
1883     return 0;
1884     }
1885    
1886    
1887     /* Remember where we are, in case of interrupt or exception: */
1888     cpu->cd.mips.pc_last = cached_pc;
1889    
1890     /*
1891     * Any pending interrupts?
1892     *
1893     * If interrupts are enabled, and any interrupt has arrived (ie its
1894     * bit in the cause register is set) and corresponding enable bits
1895     * in the status register are set, then cause an interrupt exception
1896     * instead of executing the current instruction.
1897     *
1898     * NOTE: cached_interrupt_is_possible is set to 1 whenever an
1899     * interrupt bit in the cause register is set to one (in
1900     * mips_cpu_interrupt()) and set to 0 whenever all interrupt bits are
1901     * cleared (in mips_cpu_interrupt_ack()), so we don't need to do a
1902     * full check each time.
1903     */
1904     if (cpu->cd.mips.cached_interrupt_is_possible && !cpu->cd.mips.nullify_next) {
1905     if (cpu->cd.mips.cpu_type.exc_model == EXC3K) {
1906     /* R3000: */
1907     int enabled, mask;
1908     int status = cp0->reg[COP0_STATUS];
1909    
1910     enabled = status & MIPS_SR_INT_IE;
1911     mask = status & cp0->reg[COP0_CAUSE] & STATUS_IM_MASK;
1912     if (enabled && mask) {
1913     mips_cpu_exception(cpu, EXCEPTION_INT, 0, 0, 0, 0, 0, 0);
1914     return 0;
1915     }
1916     } else {
1917     /* R4000 and others: */
1918     int enabled, mask;
1919     int status = cp0->reg[COP0_STATUS];
1920    
1921     enabled = (status & STATUS_IE)
1922     && !(status & STATUS_EXL)
1923     && !(status & STATUS_ERL);
1924    
1925     mask = status & cp0->reg[COP0_CAUSE] & STATUS_IM_MASK;
1926     if (enabled && mask) {
1927     mips_cpu_exception(cpu, EXCEPTION_INT, 0, 0, 0, 0, 0, 0);
1928     return 0;
1929     }
1930     }
1931     }
1932    
1933    
1934     /*
1935     * ROM emulation: (0xbfcXXXXX or 0x9fcXXXXX)
1936     *
1937     * This assumes that a jal was made to a ROM address,
1938     * and we should return via gpr ra.
1939     */
1940     if ((cached_pc & 0xdff00000) == 0x9fc00000 &&
1941     cpu->machine->prom_emulation) {
1942     int rom_jal = 1, res = 1;
1943     switch (cpu->machine->machine_type) {
1944     case MACHINE_DEC:
1945     res = decstation_prom_emul(cpu);
1946     break;
1947     case MACHINE_PS2:
1948     res = playstation2_sifbios_emul(cpu);
1949     break;
1950     case MACHINE_ARC:
1951     case MACHINE_SGI:
1952     res = arcbios_emul(cpu);
1953     break;
1954     case MACHINE_EVBMIPS:
1955     res = yamon_emul(cpu);
1956     break;
1957     default:
1958     rom_jal = 0;
1959     }
1960    
1961     if (rom_jal) {
1962     /*
1963     * Special hack: If the PROM emulation layer needs
1964     * to loop (for example when emulating blocking
1965     * console input) then we should simply return, so
1966     * that the same PROM routine is called on the next
1967     * round as well.
1968     *
1969     * This still has to count as one or more
1970     * instructions, so 1000 is returned. (Ugly.)
1971     */
1972     if (!res)
1973     return 1000;
1974    
1975     cpu->pc = cpu->cd.mips.gpr[MIPS_GPR_RA];
1976     /* no need to update cached_pc, as we're returning */
1977     cpu->cd.mips.delay_slot = NOT_DELAYED;
1978    
1979     if (cpu->machine->show_trace_tree)
1980     cpu_functioncall_trace_return(cpu);
1981    
1982     /* TODO: how many instrs should this count as? */
1983     return 10;
1984     }
1985     }
1986    
1987     #ifdef ALWAYS_SIGNEXTEND_32
1988     /*
1989     * An extra check for 32-bit mode to make sure that all
1990     * registers are sign-extended: (Slow, but might be useful
1991     * to detect bugs that have to do with sign-extension.)
1992     */
1993     if (cpu->is_32bit) {
1994     int warning = 0;
1995     uint64_t x;
1996    
1997     if (cpu->cd.mips.gpr[0] != 0) {
1998     fatal("\nWARNING: r0 was not zero! (%016llx)\n\n",
1999     (long long)cpu->cd.mips.gpr[0]);
2000     cpu->cd.mips.gpr[0] = 0;
2001     warning = 1;
2002     }
2003    
2004     if (cpu->pc != (int64_t)(int32_t)cpu->pc) {
2005     fatal("\nWARNING: pc was not sign-extended correctly"
2006     " (%016llx)\n\n", (long long)cpu->pc);
2007     cpu->pc = (int64_t)(int32_t)cpu->pc;
2008     warning = 1;
2009     }
2010    
2011     if (cpu->cd.mips.pc_last != (int64_t)(int32_t)cpu->cd.mips.pc_last) {
2012     fatal("\nWARNING: pc_last was not sign-extended correc"
2013     "tly (%016llx)\n\n", (long long)cpu->cd.mips.pc_last);
2014     cpu->cd.mips.pc_last = (int64_t)(int32_t)cpu->cd.mips.pc_last;
2015     warning = 1;
2016     }
2017    
2018     /* Sign-extend ALL registers, including coprocessor registers and tlbs: */
2019     for (i=1; i<32; i++) {
2020     x = cpu->cd.mips.gpr[i];
2021     cpu->cd.mips.gpr[i] &= 0xffffffff;
2022     if (cpu->cd.mips.gpr[i] & 0x80000000ULL)
2023     cpu->cd.mips.gpr[i] |= 0xffffffff00000000ULL;
2024     if (x != cpu->cd.mips.gpr[i]) {
2025     fatal("\nWARNING: r%i (%s) was not sign-"
2026     "extended correctly (%016llx != "
2027     "%016llx)\n\n", i, regname(cpu->machine, i),
2028     (long long)x, (long long)cpu->cd.mips.gpr[i]);
2029     warning = 1;
2030     }
2031     }
2032     for (i=0; i<32; i++) {
2033     x = cpu->cd.mips.coproc[0]->reg[i];
2034     cpu->cd.mips.coproc[0]->reg[i] &= 0xffffffffULL;
2035     if (cpu->cd.mips.coproc[0]->reg[i] & 0x80000000ULL)
2036     cpu->cd.mips.coproc[0]->reg[i] |=
2037     0xffffffff00000000ULL;
2038     if (x != cpu->cd.mips.coproc[0]->reg[i]) {
2039     fatal("\nWARNING: cop0,r%i was not sign-extended correctly (%016llx != %016llx)\n\n",
2040     i, (long long)x, (long long)cpu->cd.mips.coproc[0]->reg[i]);
2041     warning = 1;
2042     }
2043     }
2044     for (i=0; i<cpu->cd.mips.coproc[0]->nr_of_tlbs; i++) {
2045     x = cpu->cd.mips.coproc[0]->tlbs[i].hi;
2046     cpu->cd.mips.coproc[0]->tlbs[i].hi &= 0xffffffffULL;
2047     if (cpu->cd.mips.coproc[0]->tlbs[i].hi & 0x80000000ULL)
2048     cpu->cd.mips.coproc[0]->tlbs[i].hi |=
2049     0xffffffff00000000ULL;
2050     if (x != cpu->cd.mips.coproc[0]->tlbs[i].hi) {
2051     fatal("\nWARNING: tlb[%i].hi was not sign-extended correctly (%016llx != %016llx)\n\n",
2052     i, (long long)x, (long long)cpu->cd.mips.coproc[0]->tlbs[i].hi);
2053     warning = 1;
2054     }
2055    
2056     x = cpu->cd.mips.coproc[0]->tlbs[i].lo0;
2057     cpu->cd.mips.coproc[0]->tlbs[i].lo0 &= 0xffffffffULL;
2058     if (cpu->cd.mips.coproc[0]->tlbs[i].lo0 & 0x80000000ULL)
2059     cpu->cd.mips.coproc[0]->tlbs[i].lo0 |=
2060     0xffffffff00000000ULL;
2061     if (x != cpu->cd.mips.coproc[0]->tlbs[i].lo0) {
2062     fatal("\nWARNING: tlb[%i].lo0 was not sign-extended correctly (%016llx != %016llx)\n\n",
2063     i, (long long)x, (long long)cpu->cd.mips.coproc[0]->tlbs[i].lo0);
2064     warning = 1;
2065     }
2066     }
2067    
2068     if (warning) {
2069     fatal("Halting. pc = %016llx\n", (long long)cpu->pc);
2070     cpu->running = 0;
2071     }
2072     }
2073     #endif
2074    
2075     PREFETCH(cpu->cd.mips.pc_last_host_4k_page + (cached_pc & 0xfff));
2076    
2077     #ifdef HALT_IF_PC_ZERO
2078     /* Halt if PC = 0: */
2079     if (cached_pc == 0) {
2080     debug("cpu%i: pc=0, halting\n", cpu->cpu_id);
2081     cpu->running = 0;
2082     return 0;
2083     }
2084     #endif
2085    
2086     #ifdef BINTRANS
2087     if ((single_step || instruction_trace_cached)
2088     && cpu->machine->bintrans_enable)
2089     cpu->cd.mips.dont_run_next_bintrans = 1;
2090     #endif
2091    
2092     if (!quiet_mode_cached) {
2093     /* Dump CPU registers for debugging: */
2094     if (cpu->machine->register_dump) {
2095     debug("\n");
2096     mips_cpu_register_dump(cpu, 1, 0x1);
2097     }
2098     }
2099    
2100     /* Trace tree: */
2101     if (cpu->machine->show_trace_tree && cpu->cd.mips.show_trace_delay > 0) {
2102     cpu->cd.mips.show_trace_delay --;
2103     if (cpu->cd.mips.show_trace_delay == 0)
2104     cpu_functioncall_trace(cpu, cpu->cd.mips.show_trace_addr);
2105     }
2106    
2107     #ifdef MFHILO_DELAY
2108     /* Decrease the MFHI/MFLO delays: */
2109     if (cpu->mfhi_delay > 0)
2110     cpu->mfhi_delay--;
2111     if (cpu->mflo_delay > 0)
2112     cpu->mflo_delay--;
2113     #endif
2114    
2115     /* Read an instruction from memory: */
2116     #ifdef ENABLE_MIPS16
2117     if (cpu->cd.mips.mips16 && (cached_pc & 1)) {
2118     /* 16-bit instruction word: */
2119     unsigned char instr16[2];
2120     int mips16_offset = 0;
2121    
2122     if (!cpu->memory_rw(cpu, cpu->mem, cached_pc ^ 1, &instr16[0],
2123     sizeof(instr16), MEM_READ, CACHE_INSTRUCTION))
2124     return 0;
2125    
2126     /* TODO: If Reverse-endian is set in the status cop0 register, and
2127     we are in usermode, then reverse endianness! */
2128    
2129     /* The rest of the code is written for little endian, so swap if necessary: */
2130     if (cpu->byte_order == EMUL_BIG_ENDIAN) {
2131     int tmp;
2132     tmp = instr16[0]; instr16[0] = instr16[1]; instr16[1] = tmp;
2133     }
2134    
2135     cpu->cd.mips.mips16_extend = 0;
2136    
2137     /*
2138     * Translate into 32-bit instruction, little endian (instr[3..0]):
2139     *
2140     * This ugly loop is necessary because if we would get an exception between
2141     * reading an extend instruction and the next instruction, and execution
2142     * continues on the second instruction, the extend data would be lost. So the
2143     * entire instruction (the two parts) need to be read in. If an exception is
2144     * caused, it will appear as if it was caused when reading the extend instruction.
2145     */
2146     while (mips16_to_32(cpu, instr16, instr) == 0) {
2147     if (instruction_trace_cached)
2148     debug("cpu%i @ %016llx: %02x%02x\t\t\textend\n",
2149     cpu->cpu_id, (cpu->cd.mips.pc_last ^ 1) + mips16_offset,
2150     instr16[1], instr16[0]);
2151    
2152     /* instruction with extend: */
2153     mips16_offset += 2;
2154     if (!cpu->memory_rw(cpu, cpu->mem, (cached_pc ^ 1) +
2155     mips16_offset, &instr16[0], sizeof(instr16),
2156     MEM_READ, CACHE_INSTRUCTION))
2157     return 0;
2158    
2159     if (cpu->byte_order == EMUL_BIG_ENDIAN) {
2160     int tmp;
2161     tmp = instr16[0]; instr16[0] = instr16[1]; instr16[1] = tmp;
2162     }
2163     }
2164    
2165     /* TODO: bintrans like in 32-bit mode? */
2166    
2167     /* Advance the program counter: */
2168     cpu->pc += sizeof(instr16) + mips16_offset;
2169     cached_pc = cpu->pc;
2170    
2171     if (instruction_trace_cached) {
2172     uint64_t offset;
2173     char *symbol = get_symbol_name(&cpu->machine->
2174     symbol_context, cpu->cd.mips.pc_last ^ 1, &offset);
2175     if (symbol != NULL && offset==0)
2176     debug("<%s>\n", symbol);
2177    
2178     debug("cpu%i @ %016llx: %02x%02x => %02x%02x%02x%02x%s\t",
2179     cpu->cpu_id, (cpu->cd.mips.pc_last ^ 1) + mips16_offset,
2180     instr16[1], instr16[0],
2181     instr[3], instr[2], instr[1], instr[0],
2182     cpu_flags(cpu));
2183     }
2184     } else
2185     #endif
2186     {
2187     /*
2188     * Fetch a 32-bit instruction word from memory:
2189     *
2190     * 1) The special case of reading an instruction from the
2191     * same host RAM page as the last one is handled here,
2192     * to gain a little bit performance.
2193     *
2194     * 2) Fallback to reading from memory the usual way.
2195     */
2196     if (cached_pc & 3) {
2197     mips_cpu_exception(cpu, EXCEPTION_ADEL,
2198     0, cached_pc, 0, 0, 0, 0);
2199     return 0;
2200     }
2201     if (cpu->cd.mips.pc_last_host_4k_page != NULL &&
2202     (cached_pc & ~0xfff) == cpu->cd.mips.pc_last_virtual_page) {
2203     /* NOTE: This only works on the host if offset is
2204     aligned correctly! (TODO) */
2205     *(uint32_t *)instr = *(uint32_t *)
2206     (cpu->cd.mips.pc_last_host_4k_page + (cached_pc & 0xffc));
2207     #ifdef BINTRANS
2208     cpu->cd.mips.pc_bintrans_paddr_valid = 1;
2209     cpu->cd.mips.pc_bintrans_paddr =
2210     cpu->cd.mips.pc_last_physical_page | (cached_pc & 0xfff);
2211     cpu->cd.mips.pc_bintrans_host_4kpage = cpu->cd.mips.pc_last_host_4k_page;
2212     #endif
2213     } else {
2214     if (!cpu->memory_rw(cpu, cpu->mem, cached_pc, &instr[0],
2215     sizeof(instr), MEM_READ, CACHE_INSTRUCTION))
2216     return 0;
2217     }
2218    
2219     #ifdef BINTRANS
2220     if (cpu->cd.mips.dont_run_next_bintrans) {
2221     cpu->cd.mips.dont_run_next_bintrans = 0;
2222     } else if (cpu->machine->bintrans_enable &&
2223     cpu->cd.mips.pc_bintrans_paddr_valid) {
2224     int res;
2225     cpu->cd.mips.bintrans_instructions_executed = 0;
2226    
2227     res = bintrans_attempt_translate(cpu,
2228     cpu->cd.mips.pc_bintrans_paddr);
2229    
2230     if (res >= 0) {
2231     /* debug("BINTRANS translation + hit,"
2232     " pc = %016llx\n", (long long)cached_pc); */
2233     if (res > 0 || cpu->pc != cached_pc) {
2234     if (instruction_trace_cached)
2235     mips_cpu_disassemble_instr(cpu, instr, 1, 0, 1);
2236     if (res & BINTRANS_DONT_RUN_NEXT)
2237     cpu->cd.mips.dont_run_next_bintrans = 1;
2238     res &= BINTRANS_N_MASK;
2239    
2240     if (cpu->cd.mips.cpu_type.exc_model != EXC3K) {
2241     int x = cp0->reg[COP0_COUNT], y = cp0->reg[COP0_COMPARE];
2242     int diff = x - y;
2243     if (diff < 0 && diff + (res-1) >= 0
2244     && cpu->cd.mips.compare_register_set) {
2245     mips_cpu_interrupt(cpu, 7);
2246     cpu->cd.mips.compare_register_set = 0;
2247     }
2248    
2249     cp0->reg[COP0_COUNT] = (int64_t)
2250     (int32_t)(cp0->reg[COP0_COUNT] + res-1);
2251     }
2252    
2253     return res;
2254     }
2255     }
2256     }
2257     #endif
2258    
2259     if (instruction_trace_cached)
2260     mips_cpu_disassemble_instr(cpu, instr, 1, 0, 0);
2261    
2262     /* Advance the program counter: */
2263     cpu->pc += sizeof(instr);
2264     cached_pc = cpu->pc;
2265    
2266     /*
2267     * TODO: If Reverse-endian is set in the status cop0 register
2268     * and we are in usermode, then reverse endianness!
2269     */
2270    
2271     /*
2272     * The rest of the code is written for little endian, so
2273     * swap if necessary:
2274     */
2275     if (cpu->byte_order == EMUL_BIG_ENDIAN) {
2276     int tmp = instr[0]; instr[0] = instr[3]; instr[3] = tmp;
2277     tmp = instr[1]; instr[1] = instr[2]; instr[2] = tmp;
2278     }
2279     }
2280    
2281    
2282     /*
2283     * Nullify this instruction? (Set by a previous branch-likely
2284     * instruction.)
2285     *
2286     * Note: The return value is 1, even if no instruction was actually
2287     * executed.
2288     */
2289     if (cpu->cd.mips.nullify_next) {
2290     cpu->cd.mips.nullify_next = 0;
2291     return 1;
2292     }
2293    
2294    
2295     /*
2296     * Execute the instruction:
2297     */
2298    
2299     /* Get the top 6 bits of the instruction: */
2300     hi6 = instr[3] >> 2; /* & 0x3f */
2301    
2302     if (show_opcode_statistics)
2303     cpu->cd.mips.stats_opcode[hi6] ++;
2304    
2305     switch (hi6) {
2306     case HI6_SPECIAL:
2307     special6 = instr[0] & 0x3f;
2308    
2309     if (show_opcode_statistics)
2310     cpu->cd.mips.stats__special[special6] ++;
2311    
2312     switch (special6) {
2313     case SPECIAL_SLL:
2314     case SPECIAL_SRL:
2315     case SPECIAL_SRA:
2316     case SPECIAL_DSLL:
2317     case SPECIAL_DSRL:
2318     case SPECIAL_DSRA:
2319     case SPECIAL_DSLL32:
2320     case SPECIAL_DSRL32:
2321     case SPECIAL_DSRA32:
2322     rt = instr[2] & 31;
2323     rd = (instr[1] >> 3) & 31;
2324     sa = ((instr[1] & 7) << 2) + ((instr[0] >> 6) & 3);
2325    
2326     /*
2327     * Check for NOP:
2328     *
2329     * The R4000 manual says that a shift amount of zero
2330     * is treated as a nop by some assemblers. Checking
2331     * for sa == 0 here would not be correct, though,
2332     * because instructions such as sll r3,r4,0 are
2333     * possible, and are definitely not a nop.
2334     * Instead, check if the destination register is r0.
2335     *
2336     * TODO: ssnop should wait until the _next_
2337     * cycle boundary, or something like that. The
2338     * code here is incorrect.
2339     */
2340     if (rd == 0 && special6 == SPECIAL_SLL) {
2341     if (sa == 1) {
2342     /* ssnop */
2343     #ifdef ENABLE_INSTRUCTION_DELAYS
2344     cpu->cd.mips.instruction_delay +=
2345     cpu->cd.mips.cpu_type.
2346     instrs_per_cycle - 1;
2347     #endif
2348     }
2349     return 1;
2350     }
2351    
2352     if (special6 == SPECIAL_SLL) {
2353     switch (sa) {
2354     case 8: cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] << 8; break;
2355     case 16:cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] << 16; break;
2356     default:cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] << sa;
2357     }
2358     /* Sign-extend rd: */
2359     cpu->cd.mips.gpr[rd] = (int64_t) (int32_t) cpu->cd.mips.gpr[rd];
2360     }
2361     if (special6 == SPECIAL_DSLL) {
2362     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] << sa;
2363     }
2364     if (special6 == SPECIAL_DSRL) {
2365     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] >> sa;
2366     }
2367     if (special6 == SPECIAL_DSLL32) {
2368     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] << (sa + 32);
2369     }
2370     if (special6 == SPECIAL_SRL) {
2371     /*
2372     * Three cases:
2373     * shift amount = zero: just copy
2374     * high bit of rt zero: plain shift right (of all bits)
2375     * high bit of rt one: plain shift right (of lowest 32 bits)
2376     */
2377     if (sa == 0)
2378     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt];
2379     else if (!(cpu->cd.mips.gpr[rt] & 0x80000000ULL)) {
2380     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] >> sa;
2381     } else
2382     cpu->cd.mips.gpr[rd] = (cpu->cd.mips.gpr[rt] & 0xffffffffULL) >> sa;
2383     }
2384     if (special6 == SPECIAL_SRA) {
2385     int topbit = cpu->cd.mips.gpr[rt] & 0x80000000ULL;
2386     switch (sa) {
2387     case 8: cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] >> 8; break;
2388     case 16:cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] >> 16; break;
2389     default:cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] >> sa;
2390     }
2391     if (topbit)
2392     cpu->cd.mips.gpr[rd] |= 0xffffffff00000000ULL;
2393     }
2394     if (special6 == SPECIAL_DSRL32) {
2395     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] >> (sa + 32);
2396     }
2397     if (special6 == SPECIAL_DSRA32 || special6 == SPECIAL_DSRA) {
2398     if (special6 == SPECIAL_DSRA32)
2399     sa += 32;
2400     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt];
2401     while (sa > 0) {
2402     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rd] >> 1;
2403     sa--;
2404     if (cpu->cd.mips.gpr[rd] & ((uint64_t)1 << 62)) /* old signbit */
2405     cpu->cd.mips.gpr[rd] |= ((uint64_t)1 << 63);
2406     }
2407     }
2408     return 1;
2409     case SPECIAL_DSRLV:
2410     case SPECIAL_DSRAV:
2411     case SPECIAL_DSLLV:
2412     case SPECIAL_SLLV:
2413     case SPECIAL_SRAV:
2414     case SPECIAL_SRLV:
2415     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
2416     rt = instr[2] & 31;
2417     rd = (instr[1] >> 3) & 31;
2418    
2419     if (special6 == SPECIAL_DSRLV) {
2420     sa = cpu->cd.mips.gpr[rs] & 63;
2421     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt] >> sa;
2422     }
2423     if (special6 == SPECIAL_DSRAV) {
2424     sa = cpu->cd.mips.gpr[rs] & 63;
2425     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt];
2426     while (sa > 0) {
2427     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rd] >> 1;
2428     sa--;
2429     if (cpu->cd.mips.gpr[rd] & ((uint64_t)1 << 62)) /* old sign-bit */
2430     cpu->cd.mips.gpr[rd] |= ((uint64_t)1 << 63);
2431     }
2432     }
2433     if (special6 == SPECIAL_DSLLV) {
2434     sa = cpu->cd.mips.gpr[rs] & 63;
2435     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt];
2436     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rd] << sa;
2437     }
2438     if (special6 == SPECIAL_SLLV) {
2439     sa = cpu->cd.mips.gpr[rs] & 31;
2440     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt];
2441     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rd] << sa;
2442     /* Sign-extend rd: */
2443     cpu->cd.mips.gpr[rd] &= 0xffffffffULL;
2444     if (cpu->cd.mips.gpr[rd] & 0x80000000ULL)
2445     cpu->cd.mips.gpr[rd] |= 0xffffffff00000000ULL;
2446     }
2447     if (special6 == SPECIAL_SRAV) {
2448     sa = cpu->cd.mips.gpr[rs] & 31;
2449     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt];
2450     /* Sign-extend rd: */
2451     cpu->cd.mips.gpr[rd] &= 0xffffffffULL;
2452     if (cpu->cd.mips.gpr[rd] & 0x80000000ULL)
2453     cpu->cd.mips.gpr[rd] |= 0xffffffff00000000ULL;
2454     while (sa > 0) {
2455     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rd] >> 1;
2456     sa--;
2457     }
2458     if (cpu->cd.mips.gpr[rd] & 0x80000000ULL)
2459     cpu->cd.mips.gpr[rd] |= 0xffffffff00000000ULL;
2460     }
2461     if (special6 == SPECIAL_SRLV) {
2462     sa = cpu->cd.mips.gpr[rs] & 31;
2463     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rt];
2464     cpu->cd.mips.gpr[rd] &= 0xffffffffULL;
2465     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rd] >> sa;
2466     /* And finally sign-extend rd: */
2467     if (cpu->cd.mips.gpr[rd] & 0x80000000ULL)
2468     cpu->cd.mips.gpr[rd] |= 0xffffffff00000000ULL;
2469     }
2470     return 1;
2471     case SPECIAL_JR:
2472     if (cpu->cd.mips.delay_slot) {
2473     fatal("jr: jump inside a jump's delay slot, or similar. TODO\n");
2474     cpu->running = 0;
2475     return 1;
2476     }
2477    
2478     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
2479    
2480     cpu->cd.mips.delay_slot = TO_BE_DELAYED;
2481     cpu->cd.mips.delay_jmpaddr = cpu->cd.mips.gpr[rs];
2482    
2483     if (cpu->machine->show_trace_tree && rs == 31)
2484     cpu_functioncall_trace_return(cpu);
2485    
2486     return 1;
2487     case SPECIAL_JALR:
2488     if (cpu->cd.mips.delay_slot) {
2489     fatal("jalr: jump inside a jump's delay slot, or similar. TODO\n");
2490     cpu->running = 0;
2491     return 1;
2492     }
2493    
2494     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
2495     rd = (instr[1] >> 3) & 31;
2496    
2497     tmpvalue = cpu->cd.mips.gpr[rs];
2498     cpu->cd.mips.gpr[rd] = cached_pc + 4;
2499     /* already increased by 4 earlier */
2500    
2501     if (cpu->machine->show_trace_tree && rd == 31) {
2502     cpu->cd.mips.show_trace_delay = 2;
2503     cpu->cd.mips.show_trace_addr = tmpvalue;
2504     }
2505    
2506     cpu->cd.mips.delay_slot = TO_BE_DELAYED;
2507     cpu->cd.mips.delay_jmpaddr = tmpvalue;
2508     return 1;
2509     case SPECIAL_MFHI:
2510     case SPECIAL_MFLO:
2511     rd = (instr[1] >> 3) & 31;
2512    
2513     if (special6 == SPECIAL_MFHI) {
2514     cpu->cd.mips.gpr[rd] = cpu->cd.mips.hi;
2515     #ifdef MFHILO_DELAY
2516     cpu->mfhi_delay = 3;
2517     #endif
2518     }
2519     if (special6 == SPECIAL_MFLO) {
2520     cpu->cd.mips.gpr[rd] = cpu->cd.mips.lo;
2521     #ifdef MFHILO_DELAY
2522     cpu->mflo_delay = 3;
2523     #endif
2524     }
2525     return 1;
2526     case SPECIAL_ADD:
2527     case SPECIAL_ADDU:
2528     case SPECIAL_SUB:
2529     case SPECIAL_SUBU:
2530     case SPECIAL_AND:
2531     case SPECIAL_OR:
2532     case SPECIAL_XOR:
2533     case SPECIAL_NOR:
2534     case SPECIAL_SLT:
2535     case SPECIAL_SLTU:
2536     case SPECIAL_MTLO:
2537     case SPECIAL_MTHI:
2538     case SPECIAL_MULT:
2539     case SPECIAL_MULTU:
2540     case SPECIAL_DMULT:
2541     case SPECIAL_DMULTU:
2542     case SPECIAL_DIV:
2543     case SPECIAL_DIVU:
2544     case SPECIAL_DDIV:
2545     case SPECIAL_DDIVU:
2546     case SPECIAL_TGE:
2547     case SPECIAL_TGEU:
2548     case SPECIAL_TLT:
2549     case SPECIAL_TLTU:
2550     case SPECIAL_TEQ:
2551     case SPECIAL_TNE:
2552     case SPECIAL_DADD:
2553     case SPECIAL_DADDU:
2554     case SPECIAL_DSUB:
2555     case SPECIAL_DSUBU:
2556     case SPECIAL_MOVZ:
2557     case SPECIAL_MOVN:
2558     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
2559     rt = instr[2] & 31;
2560     rd = (instr[1] >> 3) & 31;
2561    
2562     #ifdef MFHILO_DELAY
2563     if (cpu->mflo_delay > 0 && (
2564     special6 == SPECIAL_DDIV || special6 == SPECIAL_DDIVU ||
2565     special6 == SPECIAL_DIV || special6 == SPECIAL_DIVU ||
2566     special6 == SPECIAL_DMULT || special6 == SPECIAL_DMULTU ||
2567     special6 == SPECIAL_MTLO || special6 == SPECIAL_MULT
2568     || special6 == SPECIAL_MULTU
2569     ) )
2570     debug("warning: instruction modifying LO too early after mflo!\n");
2571    
2572     if (cpu->mfhi_delay > 0 && (
2573     special6 == SPECIAL_DDIV || special6 == SPECIAL_DDIVU ||
2574     special6 == SPECIAL_DIV || special6 == SPECIAL_DIVU ||
2575     special6 == SPECIAL_DMULT || special6 == SPECIAL_DMULTU ||
2576     special6 == SPECIAL_MTHI || special6 == SPECIAL_MULT
2577     || special6 == SPECIAL_MULTU
2578     ) )
2579     debug("warning: instruction modifying HI too early after mfhi!\n");
2580     #endif
2581    
2582     if (special6 == SPECIAL_ADDU) {
2583     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs] + cpu->cd.mips.gpr[rt];
2584     cpu->cd.mips.gpr[rd] &= 0xffffffffULL;
2585     if (cpu->cd.mips.gpr[rd] & 0x80000000ULL)
2586     cpu->cd.mips.gpr[rd] |= 0xffffffff00000000ULL;
2587     break;
2588     }
2589     if (special6 == SPECIAL_ADD) {
2590     /* According to the MIPS64 manual: */
2591     uint64_t temp, temp1, temp2;
2592     temp1 = cpu->cd.mips.gpr[rs] + ((cpu->cd.mips.gpr[rs] & 0x80000000ULL) << 1);
2593     temp2 = cpu->cd.mips.gpr[rt] + ((cpu->cd.mips.gpr[rt] & 0x80000000ULL) << 1);
2594     temp = temp1 + temp2;
2595     #if 0
2596     /* TODO: apparently this doesn't work (an example of
2597     something that breaks is NetBSD/sgimips' mips3_TBIA() */
2598     /* If bits 32 and 31 of temp differ, then it's an overflow */
2599     temp1 = temp & 0x100000000ULL;
2600     temp2 = temp & 0x80000000ULL;
2601     if ((temp1 && !temp2) || (!temp1 && temp2)) {
2602     mips_cpu_exception(cpu, EXCEPTION_OV, 0, 0, 0, 0, 0, 0);
2603     break;
2604     }
2605     #endif
2606     cpu->cd.mips.gpr[rd] = temp & 0xffffffffULL;
2607     if (cpu->cd.mips.gpr[rd] & 0x80000000ULL)
2608     cpu->cd.mips.gpr[rd] |= 0xffffffff00000000ULL;
2609     break;
2610     }
2611     if (special6 == SPECIAL_SUBU) {
2612     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs] - cpu->cd.mips.gpr[rt];
2613     cpu->cd.mips.gpr[rd] &= 0xffffffffULL;
2614     if (cpu->cd.mips.gpr[rd] & 0x80000000ULL)
2615     cpu->cd.mips.gpr[rd] |= 0xffffffff00000000ULL;
2616     break;
2617     }
2618     if (special6 == SPECIAL_SUB) {
2619     /* According to the MIPS64 manual: */
2620     uint64_t temp, temp1, temp2;
2621     temp1 = cpu->cd.mips.gpr[rs] + ((cpu->cd.mips.gpr[rs] & 0x80000000ULL) << 1);
2622     temp2 = cpu->cd.mips.gpr[rt] + ((cpu->cd.mips.gpr[rt] & 0x80000000ULL) << 1);
2623     temp = temp1 - temp2;
2624     #if 0
2625     /* If bits 32 and 31 of temp differ, then it's an overflow */
2626     temp1 = temp & 0x100000000ULL;
2627     temp2 = temp & 0x80000000ULL;
2628     if ((temp1 && !temp2) || (!temp1 && temp2)) {
2629     mips_cpu_exception(cpu, EXCEPTION_OV, 0, 0, 0, 0, 0, 0);
2630     break;
2631     }
2632     #endif
2633     cpu->cd.mips.gpr[rd] = temp & 0xffffffffULL;
2634     if (cpu->cd.mips.gpr[rd] & 0x80000000ULL)
2635     cpu->cd.mips.gpr[rd] |= 0xffffffff00000000ULL;
2636     break;
2637     }
2638    
2639     if (special6 == SPECIAL_AND) {
2640     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs] & cpu->cd.mips.gpr[rt];
2641     break;
2642     }
2643     if (special6 == SPECIAL_OR) {
2644     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs] | cpu->cd.mips.gpr[rt];
2645     break;
2646     }
2647     if (special6 == SPECIAL_XOR) {
2648     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs] ^ cpu->cd.mips.gpr[rt];
2649     break;
2650     }
2651     if (special6 == SPECIAL_NOR) {
2652     cpu->cd.mips.gpr[rd] = ~(cpu->cd.mips.gpr[rs] | cpu->cd.mips.gpr[rt]);
2653     break;
2654     }
2655     if (special6 == SPECIAL_SLT) {
2656     cpu->cd.mips.gpr[rd] = (int64_t)cpu->cd.mips.gpr[rs] < (int64_t)cpu->cd.mips.gpr[rt];
2657     break;
2658     }
2659     if (special6 == SPECIAL_SLTU) {
2660     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs] < cpu->cd.mips.gpr[rt];
2661     break;
2662     }
2663     if (special6 == SPECIAL_MTLO) {
2664     cpu->cd.mips.lo = cpu->cd.mips.gpr[rs];
2665     break;
2666     }
2667     if (special6 == SPECIAL_MTHI) {
2668     cpu->cd.mips.hi = cpu->cd.mips.gpr[rs];
2669     break;
2670     }
2671     if (special6 == SPECIAL_MULT) {
2672     int64_t f1, f2, sum;
2673     f1 = cpu->cd.mips.gpr[rs] & 0xffffffffULL;
2674     /* sign extend f1 */
2675     if (f1 & 0x80000000ULL)
2676     f1 |= 0xffffffff00000000ULL;
2677     f2 = cpu->cd.mips.gpr[rt] & 0xffffffffULL;
2678     /* sign extend f2 */
2679     if (f2 & 0x80000000ULL)
2680     f2 |= 0xffffffff00000000ULL;
2681     sum = f1 * f2;
2682    
2683     cpu->cd.mips.lo = sum & 0xffffffffULL;
2684     cpu->cd.mips.hi = ((uint64_t)sum >> 32) & 0xffffffffULL;
2685    
2686     /* sign-extend: */
2687     if (cpu->cd.mips.lo & 0x80000000ULL)
2688     cpu->cd.mips.lo |= 0xffffffff00000000ULL;
2689     if (cpu->cd.mips.hi & 0x80000000ULL)
2690     cpu->cd.mips.hi |= 0xffffffff00000000ULL;
2691    
2692     /*
2693     * NOTE: The stuff about rd!=0 is just a
2694     * guess, judging from how some NetBSD code
2695     * seems to execute. It is not documented in
2696     * the MIPS64 ISA docs :-/
2697     */
2698    
2699     if (rd != 0) {
2700     if (cpu->cd.mips.cpu_type.rev != MIPS_R5900)
2701     debug("WARNING! mult_xx is an undocumented instruction!");
2702     cpu->cd.mips.gpr[rd] = cpu->cd.mips.lo;
2703     }
2704     break;
2705     }
2706     if (special6 == SPECIAL_MULTU) {
2707     uint64_t f1, f2, sum;
2708     /* zero extend f1 and f2 */
2709     f1 = cpu->cd.mips.gpr[rs] & 0xffffffffULL;
2710     f2 = cpu->cd.mips.gpr[rt] & 0xffffffffULL;
2711     sum = f1 * f2;
2712     cpu->cd.mips.lo = sum & 0xffffffffULL;
2713     cpu->cd.mips.hi = (sum >> 32) & 0xffffffffULL;
2714    
2715     /* sign-extend: */
2716     if (cpu->cd.mips.lo & 0x80000000ULL)
2717     cpu->cd.mips.lo |= 0xffffffff00000000ULL;
2718     if (cpu->cd.mips.hi & 0x80000000ULL)
2719     cpu->cd.mips.hi |= 0xffffffff00000000ULL;
2720     break;
2721     }
2722     if (special6 == SPECIAL_DMULT) {
2723     /* 64x64 = 128 bit multiplication, signed. */
2724     uint64_t s1 = cpu->cd.mips.gpr[rt];
2725     uint64_t s2 = cpu->cd.mips.gpr[rs];
2726     int n_negative = 0;
2727     int i;
2728    
2729     if ((int64_t)s1 < 0) {
2730     s1 = -(int64_t)s1;
2731     n_negative ++;
2732     }
2733     if ((int64_t)s2 < 0) {
2734     s2 = -(int64_t)s2;
2735     n_negative ++;
2736     }
2737    
2738     cpu->cd.mips.lo = cpu->cd.mips.hi = 0;
2739    
2740     for (i=0; i<64; i++) {
2741     int bit = (s1 & 0x8000000000000000ULL)? 1 : 0;
2742     s1 <<= 1;
2743     /* If bit in s1 set, then add s2 to hi/lo: */
2744     if (bit) {
2745     uint64_t old_lo = cpu->cd.mips.lo;
2746     cpu->cd.mips.lo += s2;
2747     if (cpu->cd.mips.lo < old_lo)
2748     cpu->cd.mips.hi ++;
2749     }
2750     if (i != 63) {
2751     cpu->cd.mips.hi <<= 1;
2752     cpu->cd.mips.hi +=
2753     (cpu->cd.mips.lo & 0x8000000000000000ULL) ? 1 : 0;
2754     cpu->cd.mips.lo <<= 1;
2755     }
2756     }
2757    
2758     if (n_negative == 1) {
2759     cpu->cd.mips.hi = -(int64_t)cpu->cd.mips.hi;
2760     cpu->cd.mips.lo = -(int64_t)cpu->cd.mips.lo;
2761     if ((int64_t)cpu->cd.mips.lo < 0)
2762     cpu->cd.mips.hi --;
2763     }
2764     break;
2765     }
2766     if (special6 == SPECIAL_DMULTU) {
2767     /* 64x64 = 128 bit multiplication, unsigned. */
2768     uint64_t s1 = cpu->cd.mips.gpr[rt];
2769     uint64_t s2 = cpu->cd.mips.gpr[rs];
2770     int i;
2771    
2772     cpu->cd.mips.lo = cpu->cd.mips.hi = 0;
2773    
2774     for (i=0; i<64; i++) {
2775     int bit = (s1 & 0x8000000000000000ULL)? 1 : 0;
2776     s1 <<= 1;
2777     /* If bit in s1 set, then add s2 to hi/lo: */
2778     if (bit) {
2779     uint64_t old_lo = cpu->cd.mips.lo;
2780     cpu->cd.mips.lo += s2;
2781     if (cpu->cd.mips.lo < old_lo)
2782     cpu->cd.mips.hi ++;
2783     }
2784     if (i != 63) {
2785     cpu->cd.mips.hi <<= 1;
2786     cpu->cd.mips.hi +=
2787     (cpu->cd.mips.lo & 0x8000000000000000ULL) ? 1 : 0;
2788     cpu->cd.mips.lo <<= 1;
2789     }
2790     }
2791     break;
2792     }
2793     if (special6 == SPECIAL_DIV) {
2794     int64_t a, b;
2795     /* Signextend rs and rt: */
2796     a = cpu->cd.mips.gpr[rs] & 0xffffffffULL;
2797     if (a & 0x80000000ULL)
2798     a |= 0xffffffff00000000ULL;
2799     b = cpu->cd.mips.gpr[rt] & 0xffffffffULL;
2800     if (b & 0x80000000ULL)
2801     b |= 0xffffffff00000000ULL;
2802    
2803     if (b == 0) {
2804     /* undefined */
2805     cpu->cd.mips.lo = cpu->cd.mips.hi = 0;
2806     } else {
2807     cpu->cd.mips.lo = a / b;
2808     cpu->cd.mips.hi = a % b;
2809     }
2810     /* Sign-extend lo and hi: */
2811     cpu->cd.mips.lo &= 0xffffffffULL;
2812     if (cpu->cd.mips.lo & 0x80000000ULL)
2813     cpu->cd.mips.lo |= 0xffffffff00000000ULL;
2814     cpu->cd.mips.hi &= 0xffffffffULL;
2815     if (cpu->cd.mips.hi & 0x80000000ULL)
2816     cpu->cd.mips.hi |= 0xffffffff00000000ULL;
2817     break;
2818     }
2819     if (special6 == SPECIAL_DIVU) {
2820     int64_t a, b;
2821     /* Zero-extend rs and rt: */
2822     a = cpu->cd.mips.gpr[rs] & 0xffffffffULL;
2823     b = cpu->cd.mips.gpr[rt] & 0xffffffffULL;
2824     if (b == 0) {
2825     /* undefined */
2826     cpu->cd.mips.lo = cpu->cd.mips.hi = 0;
2827     } else {
2828     cpu->cd.mips.lo = a / b;
2829     cpu->cd.mips.hi = a % b;
2830     }
2831     /* Sign-extend lo and hi: */
2832     cpu->cd.mips.lo &= 0xffffffffULL;
2833     if (cpu->cd.mips.lo & 0x80000000ULL)
2834     cpu->cd.mips.lo |= 0xffffffff00000000ULL;
2835     cpu->cd.mips.hi &= 0xffffffffULL;
2836     if (cpu->cd.mips.hi & 0x80000000ULL)
2837     cpu->cd.mips.hi |= 0xffffffff00000000ULL;
2838     break;
2839     }
2840     if (special6 == SPECIAL_DDIV) {
2841     if (cpu->cd.mips.gpr[rt] == 0) {
2842     cpu->cd.mips.lo = cpu->cd.mips.hi = 0; /* undefined */
2843     } else {
2844     cpu->cd.mips.lo = (int64_t)cpu->cd.mips.gpr[rs] / (int64_t)cpu->cd.mips.gpr[rt];
2845     cpu->cd.mips.hi = (int64_t)cpu->cd.mips.gpr[rs] % (int64_t)cpu->cd.mips.gpr[rt];
2846     }
2847     break;
2848     }
2849     if (special6 == SPECIAL_DDIVU) {
2850     if (cpu->cd.mips.gpr[rt] == 0) {
2851     cpu->cd.mips.lo = cpu->cd.mips.hi = 0; /* undefined */
2852     } else {
2853     cpu->cd.mips.lo = cpu->cd.mips.gpr[rs] / cpu->cd.mips.gpr[rt];
2854     cpu->cd.mips.hi = cpu->cd.mips.gpr[rs] % cpu->cd.mips.gpr[rt];
2855     }
2856     break;
2857     }
2858     if (special6 == SPECIAL_TGE) {
2859     if ((int64_t)cpu->cd.mips.gpr[rs] >= (int64_t)cpu->cd.mips.gpr[rt])
2860     mips_cpu_exception(cpu, EXCEPTION_TR, 0, 0, 0, 0, 0, 0);
2861     break;
2862     }
2863     if (special6 == SPECIAL_TGEU) {
2864     if (cpu->cd.mips.gpr[rs] >= cpu->cd.mips.gpr[rt])
2865     mips_cpu_exception(cpu, EXCEPTION_TR, 0, 0, 0, 0, 0, 0);
2866     break;
2867     }
2868     if (special6 == SPECIAL_TLT) {
2869     if ((int64_t)cpu->cd.mips.gpr[rs] < (int64_t)cpu->cd.mips.gpr[rt])
2870     mips_cpu_exception(cpu, EXCEPTION_TR, 0, 0, 0, 0, 0, 0);
2871     break;
2872     }
2873     if (special6 == SPECIAL_TLTU) {
2874     if (cpu->cd.mips.gpr[rs] < cpu->cd.mips.gpr[rt])
2875     mips_cpu_exception(cpu, EXCEPTION_TR, 0, 0, 0, 0, 0, 0);
2876     break;
2877     }
2878     if (special6 == SPECIAL_TEQ) {
2879     if (cpu->cd.mips.gpr[rs] == cpu->cd.mips.gpr[rt])
2880     mips_cpu_exception(cpu, EXCEPTION_TR, 0, 0, 0, 0, 0, 0);
2881     break;
2882     }
2883     if (special6 == SPECIAL_TNE) {
2884     if (cpu->cd.mips.gpr[rs] != cpu->cd.mips.gpr[rt])
2885     mips_cpu_exception(cpu, EXCEPTION_TR, 0, 0, 0, 0, 0, 0);
2886     break;
2887     }
2888     if (special6 == SPECIAL_DADD) {
2889     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs] + cpu->cd.mips.gpr[rt];
2890     /* TODO: exception on overflow */
2891     break;
2892     }
2893     if (special6 == SPECIAL_DADDU) {
2894     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs] + cpu->cd.mips.gpr[rt];
2895     break;
2896     }
2897     if (special6 == SPECIAL_DSUB) {
2898     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs] - cpu->cd.mips.gpr[rt];
2899     /* TODO: exception on overflow */
2900     break;
2901     }
2902     if (special6 == SPECIAL_DSUBU) {
2903     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs] - cpu->cd.mips.gpr[rt];
2904     break;
2905     }
2906     if (special6 == SPECIAL_MOVZ) {
2907     if (cpu->cd.mips.gpr[rt] == 0)
2908     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs];
2909     break;
2910     }
2911     if (special6 == SPECIAL_MOVN) {
2912     if (cpu->cd.mips.gpr[rt] != 0)
2913     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs];
2914     return 1;
2915     }
2916     return 1;
2917     case SPECIAL_SYNC:
2918     /* imm = ((instr[1] & 7) << 2) + (instr[0] >> 6); */
2919     /* TODO: actually sync */
2920    
2921     /* Clear the LLbit (at least on R10000): */
2922     cpu->cd.mips.rmw = 0;
2923     return 1;
2924     case SPECIAL_SYSCALL:
2925     imm = ((instr[3] << 24) + (instr[2] << 16) +
2926     (instr[1] << 8) + instr[0]) >> 6;
2927     imm &= 0xfffff;
2928    
2929     if (cpu->machine->userland_emul != NULL)
2930     useremul_syscall(cpu, imm);
2931     else
2932     mips_cpu_exception(cpu, EXCEPTION_SYS,
2933     0, 0, 0, 0, 0, 0);
2934     return 1;
2935     case SPECIAL_BREAK:
2936     mips_cpu_exception(cpu, EXCEPTION_BP, 0, 0, 0, 0, 0, 0);
2937     return 1;
2938     case SPECIAL_MFSA:
2939     /* R5900? Move from shift amount register? */
2940     /* rd = (instr[1] >> 3) & 31; */
2941     /* TODO */
2942     return 1;
2943     case SPECIAL_MTSA:
2944     /* R5900? Move to shift amount register? */
2945     /* rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7); */
2946     /* TODO */
2947     return 1;
2948     default:
2949     if (!instruction_trace_cached) {
2950     fatal("cpu%i @ %016llx: %02x%02x%02x%02x%s\t",
2951     cpu->cpu_id, (long long)cpu->cd.mips.pc_last,
2952     instr[3], instr[2], instr[1], instr[0], cpu_flags(cpu));
2953     }
2954     fatal("unimplemented special6 = 0x%02x\n", special6);
2955     cpu->running = 0;
2956     return 1;
2957     }
2958     return 1;
2959     case HI6_BEQ:
2960     case HI6_BEQL:
2961     case HI6_BNE:
2962     case HI6_BGTZ:
2963     case HI6_BGTZL:
2964     case HI6_BLEZ:
2965     case HI6_BLEZL:
2966     case HI6_BNEL:
2967     case HI6_ADDI:
2968     case HI6_ADDIU:
2969     case HI6_DADDI:
2970     case HI6_DADDIU:
2971     case HI6_SLTI:
2972     case HI6_SLTIU:
2973     case HI6_ANDI:
2974     case HI6_ORI:
2975     case HI6_XORI:
2976     case HI6_LUI:
2977     case HI6_LB:
2978     case HI6_LBU:
2979     case HI6_LH:
2980     case HI6_LHU:
2981     case HI6_LW:
2982     case HI6_LWU:
2983     case HI6_LD:
2984     case HI6_LQ_MDMX:
2985     case HI6_LWC1:
2986     case HI6_LWC2:
2987     case HI6_LWC3:
2988     case HI6_LDC1:
2989     case HI6_LDC2:
2990     case HI6_LL:
2991     case HI6_LLD:
2992     case HI6_SB:
2993     case HI6_SH:
2994     case HI6_SW:
2995     case HI6_SD:
2996     case HI6_SQ:
2997     case HI6_SC:
2998     case HI6_SCD:
2999     case HI6_SWC1:
3000     case HI6_SWC2:
3001     case HI6_SWC3:
3002     case HI6_SDC1:
3003     case HI6_SDC2:
3004     case HI6_LWL: /* Unaligned load/store */
3005     case HI6_LWR:
3006     case HI6_LDL:
3007     case HI6_LDR:
3008     case HI6_SWL:
3009     case HI6_SWR:
3010     case HI6_SDL:
3011     case HI6_SDR:
3012     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
3013     rt = instr[2] & 31;
3014     imm = (instr[1] << 8) + instr[0];
3015     if (imm >= 32768) /* signed 16-bit */
3016     imm -= 65536;
3017    
3018     tmpvalue = imm; /* used later in several cases */
3019    
3020     switch (hi6) {
3021     case HI6_ADDI:
3022     case HI6_ADDIU:
3023     case HI6_DADDI:
3024     case HI6_DADDIU:
3025     tmpvalue = cpu->cd.mips.gpr[rs];
3026     result_value = cpu->cd.mips.gpr[rs] + imm;
3027    
3028     if (hi6 == HI6_ADDI || hi6 == HI6_DADDI) {
3029     /*
3030     * addi and daddi should trap on overflow:
3031     *
3032     * TODO: This is incorrect? The R4000 manual
3033     * says that overflow occurs if the carry bits
3034     * out of bit 62 and 63 differ. The
3035     * destination register should not be modified
3036     * on overflow.
3037     */
3038     if (imm >= 0) {
3039     /* Turn around from 0x7fff.. to 0x800 ? Then overflow. */
3040     if ( ((hi6 == HI6_ADDI && (result_value &
3041     0x80000000ULL) && (tmpvalue &
3042     0x80000000ULL)==0))
3043     || ((hi6 == HI6_DADDI && (result_value &
3044     0x8000000000000000ULL) && (tmpvalue &
3045     0x8000000000000000ULL)==0)) ) {
3046     mips_cpu_exception(cpu, EXCEPTION_OV, 0, 0, 0, 0, 0, 0);
3047     break;
3048     }
3049     } else {
3050     /* Turn around from 0x8000.. to 0x7fff.. ? Then overflow. */
3051     if ( ((hi6 == HI6_ADDI && (result_value &
3052     0x80000000ULL)==0 && (tmpvalue &
3053     0x80000000ULL)))
3054     || ((hi6 == HI6_DADDI && (result_value &
3055     0x8000000000000000ULL)==0 && (tmpvalue &
3056     0x8000000000000000ULL))) ) {
3057     mips_cpu_exception(cpu, EXCEPTION_OV, 0, 0, 0, 0, 0, 0);
3058     break;
3059     }
3060     }
3061     }
3062    
3063     cpu->cd.mips.gpr[rt] = result_value;
3064    
3065     /*
3066     * Super-ugly speed-hack: (only if speed_tricks != 0)
3067     * NOTE: This makes the emulation less correct.
3068     *
3069     * If we encounter a loop such as:
3070     *
3071     * 8012f5f4: 1c40ffff bgtz r0,r2,ffffffff8012f5f4
3072     * 8012f5f8: 2442ffff (d) addiu r2,r2,-1
3073     *
3074     * then it is a small loop which simply waits for r2
3075     * to become zero.
3076     *
3077     * TODO: increaste the count register, and cause
3078     * interrupts!!! For now: return as if we just
3079     * executed 1 instruction.
3080     */
3081     ninstrs_executed = 1;
3082     if (cpu->machine->speed_tricks && cpu->cd.mips.delay_slot &&
3083     cpu->cd.mips.last_was_jumptoself &&
3084     cpu->cd.mips.jump_to_self_reg == rt &&
3085     cpu->cd.mips.jump_to_self_reg == rs) {
3086     if ((int64_t)cpu->cd.mips.gpr[rt] > 1 && (int64_t)cpu->cd.mips.gpr[rt] < 0x70000000
3087     && (imm >= -30000 && imm <= -1)) {
3088     if (instruction_trace_cached)
3089     debug("changing r%i from %016llx to", rt, (long long)cpu->cd.mips.gpr[rt]);
3090    
3091     while ((int64_t)cpu->cd.mips.gpr[rt] > 0 && ninstrs_executed < 1000
3092     && ((int64_t)cpu->cd.mips.gpr[rt] + (int64_t)imm) > 0) {
3093     cpu->cd.mips.gpr[rt] += (int64_t)imm;
3094     ninstrs_executed += 2;
3095     }
3096    
3097     if (instruction_trace_cached)
3098     debug(" %016llx\n", (long long)cpu->cd.mips.gpr[rt]);
3099    
3100     /* TODO: return value, cpu->cd.mips.gpr[rt] * 2; */
3101     }
3102     if ((int64_t)cpu->cd.mips.gpr[rt] > -0x70000000 && (int64_t)cpu->cd.mips.gpr[rt] < -1
3103     && (imm >= 1 && imm <= 30000)) {
3104     if (instruction_trace_cached)
3105     debug("changing r%i from %016llx to", rt, (long long)cpu->cd.mips.gpr[rt]);
3106    
3107     while ((int64_t)cpu->cd.mips.gpr[rt] < 0 && ninstrs_executed < 1000
3108     && ((int64_t)cpu->cd.mips.gpr[rt] + (int64_t)imm) < 0) {
3109     cpu->cd.mips.gpr[rt] += (int64_t)imm;
3110     ninstrs_executed += 2;
3111     }
3112    
3113     if (instruction_trace_cached)
3114     debug(" %016llx\n", (long long)cpu->cd.mips.gpr[rt]);
3115     }
3116     }
3117    
3118     if (hi6 == HI6_ADDI || hi6 == HI6_ADDIU) {
3119     /* Sign-extend: */
3120     cpu->cd.mips.gpr[rt] &= 0xffffffffULL;
3121     if (cpu->cd.mips.gpr[rt] & 0x80000000ULL)
3122     cpu->cd.mips.gpr[rt] |= 0xffffffff00000000ULL;
3123     }
3124     return ninstrs_executed;
3125     case HI6_BEQ:
3126     case HI6_BNE:
3127     case HI6_BGTZ:
3128     case HI6_BGTZL:
3129     case HI6_BLEZ:
3130     case HI6_BLEZL:
3131     case HI6_BEQL:
3132     case HI6_BNEL:
3133     if (cpu->cd.mips.delay_slot) {
3134     fatal("b*: jump inside a jump's delay slot, or similar. TODO\n");
3135     cpu->running = 0;
3136     return 1;
3137     }
3138     likely = cond = 0;
3139     switch (hi6) {
3140     case HI6_BNEL: likely = 1;
3141     case HI6_BNE: cond = (cpu->cd.mips.gpr[rt] != cpu->cd.mips.gpr[rs]);
3142     break;
3143     case HI6_BEQL: likely = 1;
3144     case HI6_BEQ: cond = (cpu->cd.mips.gpr[rt] == cpu->cd.mips.gpr[rs]);
3145     break;
3146     case HI6_BLEZL: likely = 1;
3147     case HI6_BLEZ: cond = ((int64_t)cpu->cd.mips.gpr[rs] <= 0);
3148     break;
3149     case HI6_BGTZL: likely = 1;
3150     case HI6_BGTZ: cond = ((int64_t)cpu->cd.mips.gpr[rs] > 0);
3151     break;
3152     }
3153    
3154     if (cond) {
3155     cpu->cd.mips.delay_slot = TO_BE_DELAYED;
3156     cpu->cd.mips.delay_jmpaddr = cached_pc + (imm << 2);
3157     } else {
3158     if (likely)
3159     cpu->cd.mips.nullify_next = 1; /* nullify delay slot */
3160     }
3161    
3162     if (imm==-1 && (hi6 == HI6_BGTZ || hi6 == HI6_BLEZ ||
3163     (hi6 == HI6_BGTZL && cond) ||
3164     (hi6 == HI6_BLEZL && cond) ||
3165     (hi6 == HI6_BNE && (rt==0 || rs==0)) ||
3166     (hi6 == HI6_BEQ && (rt==0 || rs==0)))) {
3167     cpu->cd.mips.last_was_jumptoself = 2;
3168     if (rs == 0)
3169     cpu->cd.mips.jump_to_self_reg = rt;
3170     else
3171     cpu->cd.mips.jump_to_self_reg = rs;
3172     }
3173     return 1;
3174     case HI6_LUI:
3175     cpu->cd.mips.gpr[rt] = (imm << 16);
3176     /* No sign-extending necessary, as imm already
3177     was sign-extended if it was negative. */
3178     break;
3179     case HI6_SLTI:
3180     cpu->cd.mips.gpr[rt] = (int64_t)cpu->cd.mips.gpr[rs] < (int64_t)tmpvalue;
3181     break;
3182     case HI6_SLTIU:
3183     cpu->cd.mips.gpr[rt] = cpu->cd.mips.gpr[rs] < (uint64_t)imm;
3184     break;
3185     case HI6_ANDI:
3186     cpu->cd.mips.gpr[rt] = cpu->cd.mips.gpr[rs] & (tmpvalue & 0xffff);
3187     break;
3188     case HI6_ORI:
3189     cpu->cd.mips.gpr[rt] = cpu->cd.mips.gpr[rs] | (tmpvalue & 0xffff);
3190     break;
3191     case HI6_XORI:
3192     cpu->cd.mips.gpr[rt] = cpu->cd.mips.gpr[rs] ^ (tmpvalue & 0xffff);
3193     break;
3194     case HI6_LB:
3195     case HI6_LBU:
3196     case HI6_LH:
3197     case HI6_LHU:
3198     case HI6_LW:
3199     case HI6_LWU:
3200     case HI6_LD:
3201     case HI6_LQ_MDMX:
3202     case HI6_LWC1:
3203     case HI6_LWC2:
3204     case HI6_LWC3: /* pref */
3205     case HI6_LDC1:
3206     case HI6_LDC2:
3207     case HI6_LL:
3208     case HI6_LLD:
3209     case HI6_SB:
3210     case HI6_SH:
3211     case HI6_SW:
3212     case HI6_SD:
3213     case HI6_SQ:
3214     case HI6_SC:
3215     case HI6_SCD:
3216     case HI6_SWC1:
3217     case HI6_SWC2:
3218     case HI6_SWC3:
3219     case HI6_SDC1:
3220     case HI6_SDC2:
3221     /* These are the default "assumptions". */
3222     linked = 0;
3223     st = 1;
3224     signd = 1;
3225     wlen = 4;
3226    
3227     switch (hi6) {
3228     /* The most common ones: */
3229     case HI6_LW: { st = 0; } break;
3230     case HI6_SW: { signd = 0; } break;
3231    
3232     case HI6_LB: { wlen = 1; st = 0; } break;
3233     case HI6_LBU: { wlen = 1; st = 0; signd = 0; } break;
3234     case HI6_SB: { wlen = 1; signd = 0; } break;
3235    
3236     case HI6_LD: { wlen = 8; st = 0; signd = 0; } break;
3237     case HI6_SD: { wlen = 8; signd = 0; } break;
3238    
3239     case HI6_LQ_MDMX: { wlen = 16; st = 0; signd = 0; } break; /* R5900, otherwise MDMX (TODO) */
3240     case HI6_SQ: { wlen = 16; signd = 0; } break; /* R5900 ? */
3241    
3242     /* The rest: */
3243     case HI6_LH: { wlen = 2; st = 0; } break;
3244     case HI6_LHU: { wlen = 2; st = 0; signd = 0; } break;
3245     case HI6_LWU: { st = 0; signd = 0; } break;
3246     case HI6_LWC1: { st = 0; } break;
3247     case HI6_LWC2: { st = 0; } break;
3248     case HI6_LWC3: { st = 0; } break;
3249     case HI6_LDC1: { wlen = 8; st = 0; signd = 0; } break;
3250     case HI6_LDC2: { wlen = 8; st = 0; signd = 0; } break;
3251    
3252     case HI6_SH: { wlen = 2; signd = 0; } break;
3253     case HI6_SDC1:
3254     case HI6_SDC2: wlen = 8;
3255     case HI6_SWC1:
3256     case HI6_SWC2:
3257     case HI6_SWC3: { signd = 0; } break;
3258    
3259     case HI6_LL: { st = 0; signd = 1; linked = 1; } break;
3260     case HI6_LLD: { wlen = 8; st = 0; signd = 0; linked = 1; } break;
3261    
3262     case HI6_SC: { signd = 1; linked = 1; } break;
3263     case HI6_SCD: { wlen = 8; signd = 0; linked = 1; } break;
3264    
3265     default:
3266     fatal("cannot be here\n");
3267     wlen = 4; st = 0; signd = 0;
3268     }
3269    
3270     /*
3271     * In the MIPS IV ISA, the 'lwc3' instruction is changed into 'pref'.
3272     * The pref instruction is emulated by not doing anything. :-) TODO
3273     */
3274     if (hi6 == HI6_LWC3 && cpu->cd.mips.cpu_type.isa_level >= 4) {
3275     /* Clear the LLbit (at least on R10000): */
3276     cpu->cd.mips.rmw = 0;
3277     break;
3278     }
3279    
3280     addr = cpu->cd.mips.gpr[rs] + imm;
3281    
3282     /* Check for natural alignment: */
3283     if ((addr & (wlen - 1)) != 0) {
3284     mips_cpu_exception(cpu, st? EXCEPTION_ADES : EXCEPTION_ADEL,
3285     0, addr, 0, 0, 0, 0);
3286     break;
3287     }
3288    
3289     #if 0
3290     if (cpu->cd.mips.cpu_type.isa_level == 4 && (imm & (wlen - 1)) != 0)
3291     debug("WARNING: low bits of imm value not zero! (MIPS IV) "
3292     "pc=%016llx", (long long)cpu->cd.mips.pc_last);
3293     #endif
3294    
3295     /*
3296     * Load Linked: This initiates a Read-Modify-Write
3297     * sequence.
3298     */
3299     if (linked) {
3300     if (st==0) {
3301     /* st == 0: Load */
3302     cpu->cd.mips.rmw = 1;
3303     cpu->cd.mips.rmw_addr = addr;
3304     cpu->cd.mips.rmw_len = wlen;
3305    
3306     /*
3307     * COP0_LLADDR is updated for
3308     * diagnostic purposes, except for
3309     * CPUs in the R10000 family.
3310     */
3311     if (cpu->cd.mips.cpu_type.exc_model != MMU10K)
3312     cp0->reg[COP0_LLADDR] =
3313     (addr >> 4) & 0xffffffffULL;
3314     } else {
3315     /*
3316     * st == 1: Store
3317     * If rmw is 0, then the store failed.
3318     * (This cache-line was written to by
3319     * someone else.)
3320     */
3321     if (cpu->cd.mips.rmw == 0 ||
3322     cpu->cd.mips.rmw_addr != addr ||
3323     cpu->cd.mips.rmw_len != wlen) {
3324     /* The store failed: */
3325     cpu->cd.mips.gpr[rt] = 0;
3326     if (instruction_trace_cached)
3327     debug(" [COLLISION] ");
3328     break;
3329     }
3330     }
3331     } else {
3332     /*
3333     * If any kind of load or store occurs between
3334     * an ll and an sc, then the ll-sc sequence
3335     * should fail. (This is local to each cpu.)
3336     */
3337     cpu->cd.mips.rmw = 0;
3338     }
3339    
3340     value_hi = 0;
3341    
3342     if (st) {
3343     /* store: */
3344     int cpnr, success;
3345    
3346     if (hi6 == HI6_SWC3 || hi6 == HI6_SWC2 ||
3347     hi6 == HI6_SDC1 || hi6 == HI6_SWC1) {
3348     cpnr = 1;
3349     switch (hi6) {
3350     case HI6_SWC3: cpnr++; /* fallthrough */
3351     case HI6_SWC2: cpnr++;
3352     case HI6_SDC1:
3353     case HI6_SWC1: if (cpu->cd.mips.coproc[cpnr] == NULL ||
3354     (!(cp0->reg[COP0_STATUS] & ((1 << cpnr) << STATUS_CU_SHIFT))) ) {
3355     mips_cpu_exception(cpu, EXCEPTION_CPU, 0, 0, cpnr, 0, 0, 0);
3356     cpnr = -1;
3357     break;
3358     } else {
3359     /* Special handling of 64-bit stores
3360     on 32-bit CPUs, and on newer CPUs
3361     in 32-bit compatiblity mode: */
3362     if ((hi6==HI6_SDC1 || hi6==HI6_SDC2) &&
3363     (cpu->cd.mips.cpu_type.isa_level <= 2 ||
3364     !(cp0->reg[COP0_STATUS] & STATUS_FR))) {
3365     uint64_t a, b;
3366     coproc_register_read(cpu,
3367     cpu->cd.mips.coproc[cpnr], rt, &a, 0);
3368     coproc_register_read(cpu,
3369     cpu->cd.mips.coproc[cpnr], rt^1, &b, 0);
3370     if (rt & 1)
3371     fatal("WARNING: SDCx in 32-bit mode from odd register!\n");
3372     value = (a & 0xffffffffULL)
3373     | (b << 32);
3374     } else
3375     coproc_register_read(cpu, cpu->cd.mips.coproc[cpnr], rt, &value, 0);
3376     }
3377     break;
3378     default:
3379     ;
3380     }
3381     if (cpnr < 0)
3382     break;
3383     } else
3384     value = cpu->cd.mips.gpr[rt];
3385    
3386     if (wlen == 4) {
3387     /* Special case for 32-bit stores... (perhaps not worth it) */
3388     if (cpu->byte_order == EMUL_LITTLE_ENDIAN) {
3389     d[0] = value & 0xff; d[1] = (value >> 8) & 0xff;
3390     d[2] = (value >> 16) & 0xff; d[3] = (value >> 24) & 0xff;
3391     } else {
3392     d[3] = value & 0xff; d[2] = (value >> 8) & 0xff;
3393     d[1] = (value >> 16) & 0xff; d[0] = (value >> 24) & 0xff;
3394     }
3395     } else if (wlen == 16) {
3396     value_hi = cpu->cd.mips.gpr_quadhi[rt];
3397     /* Special case for R5900 128-bit stores: */
3398     if (cpu->byte_order == EMUL_LITTLE_ENDIAN)
3399     for (i=0; i<8; i++) {
3400     d[i] = (value >> (i*8)) & 255;
3401     d[i+8] = (value_hi >> (i*8)) & 255;
3402     }
3403     else
3404     for (i=0; i<8; i++) {
3405     d[i] = (value >> ((wlen-1-i)*8)) & 255;
3406     d[i + 8] = (value_hi >> ((wlen-1-i)*8)) & 255;
3407     }
3408     } else if (wlen == 1) {
3409     d[0] = value & 0xff;
3410     } else {
3411     /* General case: */
3412     uint64_t v = value;
3413     if (cpu->byte_order ==
3414     EMUL_LITTLE_ENDIAN)
3415     for (i=0; i<wlen; i++) {
3416     d[i] = v & 255;
3417     v >>= 8;
3418     }
3419     else
3420     for (i=0; i<wlen; i++) {
3421     d[wlen-1-i] = v & 255;
3422     v >>= 8;
3423     }
3424     }
3425    
3426     success = cpu->memory_rw(cpu, cpu->mem, addr,
3427     d, wlen, MEM_WRITE, CACHE_DATA);
3428     if (!success) {
3429     /* The store failed, and might have caused an exception. */
3430     if (instruction_trace_cached)
3431     debug("(failed)]\n");
3432     break;
3433     }
3434     } else {
3435     /* load: */
3436     int cpnr = 1;
3437     int success;
3438    
3439     success = cpu->memory_rw(cpu, cpu->mem, addr,
3440     d, wlen, MEM_READ, CACHE_DATA);
3441     if (!success) {
3442     /* The load failed, and might have caused an exception. */
3443     if (instruction_trace_cached)
3444     debug("(failed)]\n");
3445     break;
3446     }
3447    
3448     if (wlen == 1)
3449     value = d[0] | (signd && (d[0]&128)? (-1 << 8) : 0);
3450     else if (wlen != 16) {
3451     /* General case (except for 128-bit): */
3452     int i;
3453     value = 0;
3454     if (cpu->byte_order == EMUL_LITTLE_ENDIAN) {
3455     if (signd && (d[wlen-1] & 128)!=0) /* sign extend */
3456     value = -1;
3457     for (i=wlen-1; i>=0; i--) {
3458     value <<= 8;
3459     value += d[i];
3460     }
3461     } else {
3462     if (signd && (d[0] & 128)!=0) /* sign extend */
3463     value = -1;
3464     for (i=0; i<wlen; i++) {
3465     value <<= 8;
3466     value += d[i];
3467     }
3468     }
3469     } else {
3470     /* R5900 128-bit quadword: */
3471     int i;
3472     value_hi = 0;
3473     value = 0;
3474     if (cpu->byte_order == EMUL_LITTLE_ENDIAN) {
3475     for (i=wlen-1; i>=0; i--) {
3476     value_hi <<= 8;
3477     value_hi += (value >> 56) & 255;
3478     value <<= 8;
3479     value += d[i];
3480     }
3481     } else {
3482     for (i=0; i<wlen; i++) {
3483     value_hi <<= 8;
3484     value_hi += (value >> 56) & 255;
3485     value <<= 8;
3486     value += d[i];
3487     }
3488     }
3489     cpu->cd.mips.gpr_quadhi[rt] = value_hi;
3490     }
3491    
3492     switch (hi6) {
3493     case HI6_LWC3: cpnr++; /* fallthrough */
3494     case HI6_LDC2:
3495     case HI6_LWC2: cpnr++;
3496     case HI6_LDC1:
3497     case HI6_LWC1: if (cpu->cd.mips.coproc[cpnr] == NULL ||
3498     (!(cp0->reg[COP0_STATUS] & ((1 << cpnr) << STATUS_CU_SHIFT))) ) {
3499     mips_cpu_exception(cpu, EXCEPTION_CPU, 0, 0, cpnr, 0, 0, 0);
3500     } else {
3501     /* Special handling of 64-bit loads
3502     on 32-bit CPUs, and on newer CPUs
3503     in 32-bit compatiblity mode: */
3504     if ((hi6==HI6_LDC1 || hi6==HI6_LDC2) &&
3505     (cpu->cd.mips.cpu_type.isa_level <= 2 ||
3506     !(cp0->reg[COP0_STATUS] & STATUS_FR))) {
3507     uint64_t a, b;
3508     a = (int64_t)(int32_t) (value & 0xffffffffULL);
3509     b = (int64_t)(int32_t) (value >> 32);
3510     coproc_register_write(cpu,
3511     cpu->cd.mips.coproc[cpnr], rt, &a,
3512     hi6==HI6_LDC1 || hi6==HI6_LDC2, 0);
3513     coproc_register_write(cpu,
3514     cpu->cd.mips.coproc[cpnr], rt ^ 1, &b,
3515     hi6==HI6_LDC1 || hi6==HI6_LDC2, 0);
3516     if (rt & 1)
3517     fatal("WARNING: LDCx in 32-bit mode to odd register!\n");
3518     } else {
3519     coproc_register_write(cpu,
3520     cpu->cd.mips.coproc[cpnr], rt, &value,
3521     hi6==HI6_LDC1 || hi6==HI6_LDC2, 0);
3522     }
3523     }
3524     break;
3525     default: if (rt != 0)
3526     cpu->cd.mips.gpr[rt] = value;
3527     }
3528     }
3529    
3530     if (linked && st==1) {
3531     /*
3532     * The store succeeded. Invalidate any other
3533     * cpu's store to this cache line, and then
3534     * return 1 in gpr rt:
3535     *
3536     * (this is a semi-ugly hack using global
3537     * 'cpus')
3538     *
3539     * TODO: How about invalidating other CPUs
3540     * stores to this cache line, even if this
3541     * was _NOT_ a linked store?
3542     */
3543     for (i=0; i<cpu->machine->ncpus; i++) {
3544     if (cpu->machine->cpus[i]->cd.mips.rmw) {
3545     uint64_t yaddr = addr;
3546     uint64_t xaddr =
3547     cpu->machine->cpus[i]->cd.mips.rmw_addr;
3548     uint64_t mask;
3549     mask = ~(cpu->machine->cpus[i]->
3550     cd.mips.cache_linesize[CACHE_DATA]
3551     - 1);
3552     xaddr &= mask;
3553     yaddr &= mask;
3554     if (xaddr == yaddr) {
3555     cpu->machine->cpus[i]->cd.mips.rmw = 0;
3556     cpu->machine->cpus[i]->cd.mips.rmw_addr = 0;
3557     }
3558     }
3559     }
3560    
3561     if (rt != 0)
3562     cpu->cd.mips.gpr[rt] = 1;
3563    
3564     if (instruction_trace_cached)
3565     debug(" [no collision] ");
3566     cpu->cd.mips.rmw = 0;
3567     }
3568    
3569     if (instruction_trace_cached) {
3570     switch (wlen) {
3571     case 2: debug("0x%04x", (int)value); break;
3572     case 4: debug("0x%08x", (int)value); break;
3573     case 8: debug("0x%016llx", (long long)value);
3574     break;
3575     case 16:debug("0x%016llx", (long long)value_hi);
3576     debug("%016llx", (long long)value);
3577     break;
3578     default:debug("0x%02x", (int)value);
3579     }
3580     debug("]\n");
3581     }
3582     return 1;
3583     case HI6_LWL: /* Unaligned load/store */
3584     case HI6_LWR:
3585     case HI6_LDL:
3586     case HI6_LDR:
3587     case HI6_SWL:
3588     case HI6_SWR:
3589     case HI6_SDL:
3590     case HI6_SDR:
3591     /* For L (Left): address is the most significant byte */
3592     /* For R (Right): address is the least significant byte */
3593     addr = cpu->cd.mips.gpr[rs] + imm;
3594    
3595     is_left = 0;
3596     if (hi6 == HI6_SWL || hi6 == HI6_LWL ||
3597     hi6 == HI6_SDL || hi6 == HI6_LDL)
3598     is_left = 1;
3599    
3600     wlen = 0; st = 0;
3601     signd = 0;
3602     if (hi6 == HI6_LWL || hi6 == HI6_LWR)
3603     signd = 1;
3604    
3605     if (hi6 == HI6_LWL || hi6 == HI6_LWR) { wlen = 4; st = 0; }
3606     if (hi6 == HI6_SWL || hi6 == HI6_SWR) { wlen = 4; st = 1; }
3607     if (hi6 == HI6_LDL || hi6 == HI6_LDR) { wlen = 8; st = 0; }
3608     if (hi6 == HI6_SDL || hi6 == HI6_SDR) { wlen = 8; st = 1; }
3609    
3610     dir = 1; /* big endian, Left */
3611     reg_dir = -1;
3612     reg_ofs = wlen - 1; /* byte offset in the register */
3613     if (!is_left) {
3614     dir = -dir;
3615     reg_ofs = 0;
3616     reg_dir = 1;
3617     }
3618     if (cpu->byte_order == EMUL_LITTLE_ENDIAN)
3619     dir = -dir;
3620    
3621     result_value = cpu->cd.mips.gpr[rt];
3622    
3623     if (st) {
3624     /* Store: */
3625     uint64_t aligned_addr = addr & ~(wlen-1);
3626     unsigned char aligned_word[8];
3627     uint64_t oldpc = cpu->pc;
3628     /*
3629     * NOTE (this is ugly): The memory_rw()
3630     * call generates a TLBL exception, if there
3631     * is a tlb refill exception. However, since
3632     * this is a Store, the exception is converted
3633     * to a TLBS:
3634     */
3635     int ok = cpu->memory_rw(cpu, cpu->mem,
3636     aligned_addr, &aligned_word[0], wlen,
3637     MEM_READ, CACHE_DATA);
3638     if (!ok) {
3639     if (cpu->pc != oldpc) {
3640     cp0->reg[COP0_CAUSE] &= ~CAUSE_EXCCODE_MASK;
3641     cp0->reg[COP0_CAUSE] |= (EXCEPTION_TLBS << CAUSE_EXCCODE_SHIFT);
3642     }
3643     return 1;
3644     }
3645    
3646     for (i=0; i<wlen; i++) {
3647     tmpaddr = addr + i*dir;
3648     /* Have we moved into another word/dword? Then stop: */
3649     if ( (tmpaddr & ~(wlen-1)) != (addr & ~(wlen-1)) )
3650     break;
3651    
3652     /* debug("unaligned byte at %016llx, reg_ofs=%i reg=0x%016llx\n",
3653     tmpaddr, reg_ofs, (long long)result_value); */
3654    
3655     /* Store one byte: */
3656     aligned_word[tmpaddr & (wlen-1)] = (result_value >> (reg_ofs * 8)) & 255;
3657    
3658     reg_ofs += reg_dir;
3659     }
3660    
3661     ok = cpu->memory_rw(cpu, cpu->mem,
3662     aligned_addr, &aligned_word[0], wlen,
3663     MEM_WRITE, CACHE_DATA);
3664     if (!ok)
3665     return 1;
3666     } else {
3667     /* Load: */
3668     uint64_t aligned_addr = addr & ~(wlen-1);
3669     unsigned char aligned_word[8], databyte;
3670     int ok = cpu->memory_rw(cpu, cpu->mem,
3671     aligned_addr, &aligned_word[0], wlen,
3672     MEM_READ, CACHE_DATA);
3673     if (!ok)
3674     return 1;
3675    
3676     for (i=0; i<wlen; i++) {
3677     tmpaddr = addr + i*dir;
3678     /* Have we moved into another word/dword? Then stop: */
3679     if ( (tmpaddr & ~(wlen-1)) != (addr & ~(wlen-1)) )
3680     break;
3681    
3682     /* debug("unaligned byte at %016llx, reg_ofs=%i reg=0x%016llx\n",
3683     tmpaddr, reg_ofs, (long long)result_value); */
3684    
3685     /* Load one byte: */
3686     databyte = aligned_word[tmpaddr & (wlen-1)];
3687     result_value &= ~((uint64_t)0xff << (reg_ofs * 8));
3688     result_value |= (uint64_t)databyte << (reg_ofs * 8);
3689    
3690     reg_ofs += reg_dir;
3691     }
3692    
3693     if (rt != 0)
3694     cpu->cd.mips.gpr[rt] = result_value;
3695     }
3696    
3697     /* Sign extend for 32-bit load lefts: */
3698     if (!st && signd && wlen == 4) {
3699     cpu->cd.mips.gpr[rt] &= 0xffffffffULL;
3700     if (cpu->cd.mips.gpr[rt] & 0x80000000ULL)
3701     cpu->cd.mips.gpr[rt] |= 0xffffffff00000000ULL;
3702     }
3703    
3704     if (instruction_trace_cached) {
3705     char *t;
3706     switch (wlen) {
3707     case 2: t = "0x%04llx"; break;
3708     case 4: t = "0x%08llx"; break;
3709     case 8: t = "0x%016llx"; break;
3710     default: t = "0x%02llx";
3711     }
3712     debug(t, (long long)cpu->cd.mips.gpr[rt]);
3713     debug("]\n");
3714     }
3715    
3716     return 1;
3717     }
3718     return 1;
3719     case HI6_REGIMM:
3720     regimm5 = instr[2] & 0x1f;
3721    
3722     if (show_opcode_statistics)
3723     cpu->cd.mips.stats__regimm[regimm5] ++;
3724    
3725     switch (regimm5) {
3726     case REGIMM_BLTZ:
3727     case REGIMM_BGEZ:
3728     case REGIMM_BLTZL:
3729     case REGIMM_BGEZL:
3730     case REGIMM_BLTZAL:
3731     case REGIMM_BLTZALL:
3732     case REGIMM_BGEZAL:
3733     case REGIMM_BGEZALL:
3734     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
3735     imm = (instr[1] << 8) + instr[0];
3736     if (imm >= 32768) /* signed 16-bit */
3737     imm -= 65536;
3738    
3739     cond = and_link = likely = 0;
3740    
3741     switch (regimm5) {
3742     case REGIMM_BLTZL: likely = 1;
3743     case REGIMM_BLTZ: cond = (cpu->cd.mips.gpr[rs] & ((uint64_t)1 << 63)) != 0;
3744     break;
3745     case REGIMM_BGEZL: likely = 1;
3746     case REGIMM_BGEZ: cond = (cpu->cd.mips.gpr[rs] & ((uint64_t)1 << 63)) == 0;
3747     break;
3748    
3749     case REGIMM_BLTZALL: likely = 1;
3750     case REGIMM_BLTZAL: and_link = 1;
3751     cond = (cpu->cd.mips.gpr[rs] & ((uint64_t)1 << 63)) != 0;
3752     break;
3753     case REGIMM_BGEZALL: likely = 1;
3754     case REGIMM_BGEZAL: and_link = 1;
3755     cond = (cpu->cd.mips.gpr[rs] & ((uint64_t)1 << 63)) == 0;
3756     break;
3757     }
3758    
3759     if (and_link)
3760     cpu->cd.mips.gpr[31] = cached_pc + 4;
3761    
3762     if (cond) {
3763     cpu->cd.mips.delay_slot = TO_BE_DELAYED;
3764     cpu->cd.mips.delay_jmpaddr = cached_pc + (imm << 2);
3765     } else {
3766     if (likely)
3767     cpu->cd.mips.nullify_next = 1; /* nullify delay slot */
3768     }
3769    
3770     return 1;
3771     default:
3772     if (!instruction_trace_cached) {
3773     fatal("cpu%i @ %016llx: %02x%02x%02x%02x%s\t",
3774     cpu->cpu_id, (long long)cpu->cd.mips.pc_last,
3775     instr[3], instr[2], instr[1], instr[0], cpu_flags(cpu));
3776     }
3777     fatal("unimplemented regimm5 = 0x%02x\n", regimm5);
3778     cpu->running = 0;
3779     return 1;
3780     }
3781     /* NOT REACHED */
3782     case HI6_J:
3783     case HI6_JAL:
3784     if (cpu->cd.mips.delay_slot) {
3785     fatal("j/jal: jump inside a jump's delay slot, or similar. TODO\n");
3786     cpu->running = 0;
3787     return 1;
3788     }
3789     imm = ((instr[3] & 3) << 24) + (instr[2] << 16) + (instr[1] << 8) + instr[0];
3790     imm <<= 2;
3791    
3792     if (hi6 == HI6_JAL)
3793     cpu->cd.mips.gpr[31] = cached_pc + 4; /* pc already increased by 4 earlier */
3794    
3795     addr = cached_pc & ~((1 << 28) - 1);
3796     addr |= imm;
3797    
3798     cpu->cd.mips.delay_slot = TO_BE_DELAYED;
3799     cpu->cd.mips.delay_jmpaddr = addr;
3800    
3801     if (cpu->machine->show_trace_tree && hi6 == HI6_JAL) {
3802     cpu->cd.mips.show_trace_delay = 2;
3803     cpu->cd.mips.show_trace_addr = addr;
3804     }
3805    
3806     return 1;
3807     case HI6_COP0:
3808     case HI6_COP1:
3809     case HI6_COP2:
3810     case HI6_COP3:
3811     imm = (instr[3] << 24) + (instr[2] << 16) + (instr[1] << 8) + instr[0];
3812     imm &= ((1 << 26) - 1);
3813    
3814     cpnr = 0;
3815     if (hi6 == HI6_COP0) cpnr = 0;
3816     if (hi6 == HI6_COP1) cpnr = 1;
3817     if (hi6 == HI6_COP2) cpnr = 2;
3818     if (hi6 == HI6_COP3) cpnr = 3;
3819    
3820     /*
3821     * If there is no coprocessor nr cpnr, or we are running in
3822     * userland and the coprocessor is not marked as Useable in
3823     * the status register of CP0, then we get an exception.
3824     *
3825     * An exception (hehe) to this rule is that the kernel should
3826     * always be able to access CP0.
3827     */
3828     /* Set tmp = 1 if we're in user mode. */
3829     tmp = 0;
3830     switch (cpu->cd.mips.cpu_type.exc_model) {
3831     case EXC3K:
3832     /*
3833     * NOTE: If the KU bit is checked, Linux crashes.
3834     * It is the PC that counts. TODO: Check whether
3835     * this is true or not for R4000 as well.
3836     */
3837     if (cached_pc <= 0x7fffffff) /* if (cp0->reg[COP0_STATUS] & MIPS1_SR_KU_CUR) */
3838     tmp = 1;
3839     break;
3840     default:
3841     /* R4000 etc: (TODO: How about supervisor mode?) */
3842     if (((cp0->reg[COP0_STATUS] & STATUS_KSU_MASK) >> STATUS_KSU_SHIFT) != KSU_KERNEL)
3843     tmp = 1;
3844     if (cp0->reg[COP0_STATUS] & STATUS_ERL)
3845     tmp = 0;
3846     if (cp0->reg[COP0_STATUS] & STATUS_EXL)
3847     tmp = 0;
3848     break;
3849     }
3850     if (cpu->cd.mips.coproc[cpnr] == NULL ||
3851     (tmp && !(cp0->reg[COP0_STATUS] & ((1 << cpnr) << STATUS_CU_SHIFT))) ||
3852     (!tmp && cpnr >= 1 && !(cp0->reg[COP0_STATUS] & ((1 << cpnr) << STATUS_CU_SHIFT)))
3853     ) {
3854     if (instruction_trace_cached)
3855     debug("cop%i\t0x%08x => coprocessor unusable\n", cpnr, (int)imm);
3856     mips_cpu_exception(cpu, EXCEPTION_CPU, 0, 0, cpnr, 0, 0, 0);
3857     } else {
3858     /*
3859     * Execute the coprocessor function. The
3860     * coproc_function code outputs instruction
3861     * trace, if necessary.
3862     */
3863     coproc_function(cpu, cpu->cd.mips.coproc[cpnr],
3864     cpnr, imm, 0, 1);
3865     }
3866     return 1;
3867     case HI6_CACHE:
3868     rt = ((instr[3] & 3) << 3) + (instr[2] >> 5); /* base */
3869     copz = instr[2] & 31;
3870     imm = (instr[1] << 8) + instr[0];
3871    
3872     cache_op = copz >> 2;
3873     which_cache = copz & 3;
3874    
3875     /*
3876     * TODO: The cache instruction is implementation dependant.
3877     */
3878    
3879     /*
3880     * Clear the LLbit (at least on R10000):
3881     * TODO: How about R4000?
3882     */
3883     cpu->cd.mips.rmw = 0;
3884    
3885     return 1;
3886     case HI6_SPECIAL2:
3887     special6 = instr[0] & 0x3f;
3888    
3889     if (show_opcode_statistics)
3890     cpu->cd.mips.stats__special2[special6] ++;
3891    
3892     instrword = (instr[3] << 24) + (instr[2] << 16) + (instr[1] << 8) + instr[0];
3893    
3894     rs = ((instr[3] & 3) << 3) + ((instr[2] >> 5) & 7);
3895     rt = instr[2] & 31;
3896     rd = (instr[1] >> 3) & 31;
3897    
3898     /* printf("special2 %08x rs=0x%02x rt=0x%02x rd=0x%02x\n", instrword, rs,rt,rd); */
3899    
3900     /*
3901     * Many of these can be found in the R5000 docs, or figured out
3902     * by studying binutils source code for MIPS instructions.
3903     */
3904    
3905     if ((instrword & 0xfc0007ffULL) == 0x70000000) {
3906     {
3907     int32_t a, b;
3908     int64_t c;
3909     a = (int32_t)cpu->cd.mips.gpr[rs];
3910     b = (int32_t)cpu->cd.mips.gpr[rt];
3911     c = a * b;
3912     c += (cpu->cd.mips.lo & 0xffffffffULL)
3913     + (cpu->cd.mips.hi << 32);
3914     cpu->cd.mips.lo = (int64_t)((int32_t)c);
3915     cpu->cd.mips.hi = (int64_t)((int32_t)(c >> 32));
3916    
3917     /*
3918     * The R5000 manual says that rd should be all zeros,
3919     * but it isn't on R5900. I'm just guessing here that
3920     * it stores the value in register rd, in addition to hi/lo.
3921     * TODO
3922     */
3923     if (rd != 0)
3924     cpu->cd.mips.gpr[rd] = cpu->cd.mips.lo;
3925     }
3926     } else if ((instrword & 0xffff07ffULL) == 0x70000209
3927     || (instrword & 0xffff07ffULL) == 0x70000249) {
3928     /*
3929     * This is just a guess for R5900, I've not found any docs on this one yet.
3930     *
3931     * pmfhi/pmflo rd
3932     *
3933     * If the lowest 8 bits of the instruction word are 0x09, it's a pmfhi.
3934     * If the lowest bits are 0x49, it's a pmflo.
3935     *
3936     * A wild guess is that this is a 128-bit version of mfhi/mflo.
3937     * For now, this is implemented as 64-bit only. (TODO)
3938     */
3939     if (instr[0] == 0x49) {
3940     cpu->cd.mips.gpr[rd] = cpu->cd.mips.lo;
3941     } else {
3942     cpu->cd.mips.gpr[rd] = cpu->cd.mips.hi;
3943     }
3944     } else if ((instrword & 0xfc1fffff) == 0x70000269 || (instrword & 0xfc1fffff) == 0x70000229) {
3945     /*
3946     * This is just a guess for R5900, I've not found any docs on this one yet.
3947     *
3948     * pmthi/pmtlo rs (pmtlo = 269, pmthi = 229)
3949     *
3950     * A wild guess is that this is a 128-bit version of mthi/mtlo.
3951     * For now, this is implemented as 64-bit only. (TODO)
3952     */
3953     if (instr[0] == 0x69) {
3954     cpu->cd.mips.lo = cpu->cd.mips.gpr[rs];
3955     } else {
3956     cpu->cd.mips.hi = cpu->cd.mips.gpr[rs];
3957     }
3958     } else if ((instrword & 0xfc0007ff) == 0x700004a9) {
3959     /*
3960     * This is just a guess for R5900, I've not found any docs on this one yet.
3961     *
3962     * por dst,src,src2 ==> rs=src rt=src2 rd=dst
3963     *
3964     * A wild guess is that this is a 128-bit "or" between two registers.
3965     * For now, let's just or using 64-bits. (TODO)
3966     */
3967     cpu->cd.mips.gpr[rd] = cpu->cd.mips.gpr[rs] | cpu->cd.mips.gpr[rt];
3968     } else if ((instrword & 0xfc0007ff) == 0x70000488) {
3969     /*
3970     * R5900 "undocumented" pextlw. TODO: find out if this is correct.
3971     * It seems that this instruction is used to combine two 32-bit
3972     * words into a 64-bit dword, typically before a sd (store dword).
3973     */
3974     cpu->cd.mips.gpr[rd] =
3975     ((cpu->cd.mips.gpr[rs] & 0xffffffffULL) << 32) /* TODO: switch rt and rs? */
3976     | (cpu->cd.mips.gpr[rt] & 0xffffffffULL);
3977     } else if (special6 == SPECIAL2_MUL) {
3978     cpu->cd.mips.gpr[rd] = (int64_t)cpu->cd.mips.gpr[rt] *
3979     (int64_t)cpu->cd.mips.gpr[rs];
3980     } else if (special6 == SPECIAL2_CLZ) {
3981     /* clz: count leading zeroes */
3982     int i, n=0;
3983     for (i=31; i>=0; i--) {
3984     if (cpu->cd.mips.gpr[rs] & ((uint32_t)1 << i))
3985     break;
3986     else
3987     n++;
3988     }
3989     cpu->cd.mips.gpr[rd] = n;
3990     } else if (special6 == SPECIAL2_CLO) {
3991     /* clo: count leading ones */
3992     int i, n=0;
3993     for (i=31; i>=0; i--) {
3994     if (cpu->cd.mips.gpr[rs] & ((uint32_t)1 << i))
3995     n++;
3996     else
3997     break;
3998     }
3999     cpu->cd.mips.gpr[rd] = n;
4000     } else if (special6 == SPECIAL2_DCLZ) {
4001     /* dclz: count leading zeroes */
4002     int i, n=0;
4003     for (i=63; i>=0; i--) {
4004     if (cpu->cd.mips.gpr[rs] & ((uint64_t)1 << i))
4005     break;
4006     else
4007     n++;
4008     }
4009     cpu->cd.mips.gpr[rd] = n;
4010     } else if (special6 == SPECIAL2_DCLO) {
4011     /* dclo: count leading ones */
4012     int i, n=0;
4013     for (i=63; i>=0; i--) {
4014     if (cpu->cd.mips.gpr[rs] & ((uint64_t)1 << i))
4015     n++;
4016     else
4017     break;
4018     }
4019     cpu->cd.mips.gpr[rd] = n;
4020     } else {
4021     if (!instruction_trace_cached) {
4022     fatal("cpu%i @ %016llx: %02x%02x%02x%02x%s\t",
4023     cpu->cpu_id, (long long)cpu->cd.mips.pc_last,
4024     instr[3], instr[2], instr[1], instr[0], cpu_flags(cpu));
4025     }
4026     fatal("unimplemented special_2 = 0x%02x, rs=0x%02x rt=0x%02x rd=0x%02x\n",
4027     special6, rs, rt, rd);
4028     cpu->running = 0;
4029     return 1;
4030     }
4031     return 1;
4032     default:
4033     if (!instruction_trace_cached) {
4034     fatal("cpu%i @ %016llx: %02x%02x%02x%02x%s\t",
4035     cpu->cpu_id, (long long)cpu->cd.mips.pc_last,
4036     instr[3], instr[2], instr[1], instr[0], cpu_flags(cpu));
4037     }
4038     fatal("unimplemented hi6 = 0x%02x\n", hi6);
4039     cpu->running = 0;
4040     return 1;
4041     }
4042    
4043     /* NOTREACHED */
4044     }
4045    
4046    
4047     #define CPU_RUN mips_cpu_run
4048     #define CPU_RUN_MIPS
4049     #define CPU_RINSTR mips_cpu_run_instr
4050     #include "cpu_run.c"
4051     #undef CPU_RINSTR
4052     #undef CPU_RUN_MIPS
4053     #undef CPU_RUN
4054    
4055    
4056     /*
4057     * mips_cpu_dumpinfo():
4058     *
4059     * Debug dump of MIPS-specific CPU data for specific CPU.
4060     */
4061     void mips_cpu_dumpinfo(struct cpu *cpu)
4062     {
4063     int iadd = 4;
4064     struct mips_cpu_type_def *ct = &cpu->cd.mips.cpu_type;
4065    
4066     debug_indentation(iadd);
4067    
4068     debug("\n%i-bit %s (MIPS",
4069     cpu->is_32bit? 32 : 64,
4070     cpu->byte_order == EMUL_BIG_ENDIAN? "BE" : "LE");
4071    
4072     switch (ct->isa_level) {
4073     case 1: debug(" ISA I"); break;
4074     case 2: debug(" ISA II"); break;
4075     case 3: debug(" ISA III"); break;
4076     case 4: debug(" ISA IV"); break;
4077     case 5: debug(" ISA V"); break;
4078     case 32:
4079     case 64:debug("%i", ct->isa_level); break;
4080     default:debug(" ISA level %i", ct->isa_level);
4081     }
4082    
4083     debug("), ");
4084     if (ct->nr_of_tlb_entries)
4085     debug("%i TLB entries", ct->nr_of_tlb_entries);
4086     else
4087     debug("no TLB");
4088     debug("\n");
4089    
4090     if (ct->picache) {
4091     debug("L1 I-cache: %i KB", (1 << ct->picache) / 1024);
4092     if (ct->pilinesize)
4093     debug(", %i bytes per line", 1 << ct->pilinesize);
4094     if (ct->piways > 1)
4095     debug(", %i-way", ct->piways);
4096     else
4097     debug(", direct-mapped");
4098     debug("\n");
4099     }
4100    
4101     if (ct->pdcache) {
4102     debug("L1 D-cache: %i KB", (1 << ct->pdcache) / 1024);
4103     if (ct->pdlinesize)
4104     debug(", %i bytes per line", 1 << ct->pdlinesize);
4105     if (ct->pdways > 1)
4106     debug(", %i-way", ct->pdways);
4107     else
4108     debug(", direct-mapped");
4109     debug("\n");
4110     }
4111    
4112     if (ct->scache) {
4113     int kb = (1 << ct->scache) / 1024;
4114     debug("L2 cache: %i %s",
4115     kb >= 1024? kb / 1024 : kb, kb >= 1024? "MB":"KB");
4116     if (ct->slinesize)
4117     debug(", %i bytes per line", 1 << ct->slinesize);
4118     if (ct->sways > 1)
4119     debug(", %i-way", ct->sways);
4120     else
4121     debug(", direct-mapped");
4122     debug("\n");
4123     }
4124    
4125     debug_indentation(-iadd);
4126     }
4127    
4128    
4129     /*
4130     * mips_cpu_list_available_types():
4131     *
4132     * Print a list of available MIPS CPU types.
4133     */
4134     void mips_cpu_list_available_types(void)
4135     {
4136     int i, j;
4137     struct mips_cpu_type_def cpu_type_defs[] = MIPS_CPU_TYPE_DEFS;
4138    
4139     i = 0;
4140     while (cpu_type_defs[i].name != NULL) {
4141     debug("%s", cpu_type_defs[i].name);
4142     for (j=10 - strlen(cpu_type_defs[i].name); j>0; j--)
4143     debug(" ");
4144     i++;
4145     if ((i % 6) == 0 || cpu_type_defs[i].name == NULL)
4146     debug("\n");
4147     }
4148     }
4149    
4150    
4151     CPU_FAMILY_INIT(mips,"MIPS")
4152    
4153    
4154     #endif /* ENABLE_MIPS */

  ViewVC Help
Powered by ViewVC 1.1.26