/[gxemul]/trunk/src/cpus/cpu_arm.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_arm.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: 31125 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) 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_arm.c,v 1.28 2005/10/07 10:26:03 debug Exp $
29     *
30     * ARM CPU emulation.
31     *
32     * A good source of quick info on ARM instruction encoding:
33     *
34     * http://www.pinknoise.demon.co.uk/ARMinstrs/ARMinstrs.html
35     *
36     * (Most "xxxx0101..." and similar strings in this file are from that URL,
37     * or from the ARM manual.)
38     */
39    
40     #include <stdio.h>
41     #include <stdlib.h>
42     #include <string.h>
43     #include <ctype.h>
44    
45     #include "arm_cpu_types.h"
46     #include "cpu.h"
47     #include "machine.h"
48     #include "memory.h"
49     #include "misc.h"
50     #include "symbol.h"
51    
52     #define DYNTRANS_32
53     #include "tmp_arm_head.c"
54    
55    
56     /* ARM symbolic register names and condition strings: */
57     static char *arm_regname[N_ARM_REGS] = ARM_REG_NAMES;
58     static char *arm_condition_string[16] = ARM_CONDITION_STRINGS;
59    
60     /* Data Processing Instructions: */
61     static char *arm_dpiname[16] = ARM_DPI_NAMES;
62     static int arm_dpi_uses_d[16] = { 1,1,1,1,1,1,1,1,0,0,0,0,1,1,1,1 };
63     static int arm_dpi_uses_n[16] = { 1,1,1,1,1,1,1,1,1,1,1,1,1,0,1,0 };
64    
65     /* Forward reference: */
66     void arm_pc_to_pointers(struct cpu *cpu);
67    
68    
69     /*
70     * arm_cpu_new():
71     *
72     * Create a new ARM cpu object by filling the CPU struct.
73     * Return 1 on success, 0 if cpu_type_name isn't a valid ARM processor.
74     */
75     int arm_cpu_new(struct cpu *cpu, struct memory *mem,
76     struct machine *machine, int cpu_id, char *cpu_type_name)
77     {
78     int any_cache = 0, i, found;
79     struct arm_cpu_type_def cpu_type_defs[] = ARM_CPU_TYPE_DEFS;
80    
81     /* Scan the list for this cpu type: */
82     i = 0; found = -1;
83     while (i >= 0 && cpu_type_defs[i].name != NULL) {
84     if (strcasecmp(cpu_type_defs[i].name, cpu_type_name) == 0) {
85     found = i;
86     break;
87     }
88     i++;
89     }
90     if (found == -1)
91     return 0;
92    
93     cpu->memory_rw = arm_memory_rw;
94     cpu->update_translation_table = arm_update_translation_table;
95     cpu->invalidate_translation_caches_paddr =
96     arm_invalidate_translation_caches_paddr;
97     cpu->invalidate_code_translation = arm_invalidate_code_translation;
98     cpu->translate_address = arm_translate_address;
99    
100     cpu->cd.arm.cpu_type = cpu_type_defs[found];
101     cpu->name = cpu->cd.arm.cpu_type.name;
102     cpu->is_32bit = 1;
103    
104     cpu->cd.arm.cpsr = ARM_FLAG_I | ARM_FLAG_F;
105     cpu->cd.arm.control = ARM_CONTROL_PROG32 | ARM_CONTROL_DATA32
106     | ARM_CONTROL_CACHE | ARM_CONTROL_ICACHE | ARM_CONTROL_ALIGN;
107    
108     if (cpu->machine->prom_emulation) {
109     cpu->cd.arm.cpsr |= ARM_MODE_SVC32;
110     cpu->cd.arm.control |= ARM_CONTROL_S;
111     } else {
112     cpu->cd.arm.cpsr |= ARM_MODE_USR32;
113     cpu->cd.arm.control |= ARM_CONTROL_S | ARM_CONTROL_R;
114     }
115    
116     /* Only show name and caches etc for CPU nr 0: */
117     if (cpu_id == 0) {
118     debug("%s", cpu->name);
119     if (cpu->cd.arm.cpu_type.icache_shift != 0)
120     any_cache = 1;
121     if (cpu->cd.arm.cpu_type.dcache_shift != 0)
122     any_cache = 1;
123     if (any_cache) {
124     debug(" (I+D = %i+%i KB",
125     (int)(1 << (cpu->cd.arm.cpu_type.icache_shift-10)),
126     (int)(1 << (cpu->cd.arm.cpu_type.dcache_shift-10)));
127     debug(")");
128     }
129     }
130    
131     /* Coprocessor 15 = the system control coprocessor. */
132     cpu->cd.arm.coproc[15] = arm_coproc_15;
133    
134     /*
135     * NOTE/TODO: Ugly hack for OpenFirmware emulation:
136     */
137     if (cpu->machine->prom_emulation) {
138     cpu->cd.arm.of_emul_addr = cpu->machine->physical_ram_in_mb
139     * 1048576 - 8;
140     store_32bit_word(cpu, cpu->cd.arm.of_emul_addr, 0xef8c64be);
141     }
142    
143     return 1;
144     }
145    
146    
147     /*
148     * arm_setup_initial_translation_table():
149     *
150     * When booting kernels (such as OpenBSD or NetBSD) directly, it is assumed
151     * that the MMU is already enabled by the boot-loader. This function tries
152     * to emulate that.
153     */
154     void arm_setup_initial_translation_table(struct cpu *cpu, uint32_t ttb_addr)
155     {
156     unsigned char nothing[16384];
157     unsigned int i, j;
158    
159     if (cpu->machine->userland_emul != NULL) {
160     fatal("arm_setup_initial_translation_table(): should not "
161     "be called for userland emulation!\n");
162     exit(1);
163     }
164    
165     cpu->cd.arm.control |= ARM_CONTROL_MMU;
166     cpu->cd.arm.dacr |= 0x00000003;
167     cpu->cd.arm.ttb = ttb_addr;
168    
169     memset(nothing, 0, sizeof(nothing));
170     cpu->memory_rw(cpu, cpu->mem, cpu->cd.arm.ttb, nothing,
171     sizeof(nothing), MEM_WRITE, PHYSICAL | NO_EXCEPTIONS);
172     for (i=0; i<256; i++)
173     for (j=0x0; j<=0xf; j++) {
174     unsigned char descr[4];
175     uint32_t addr = cpu->cd.arm.ttb +
176     (((j << 28) + (i << 20)) >> 18);
177     uint32_t d = (1048576*i) | 0xc02;
178     /*
179     d = (1048576 * (i + (j==12? 10 : j)*256)) | 2;
180     */
181     if (cpu->byte_order == EMUL_LITTLE_ENDIAN) {
182     descr[0] = d; descr[1] = d >> 8;
183     descr[2] = d >> 16; descr[3] = d >> 24;
184     } else {
185     descr[3] = d; descr[2] = d >> 8;
186     descr[1] = d >> 16; descr[0] = d >> 24;
187     }
188     cpu->memory_rw(cpu, cpu->mem, addr, &descr[0],
189     sizeof(descr), MEM_WRITE, PHYSICAL | NO_EXCEPTIONS);
190     }
191     }
192    
193    
194     /*
195     * arm_cpu_dumpinfo():
196     */
197     void arm_cpu_dumpinfo(struct cpu *cpu)
198     {
199     struct arm_cpu_type_def *ct = &cpu->cd.arm.cpu_type;
200    
201     debug(" (I+D = %i+%i KB)\n",
202     (1 << ct->icache_shift) / 1024, (1 << ct->dcache_shift) / 1024);
203     }
204    
205    
206     /*
207     * arm_cpu_list_available_types():
208     *
209     * Print a list of available ARM CPU types.
210     */
211     void arm_cpu_list_available_types(void)
212     {
213     int i, j;
214     struct arm_cpu_type_def tdefs[] = ARM_CPU_TYPE_DEFS;
215    
216     i = 0;
217     while (tdefs[i].name != NULL) {
218     debug("%s", tdefs[i].name);
219     for (j=13 - strlen(tdefs[i].name); j>0; j--)
220     debug(" ");
221     i++;
222     if ((i % 5) == 0 || tdefs[i].name == NULL)
223     debug("\n");
224     }
225     }
226    
227    
228     /*
229     * arm_cpu_register_match():
230     */
231     void arm_cpu_register_match(struct machine *m, char *name,
232     int writeflag, uint64_t *valuep, int *match_register)
233     {
234     int i, cpunr = 0;
235    
236     /* CPU number: */
237    
238     /* TODO */
239    
240     /* Register names: */
241     for (i=0; i<N_ARM_REGS; i++) {
242     if (strcasecmp(name, arm_regname[i]) == 0) {
243     if (writeflag) {
244     m->cpus[cpunr]->cd.arm.r[i] = *valuep;
245     if (i == ARM_PC)
246     m->cpus[cpunr]->pc = *valuep;
247     } else
248     *valuep = m->cpus[cpunr]->cd.arm.r[i];
249     *match_register = 1;
250     }
251     }
252     }
253    
254    
255     /*
256     * arm_cpu_register_dump():
257     *
258     * Dump cpu registers in a relatively readable format.
259     *
260     * gprs: set to non-zero to dump GPRs and some special-purpose registers.
261     * coprocs: set bit 0..3 to dump registers in coproc 0..3.
262     */
263     void arm_cpu_register_dump(struct cpu *cpu, int gprs, int coprocs)
264     {
265     char *symbol;
266     uint64_t offset;
267     int mode = cpu->cd.arm.cpsr & ARM_FLAG_MODE;
268     int i, x = cpu->cpu_id;
269    
270     if (gprs) {
271     symbol = get_symbol_name(&cpu->machine->symbol_context,
272     cpu->cd.arm.r[ARM_PC], &offset);
273     debug("cpu%i: cpsr = ", x);
274     debug("%s%s%s%s%s%s",
275     (cpu->cd.arm.cpsr & ARM_FLAG_N)? "N" : "n",
276     (cpu->cd.arm.cpsr & ARM_FLAG_Z)? "Z" : "z",
277     (cpu->cd.arm.cpsr & ARM_FLAG_C)? "C" : "c",
278     (cpu->cd.arm.cpsr & ARM_FLAG_V)? "V" : "v",
279     (cpu->cd.arm.cpsr & ARM_FLAG_I)? "I" : "i",
280     (cpu->cd.arm.cpsr & ARM_FLAG_F)? "F" : "f");
281     if (mode < ARM_MODE_USR32)
282     debug(" pc = 0x%07x",
283     (int)(cpu->cd.arm.r[ARM_PC] & 0x03ffffff));
284     else
285     debug(" pc = 0x%08x", (int)cpu->cd.arm.r[ARM_PC]);
286    
287     debug(" <%s>\n", symbol != NULL? symbol : " no symbol ");
288    
289     for (i=0; i<N_ARM_REGS; i++) {
290     if ((i % 4) == 0)
291     debug("cpu%i:", x);
292     if (i != ARM_PC)
293     debug(" %s = 0x%08x", arm_regname[i],
294     (int)cpu->cd.arm.r[i]);
295     if ((i % 4) == 3)
296     debug("\n");
297     }
298     }
299    
300     if (coprocs & 1) {
301     int m = cpu->cd.arm.cpsr & ARM_FLAG_MODE;
302     debug("cpu%i: cpsr = 0x%08x (", x, cpu->cd.arm.cpsr);
303     switch (m) {
304     case ARM_MODE_USR32:
305     debug("USR32)\n"); break;
306     case ARM_MODE_SYS32:
307     debug("SYS32)\n"); break;
308     case ARM_MODE_FIQ32:
309     debug("FIQ32)\n"); break;
310     case ARM_MODE_IRQ32:
311     debug("IRQ32)\n"); break;
312     case ARM_MODE_SVC32:
313     debug("SVC32)\n"); break;
314     case ARM_MODE_ABT32:
315     debug("ABT32)\n"); break;
316     case ARM_MODE_UND32:
317     debug("UND32)\n"); break;
318     default:debug("unimplemented)\n");
319     }
320    
321     if (m != ARM_MODE_USR32 && m != ARM_MODE_SYS32) {
322     debug("cpu%i: usr r8..r14 =", x);
323     for (i=0; i<7; i++)
324     debug(" %08x", cpu->cd.arm.default_r8_r14[i]);
325     debug("\n");
326     }
327    
328     if (m != ARM_MODE_FIQ32) {
329     debug("cpu%i: fiq r8..r14 =", x);
330     for (i=0; i<7; i++)
331     debug(" %08x", cpu->cd.arm.fiq_r8_r14[i]);
332     debug("\n");
333     }
334    
335     if (m != ARM_MODE_IRQ32) {
336     debug("cpu%i: irq r13..r14 =", x);
337     for (i=0; i<2; i++)
338     debug(" %08x", cpu->cd.arm.irq_r13_r14[i]);
339     debug("\n");
340     }
341    
342     if (m != ARM_MODE_SVC32) {
343     debug("cpu%i: svc r13..r14 =", x);
344     for (i=0; i<2; i++)
345     debug(" %08x", cpu->cd.arm.svc_r13_r14[i]);
346     debug("\n");
347     }
348    
349     if (m != ARM_MODE_ABT32) {
350     debug("cpu%i: abt r13..r14 =", x);
351     for (i=0; i<2; i++)
352     debug(" %08x", cpu->cd.arm.abt_r13_r14[i]);
353     debug("\n");
354     }
355    
356     if (m != ARM_MODE_UND32) {
357     debug("cpu%i: und r13..r14 =", x);
358     for (i=0; i<2; i++)
359     debug(" %08x", cpu->cd.arm.und_r13_r14[i]);
360     debug("\n");
361     }
362     }
363    
364     if (coprocs & 2) {
365     debug("cpu%i: control = 0x%08x\n", x, cpu->cd.arm.control);
366     debug("cpu%i: MMU: %s\n", x,
367     cpu->cd.arm.control &
368     ARM_CONTROL_MMU? "enabled" : "disabled");
369     debug("cpu%i: alignment checks: %s\n", x,
370     cpu->cd.arm.control &
371     ARM_CONTROL_ALIGN? "enabled" : "disabled");
372     debug("cpu%i: [data] cache: %s\n", x,
373     cpu->cd.arm.control &
374     ARM_CONTROL_CACHE? "enabled" : "disabled");
375     debug("cpu%i: instruction cache: %s\n", x,
376     cpu->cd.arm.control &
377     ARM_CONTROL_ICACHE? "enabled" : "disabled");
378     debug("cpu%i: write buffer: %s\n", x,
379     cpu->cd.arm.control &
380     ARM_CONTROL_WBUFFER? "enabled" : "disabled");
381     debug("cpu%i: prog32: %s\n", x,
382     cpu->cd.arm.control &
383     ARM_CONTROL_PROG32? "yes" : "no (using prog26)");
384     debug("cpu%i: data32: %s\n", x,
385     cpu->cd.arm.control &
386     ARM_CONTROL_DATA32? "yes" : "no (using data26)");
387     debug("cpu%i: endianness: %s\n", x,
388     cpu->cd.arm.control &
389     ARM_CONTROL_BIG? "big endian" : "little endian");
390     debug("cpu%i: high vectors: %s\n", x,
391     cpu->cd.arm.control &
392     ARM_CONTROL_V? "yes (0xffff0000)" : "no");
393    
394     debug("cpu%i: ttb = 0x%08x dacr = 0x%08x\n", x,
395     cpu->cd.arm.ttb, cpu->cd.arm.dacr);
396     debug("cpu%i: fsr = 0x%08x far = 0x%08x\n", x,
397     cpu->cd.arm.fsr, cpu->cd.arm.far);
398     }
399     }
400    
401    
402     /*
403     * arm_cpu_show_full_statistics():
404     *
405     * Show detailed statistics on opcode usage on each cpu.
406     */
407     void arm_cpu_show_full_statistics(struct machine *m)
408     {
409     fatal("arm_cpu_show_full_statistics(): TODO\n");
410     }
411    
412    
413     /*
414     * arm_cpu_tlbdump():
415     *
416     * Called from the debugger to dump the TLB in a readable format.
417     * x is the cpu number to dump, or -1 to dump all CPUs.
418     *
419     * If rawflag is nonzero, then the TLB contents isn't formated nicely,
420     * just dumped.
421     */
422     void arm_cpu_tlbdump(struct machine *m, int x, int rawflag)
423     {
424     fatal("arm_cpu_tlbdump(): TODO\n");
425     }
426    
427    
428     /*
429     * arm_save_register_bank():
430     */
431     void arm_save_register_bank(struct cpu *cpu)
432     {
433     /* Save away current registers: */
434     switch (cpu->cd.arm.cpsr & ARM_FLAG_MODE) {
435     case ARM_MODE_USR32:
436     case ARM_MODE_SYS32:
437     memcpy(cpu->cd.arm.default_r8_r14,
438     &cpu->cd.arm.r[8], sizeof(uint32_t) * 7);
439     break;
440     case ARM_MODE_FIQ32:
441     memcpy(cpu->cd.arm.fiq_r8_r14,
442     &cpu->cd.arm.r[8], sizeof(uint32_t) * 7);
443     break;
444     case ARM_MODE_IRQ32:
445     cpu->cd.arm.irq_r13_r14[0] = cpu->cd.arm.r[13];
446     cpu->cd.arm.irq_r13_r14[1] = cpu->cd.arm.r[14];
447     break;
448     case ARM_MODE_SVC32:
449     if ((cpu->cd.arm.r[13] & 0xffff0000) == 0xffff0000) {
450     fatal("NEJ! pc=0x%08x\n", (int)cpu->pc);
451     exit(1);
452     }
453     cpu->cd.arm.svc_r13_r14[0] = cpu->cd.arm.r[13];
454     cpu->cd.arm.svc_r13_r14[1] = cpu->cd.arm.r[14];
455     break;
456     case ARM_MODE_ABT32:
457     cpu->cd.arm.abt_r13_r14[0] = cpu->cd.arm.r[13];
458     cpu->cd.arm.abt_r13_r14[1] = cpu->cd.arm.r[14];
459     break;
460     case ARM_MODE_UND32:
461     cpu->cd.arm.und_r13_r14[0] = cpu->cd.arm.r[13];
462     cpu->cd.arm.und_r13_r14[1] = cpu->cd.arm.r[14];
463     break;
464     default:fatal("arm_save_register_bank: unimplemented mode %i\n",
465     cpu->cd.arm.cpsr & ARM_FLAG_MODE);
466     exit(1);
467     }
468     }
469    
470    
471     /*
472     * arm_load_register_bank():
473     */
474     void arm_load_register_bank(struct cpu *cpu)
475     {
476     /* Load new registers: */
477     switch (cpu->cd.arm.cpsr & ARM_FLAG_MODE) {
478     case ARM_MODE_USR32:
479     case ARM_MODE_SYS32:
480     memcpy(&cpu->cd.arm.r[8],
481     cpu->cd.arm.default_r8_r14, sizeof(uint32_t) * 7);
482     break;
483     case ARM_MODE_FIQ32:
484     memcpy(&cpu->cd.arm.r[8], cpu->cd.arm.fiq_r8_r14,
485     sizeof(uint32_t) * 7);
486     break;
487     case ARM_MODE_IRQ32:
488     cpu->cd.arm.r[13] = cpu->cd.arm.irq_r13_r14[0];
489     cpu->cd.arm.r[14] = cpu->cd.arm.irq_r13_r14[1];
490     break;
491     case ARM_MODE_SVC32:
492     cpu->cd.arm.r[13] = cpu->cd.arm.svc_r13_r14[0];
493     cpu->cd.arm.r[14] = cpu->cd.arm.svc_r13_r14[1];
494     break;
495     case ARM_MODE_ABT32:
496     cpu->cd.arm.r[13] = cpu->cd.arm.abt_r13_r14[0];
497     cpu->cd.arm.r[14] = cpu->cd.arm.abt_r13_r14[1];
498     break;
499     case ARM_MODE_UND32:
500     cpu->cd.arm.r[13] = cpu->cd.arm.und_r13_r14[0];
501     cpu->cd.arm.r[14] = cpu->cd.arm.und_r13_r14[1];
502     break;
503     default:fatal("arm_load_register_bank: unimplemented mode %i\n",
504     cpu->cd.arm.cpsr & ARM_FLAG_MODE);
505     exit(1);
506     }
507     }
508    
509    
510     /*
511     * arm_exception():
512     */
513     void arm_exception(struct cpu *cpu, int exception_nr)
514     {
515     int arm_exception_to_mode[N_ARM_EXCEPTIONS] = ARM_EXCEPTION_TO_MODE;
516     int oldmode, newmode;
517     uint32_t retaddr;
518    
519     if (exception_nr < 0 || exception_nr >= N_ARM_EXCEPTIONS) {
520     fatal("arm_exception(): exception_nr = %i\n", exception_nr);
521     exit(1);
522     }
523    
524     retaddr = cpu->pc;
525    
526     debug("[ arm_exception(): ");
527    
528     switch (exception_nr) {
529     case ARM_EXCEPTION_RESET:
530     cpu->running = 0;
531     fatal("RESET: TODO");
532     exit(1);
533     case ARM_EXCEPTION_UND:
534     debug("UNDEFINED");
535     retaddr += 4;
536     break;
537     case ARM_EXCEPTION_SWI:
538     debug("SWI");
539     retaddr += 4;
540     break;
541     case ARM_EXCEPTION_PREF_ABT:
542     debug("PREFETCH ABORT");
543     retaddr += 4;
544     break;
545     case ARM_EXCEPTION_IRQ:
546     debug("IRQ");
547     retaddr += 4;
548     break;
549     case ARM_EXCEPTION_FIQ:
550     debug("FIQ");
551     retaddr += 4;
552     break;
553     case ARM_EXCEPTION_DATA_ABT:
554     debug("DATA ABORT, far=0x%08x fsr=0x%02x",
555     cpu->cd.arm.far, cpu->cd.arm.fsr);
556     retaddr += 8;
557     break;
558     }
559    
560     debug(" ]\n");
561    
562     arm_save_register_bank(cpu);
563    
564     switch (arm_exception_to_mode[exception_nr]) {
565     case ARM_MODE_SVC32:
566     cpu->cd.arm.spsr_svc = cpu->cd.arm.cpsr; break;
567     case ARM_MODE_ABT32:
568     cpu->cd.arm.spsr_abt = cpu->cd.arm.cpsr; break;
569     case ARM_MODE_UND32:
570     cpu->cd.arm.spsr_und = cpu->cd.arm.cpsr; break;
571     case ARM_MODE_IRQ32:
572     cpu->cd.arm.spsr_irq = cpu->cd.arm.cpsr; break;
573     case ARM_MODE_FIQ32:
574     cpu->cd.arm.spsr_fiq = cpu->cd.arm.cpsr; break;
575     default:fatal("arm_exception(): unimplemented exception nr\n");
576     exit(1);
577     }
578    
579     /*
580     * Disable Thumb mode (because exception handlers always execute
581     * in ARM mode), set the exception mode, and disable interrupts:
582     */
583     cpu->cd.arm.cpsr &= ~ARM_FLAG_T;
584    
585     oldmode = cpu->cd.arm.cpsr & ARM_FLAG_MODE;
586    
587     cpu->cd.arm.cpsr &= ~ARM_FLAG_MODE;
588     cpu->cd.arm.cpsr |= arm_exception_to_mode[exception_nr];
589    
590     newmode = cpu->cd.arm.cpsr & ARM_FLAG_MODE;
591     if (oldmode == newmode) {
592     fatal("Exception caused no mode change? TODO\n");
593     exit(1);
594     }
595    
596     cpu->cd.arm.cpsr |= ARM_FLAG_I;
597     if (exception_nr == ARM_EXCEPTION_RESET ||
598     exception_nr == ARM_EXCEPTION_FIQ)
599     cpu->cd.arm.cpsr |= ARM_FLAG_F;
600    
601     /* Load the new register bank, if we switched: */
602     arm_load_register_bank(cpu);
603    
604     /* Set the return address and new PC: */
605     cpu->cd.arm.r[ARM_LR] = retaddr;
606    
607     cpu->pc = cpu->cd.arm.r[ARM_PC] = exception_nr * 4 +
608     ((cpu->cd.arm.control & ARM_CONTROL_V)? 0xffff0000 : 0);
609     arm_pc_to_pointers(cpu);
610     }
611    
612    
613     /*
614     * arm_cpu_interrupt():
615     *
616     * 0..31 are used as footbridge interrupt numbers, 32..47 = ISA,
617     * 64 is used as a "re-assert" signal to cpu->machine->md_interrupt().
618     *
619     * TODO: don't hardcode to footbridge!
620     */
621     int arm_cpu_interrupt(struct cpu *cpu, uint64_t irq_nr)
622     {
623     /* fatal("arm_cpu_interrupt(): 0x%llx\n", (int)irq_nr); */
624     if (irq_nr <= 64) {
625     if (cpu->machine->md_interrupt != NULL)
626     cpu->machine->md_interrupt(cpu->machine,
627     cpu, irq_nr, 1);
628     else
629     fatal("arm_cpu_interrupt(): md_interrupt == NULL\n");
630     } else {
631     /* Assert ARM IRQs: */
632     cpu->cd.arm.irq_asserted = 1;
633     }
634    
635     return 1;
636     }
637    
638    
639     /*
640     * arm_cpu_interrupt_ack():
641     */
642     int arm_cpu_interrupt_ack(struct cpu *cpu, uint64_t irq_nr)
643     {
644     if (irq_nr <= 64) {
645     if (cpu->machine->md_interrupt != NULL)
646     cpu->machine->md_interrupt(cpu->machine,
647     cpu, irq_nr, 0);
648     } else {
649     /* De-assert ARM IRQs: */
650     cpu->cd.arm.irq_asserted = 0;
651     }
652    
653     return 1;
654     }
655    
656    
657     /*
658     * arm_cpu_disassemble_instr():
659     *
660     * Convert an instruction word into human readable format, for instruction
661     * tracing.
662     *
663     * If running is 1, cpu->pc should be the address of the instruction.
664     *
665     * If running is 0, things that depend on the runtime environment (eg.
666     * register contents) will not be shown, and addr will be used instead of
667     * cpu->pc for relative addresses.
668     */
669     int arm_cpu_disassemble_instr(struct cpu *cpu, unsigned char *ib,
670     int running, uint64_t dumpaddr, int bintrans)
671     {
672     uint32_t iw, tmp;
673     int main_opcode, secondary_opcode, s_bit, r16, r12, r8;
674     int i, n, p_bit, u_bit, b_bit, w_bit, l_bit;
675     char *symbol, *condition;
676     uint64_t offset;
677    
678     if (running)
679     dumpaddr = cpu->pc;
680    
681     symbol = get_symbol_name(&cpu->machine->symbol_context,
682     dumpaddr, &offset);
683     if (symbol != NULL && offset == 0)
684     debug("<%s>\n", symbol);
685    
686     if (cpu->machine->ncpus > 1 && running)
687     debug("cpu%i:\t", cpu->cpu_id);
688    
689     debug("%08x: ", (int)dumpaddr);
690    
691     if (cpu->byte_order == EMUL_LITTLE_ENDIAN)
692     iw = ib[0] + (ib[1]<<8) + (ib[2]<<16) + (ib[3]<<24);
693     else
694     iw = ib[3] + (ib[2]<<8) + (ib[1]<<16) + (ib[0]<<24);
695     debug("%08x\t", (int)iw);
696    
697     condition = arm_condition_string[iw >> 28];
698     main_opcode = (iw >> 24) & 15;
699     secondary_opcode = (iw >> 21) & 15;
700     u_bit = (iw >> 23) & 1;
701     b_bit = (iw >> 22) & 1;
702     w_bit = (iw >> 21) & 1;
703     s_bit = l_bit = (iw >> 20) & 1;
704     r16 = (iw >> 16) & 15;
705     r12 = (iw >> 12) & 15;
706     r8 = (iw >> 8) & 15;
707    
708     switch (main_opcode) {
709     case 0x0:
710     case 0x1:
711     case 0x2:
712     case 0x3:
713     /*
714     * Special cases first:
715     */
716    
717     /*
718     * Multiplication:
719     * xxxx0000 00ASdddd nnnnssss 1001mmmm (Rd, Rm, Rs [,Rn])
720     */
721     if ((iw & 0x0fc000f0) == 0x00000090) {
722     int a_bit = (iw >> 21) & 1;
723     debug("%s%s%s\t", a_bit? "mla" : "mul",
724     condition, s_bit? "s" : "");
725     debug("%s,", arm_regname[r16]);
726     debug("%s,", arm_regname[iw & 15]);
727     debug("%s", arm_regname[r8]);
728     if (a_bit)
729     debug(",%s", arm_regname[r12]);
730     debug("\n");
731     break;
732     }
733    
734     /*
735     * Long multiplication:
736     * xxxx0000 1UAShhhh llllssss 1001mmmm (Rl,Rh,Rm,Rs)
737     */
738     if ((iw & 0x0f8000f0) == 0x00800090) {
739     int u_bit = (iw >> 22) & 1;
740     int a_bit = (iw >> 21) & 1;
741     debug("%s%sl%s%s\t", u_bit? "s" : "u",
742     a_bit? "mla" : "mul", condition, s_bit? "s" : "");
743     debug("%s,", arm_regname[r12]);
744     debug("%s,", arm_regname[r16]);
745     debug("%s,", arm_regname[iw & 15]);
746     debug("%s\n", arm_regname[r8]);
747     break;
748     }
749    
750     /*
751     * xxxx0001 0010.... ........ 00L1mmmm bx/blx rm
752     */
753     if ((iw & 0x0ff000d0) == 0x01200010) {
754     int l_bit = iw & 0x20;
755     debug("b%sx%s\t%s\n", l_bit? "l" : "", condition,
756     arm_regname[iw & 15]);
757     break;
758     }
759    
760     /*
761     * xxxx0001 0s10aaaa 11110000 0000mmmm MSR Regform
762     * xxxx0011 0s10aaaa 1111rrrr bbbbbbbb MSR Immform
763     * xxxx0001 0s001111 dddd0000 00000000 MRS
764     */
765     if ((iw & 0x0fb0fff0) == 0x0120f000 ||
766     (iw & 0x0fb0f000) == 0x0320f000) {
767     int a = (iw >> 16) & 15;
768     debug("msr%s\t%s", condition, (iw&0x400000)? "S":"C");
769     debug("PSR_");
770     switch (a) {
771     case 1: debug("ctl"); break;
772     case 8: debug("flg"); break;
773     case 9: debug("all"); break;
774     default:debug(" UNIMPLEMENTED (a=%i)", a);
775     }
776     if (iw & 0x02000000) {
777     int r = (iw >> 7) & 30;
778     uint32_t b = iw & 0xff;
779     while (r-- > 0)
780     b = (b >> 1) | ((b & 1) << 31);
781     debug(",#0x%x\n", b);
782     } else
783     debug(",%s\n", arm_regname[iw & 15]);
784     break;
785     }
786     if ((iw & 0x0fbf0fff) == 0x010f0000) {
787     debug("mrs%s\t", condition);
788     debug("%s,%sPSR\n", arm_regname[r12],
789     (iw&0x400000)? "S":"C");
790     break;
791     }
792    
793     /*
794     * xxxx0001 0B00nnnn dddd0000 1001mmmm SWP Rd,Rm,[Rn]
795     */
796     if ((iw & 0x0fb00ff0) == 0x01000090) {
797     debug("swp%s%s\t", condition, (iw&0x400000)? "b":"");
798     debug("%s,%s,[%s]\n", arm_regname[r12],
799     arm_regname[iw & 15], arm_regname[r16]);
800     break;
801     }
802    
803     /*
804     * xxxx000P U1WLnnnn ddddHHHH 1SH1LLLL load/store rd,imm(rn)
805     */
806     if ((iw & 0x0e000090) == 0x00000090) {
807     int imm = ((iw >> 4) & 0xf0) | (iw & 0xf);
808     int regform = !(iw & 0x00400000);
809     p_bit = main_opcode & 1;
810     /*
811     * TODO: detect some illegal variants:
812     * signed store, or unsigned byte load/store
813     */
814     if (!l_bit && (iw & 0xd0) == 0xd0 && (r12 & 1)) {
815     debug("TODO: r12 odd, not load/store\n");
816     break;
817     }
818     /* Semi-generic case: */
819     debug("%sr%s", iw & 0x00100000? "ld" : "st",
820     condition);
821     if (!l_bit && (iw & 0xd0) == 0xd0) {
822     debug("d"); /* Double-register */
823     } else {
824     if (iw & 0x40)
825     debug("s"); /* signed */
826     if (iw & 0x20)
827     debug("h"); /* half-word */
828     else
829     debug("b"); /* byte */
830     }
831     debug("\t%s,[%s", arm_regname[r12], arm_regname[r16]);
832     if (p_bit) {
833     /* Pre-index: */
834     if (regform)
835     debug(",%s%s", u_bit? "" : "-",
836     arm_regname[iw & 15]);
837     else {
838     if (imm != 0)
839     debug(",#%s%i", u_bit? "" : "-",
840     imm);
841     }
842     debug("]%s\n", w_bit? "!" : "");
843     } else {
844     /* Post-index: */
845     debug("],");
846     if (regform)
847     debug("%s%s\n", u_bit? "" : "-",
848     arm_regname[iw & 15]);
849     else
850     debug("#%s%i\n", u_bit? "" : "-", imm);
851     }
852     break;
853     }
854    
855     /* Other special cases: */
856     if (iw & 0x80 && !(main_opcode & 2) && iw & 0x10) {
857     debug("UNIMPLEMENTED reg (c!=0), t odd\n");
858     break;
859     }
860    
861     /*
862     * Generic Data Processing Instructions:
863     *
864     * xxxx000a aaaSnnnn ddddcccc ctttmmmm Register form
865     * xxxx001a aaaSnnnn ddddrrrr bbbbbbbb Immediate form
866     */
867    
868     debug("%s%s%s\t", arm_dpiname[secondary_opcode],
869     condition, s_bit? "s" : "");
870     if (arm_dpi_uses_d[secondary_opcode])
871     debug("%s,", arm_regname[r12]);
872     if (arm_dpi_uses_n[secondary_opcode])
873     debug("%s,", arm_regname[r16]);
874    
875     if (main_opcode & 2) {
876     /* Immediate form: */
877     int r = (iw >> 7) & 30;
878     uint32_t b = iw & 0xff;
879     while (r-- > 0)
880     b = (b >> 1) | ((b & 1) << 31);
881     if (b < 15)
882     debug("#%i", b);
883     else
884     debug("#0x%x", b);
885     } else {
886     /* Register form: */
887     int t = (iw >> 4) & 7;
888     int c = (iw >> 7) & 31;
889     debug("%s", arm_regname[iw & 15]);
890     switch (t) {
891     case 0: if (c != 0)
892     debug(", lsl #%i", c);
893     break;
894     case 1: debug(", lsl %s", arm_regname[c >> 1]);
895     break;
896     case 2: debug(", lsr #%i", c? c : 32);
897     break;
898     case 3: debug(", lsr %s", arm_regname[c >> 1]);
899     break;
900     case 4: debug(", asr #%i", c? c : 32);
901     break;
902     case 5: debug(", asr %s", arm_regname[c >> 1]);
903     break;
904     case 6: if (c != 0)
905     debug(", ror #%i", c);
906     else
907     debug(", rrx");
908     break;
909     case 7: debug(", ror %s", arm_regname[c >> 1]);
910     break;
911     }
912    
913     /* mov pc,reg: */
914     if (running && t == 0 && c == 0 && secondary_opcode
915     == 0xd && r12 == ARM_PC && (iw&15)!=ARM_PC) {
916     symbol = get_symbol_name(&cpu->machine->
917     symbol_context, cpu->cd.arm.r[iw & 15],
918     &offset);
919     if (symbol != NULL)
920     debug(" \t<%s>", symbol);
921     }
922     }
923     debug("\n");
924     break;
925     case 0x4: /* Single Data Transfer */
926     case 0x5:
927     case 0x6:
928     case 0x7:
929     /* Special case first: */
930     if ((iw & 0xfc70f000) == 0xf450f000) {
931     /* Preload: */
932     debug("pld\t[%s]\n", arm_regname[r16]);
933     break;
934     }
935    
936     /*
937     * xxxx010P UBWLnnnn ddddoooo oooooooo Immediate form
938     * xxxx011P UBWLnnnn ddddcccc ctt0mmmm Register form
939     */
940     p_bit = main_opcode & 1;
941     if (main_opcode >= 6 && iw & 0x10) {
942     debug("TODO: single data transf. but 0x10\n");
943     break;
944     }
945     debug("%s%s%s", l_bit? "ldr" : "str",
946     condition, b_bit? "b" : "");
947     if (!p_bit && w_bit)
948     debug("t");
949     debug("\t%s,[%s", arm_regname[r12], arm_regname[r16]);
950     if ((iw & 0x0e000000) == 0x04000000) {
951     /* Immediate form: */
952     uint32_t imm = iw & 0xfff;
953     if (!p_bit)
954     debug("]");
955     if (imm != 0)
956     debug(",#%s%i", u_bit? "" : "-", imm);
957     if (p_bit)
958     debug("]");
959     } else if ((iw & 0x0e000010) == 0x06000000) {
960     /* Register form: */
961     if (!p_bit)
962     debug("]");
963     if ((iw & 0xfff) != 0)
964     debug(",%s%s", u_bit? "" : "-",
965     arm_regname[iw & 15]);
966     if ((iw & 0xff0) != 0x000) {
967     int c = (iw >> 7) & 31;
968     int t = (iw >> 4) & 7;
969     switch (t) {
970     case 0: if (c != 0)
971     debug(", lsl #%i", c);
972     break;
973     case 2: debug(", lsr #%i", c? c : 32);
974     break;
975     case 4: debug(", asr #%i", c? c : 32);
976     break;
977     case 6: if (c != 0)
978     debug(", ror #%i", c);
979     else
980     debug(", rrx");
981     break;
982     }
983     }
984     if (p_bit)
985     debug("]");
986     } else {
987     debug("UNKNOWN\n");
988     break;
989     }
990     debug("%s", (p_bit && w_bit)? "!" : "");
991     if ((iw & 0x0f000000) == 0x05000000 &&
992     (r16 == ARM_PC || running)) {
993     unsigned char tmpw[4];
994     uint32_t imm = iw & 0xfff;
995     uint32_t addr = (u_bit? imm : -imm);
996     if (r16 == ARM_PC)
997     addr += dumpaddr + 8;
998     else
999     addr += cpu->cd.arm.r[r16];
1000     symbol = get_symbol_name(&cpu->machine->symbol_context,
1001     addr, &offset);
1002     if (symbol != NULL)
1003     debug(" \t<%s", symbol);
1004     else
1005     debug(" \t<0x%08x", addr);
1006     if ((l_bit && cpu->memory_rw(cpu, cpu->mem, addr, tmpw,
1007     b_bit? 1 : sizeof(tmpw), MEM_READ, NO_EXCEPTIONS))
1008     || (!l_bit && running)) {
1009     if (l_bit) {
1010     if (cpu->byte_order ==
1011     EMUL_LITTLE_ENDIAN)
1012     addr = tmpw[0] +(tmpw[1] << 8) +
1013     (tmpw[2]<<16)+(tmpw[3]<<24);
1014     else
1015     addr = tmpw[3] + (tmpw[2]<<8) +
1016     (tmpw[1]<<16)+(tmpw[0]<<24);
1017     } else {
1018     tmpw[0] = addr = cpu->cd.arm.r[r12];
1019     if (r12 == ARM_PC)
1020     addr += 8;
1021     }
1022     debug(": ");
1023     if (b_bit)
1024     debug("%i", tmpw[0]);
1025     else {
1026     symbol = get_symbol_name(&cpu->machine->
1027     symbol_context, addr, &offset);
1028     if (symbol != NULL)
1029     debug("%s", symbol);
1030     else if ((int32_t)addr > -256 &&
1031     (int32_t)addr < 256)
1032     debug("%i", addr);
1033     else
1034     debug("0x%x", addr);
1035     }
1036     }
1037     debug(">");
1038     }
1039     debug("\n");
1040     break;
1041     case 0x8: /* Block Data Transfer */
1042     case 0x9:
1043     /* xxxx100P USWLnnnn llllllll llllllll */
1044     p_bit = main_opcode & 1;
1045     s_bit = b_bit;
1046     debug("%s%s", l_bit? "ldm" : "stm", condition);
1047     switch (u_bit * 2 + p_bit) {
1048     case 0: debug("da"); break;
1049     case 1: debug("db"); break;
1050     case 2: debug("ia"); break;
1051     case 3: debug("ib"); break;
1052     }
1053     debug("\t%s", arm_regname[r16]);
1054     if (w_bit)
1055     debug("!");
1056     debug(",{");
1057     n = 0;
1058     for (i=0; i<16; i++)
1059     if ((iw >> i) & 1) {
1060     debug("%s%s", (n > 0)? ",":"", arm_regname[i]);
1061     n++;
1062     }
1063     debug("}");
1064     if (s_bit)
1065     debug("^");
1066     debug("\n");
1067     break;
1068     case 0xa: /* B: branch */
1069     case 0xb: /* BL: branch and link */
1070     debug("b%s%s\t", main_opcode == 0xa? "" : "l", condition);
1071     tmp = (iw & 0x00ffffff) << 2;
1072     if (tmp & 0x02000000)
1073     tmp |= 0xfc000000;
1074     tmp = (int32_t)(dumpaddr + tmp + 8);
1075     debug("0x%x", (int)tmp);
1076     symbol = get_symbol_name(&cpu->machine->symbol_context,
1077     tmp, &offset);
1078     if (symbol != NULL)
1079     debug(" \t<%s>", symbol);
1080     debug("\n");
1081     break;
1082     case 0xc: /* Coprocessor */
1083     case 0xd: /* LDC/STC */
1084     /* xxxx110P UNWLnnnn DDDDpppp oooooooo LDC/STC */
1085     debug("TODO: coprocessor LDC/STC\n");
1086     break;
1087     case 0xe: /* CDP (Coprocessor Op) */
1088     /* or MRC/MCR!
1089     * xxxx1110 oooonnnn ddddpppp qqq0mmmm CDP
1090     * xxxx1110 oooLNNNN ddddpppp qqq1MMMM MRC/MCR
1091     */
1092     if (iw & 0x10) {
1093     debug("%s%s\t",
1094     (iw & 0x00100000)? "mrc" : "mcr", condition);
1095     debug("%i,%i,r%i,cr%i,cr%i,%i",
1096     (int)((iw >> 8) & 15), (int)((iw >>21) & 7),
1097     (int)((iw >>12) & 15), (int)((iw >>16) & 15),
1098     (int)((iw >> 0) & 15), (int)((iw >> 5) & 7));
1099     } else {
1100     debug("cdp%s\t", condition);
1101     debug("%i,%i,cr%i,cr%i,cr%i",
1102     (int)((iw >> 8) & 15),
1103     (int)((iw >>20) & 15),
1104     (int)((iw >>12) & 15),
1105     (int)((iw >>16) & 15),
1106     (int)((iw >> 0) & 15));
1107     if ((iw >> 5) & 7)
1108     debug(",0x%x", (int)((iw >> 5) & 7));
1109     }
1110     debug("\n");
1111     break;
1112     case 0xf: /* SWI */
1113     debug("swi%s\t", condition);
1114     debug("0x%x\n", (int)(iw & 0x00ffffff));
1115     break;
1116     default:debug("UNIMPLEMENTED\n");
1117     }
1118    
1119     return sizeof(uint32_t);
1120     }
1121    
1122    
1123     /*****************************************************************************/
1124    
1125    
1126     /*
1127     * arm_mcr_mrc():
1128     *
1129     * Coprocessor register move.
1130     *
1131     * The program counter should be synched before calling this function (to
1132     * make debug output with the correct PC value possible).
1133     */
1134     void arm_mcr_mrc(struct cpu *cpu, uint32_t iword)
1135     {
1136     int opcode1 = (iword >> 21) & 7;
1137     int l_bit = (iword >> 20) & 1;
1138     int crn = (iword >> 16) & 15;
1139     int rd = (iword >> 12) & 15;
1140     int cp_num = (iword >> 8) & 15;
1141     int opcode2 = (iword >> 5) & 7;
1142     int crm = iword & 15;
1143    
1144     if (cpu->cd.arm.coproc[cp_num] != NULL)
1145     cpu->cd.arm.coproc[cp_num](cpu, opcode1, opcode2, l_bit,
1146     crn, crm, rd);
1147     else {
1148     fatal("arm_mcr_mrc: pc=0x%08x, iword=0x%08x: "
1149     "cp_num=%i\n", (int)cpu->pc, iword, cp_num);
1150     exit(1);
1151     }
1152     }
1153    
1154    
1155     /*
1156     * arm_cdp():
1157     *
1158     * Coprocessor operations.
1159     *
1160     * The program counter should be synched before calling this function (to
1161     * make debug output with the correct PC value possible).
1162     */
1163     void arm_cdp(struct cpu *cpu, uint32_t iword)
1164     {
1165     fatal("arm_cdp: pc=0x%08x, iword=0x%08x\n", (int)cpu->pc, iword);
1166     exit(1);
1167     }
1168    
1169    
1170     /*****************************************************************************/
1171    
1172    
1173     #include "tmp_arm_tail.c"
1174    

  ViewVC Help
Powered by ViewVC 1.1.26