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

Parent Directory Parent Directory | Revision Log Revision Log


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

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


1 dpavlin 14 /*
2 dpavlin 22 * Copyright (C) 2005-2006 Anders Gavare. All rights reserved.
3 dpavlin 14 *
4     * Redistribution and use in source and binary forms, with or without
5     * modification, are permitted provided that the following conditions are met:
6     *
7     * 1. Redistributions of source code must retain the above copyright
8     * notice, this list of conditions and the following disclaimer.
9     * 2. Redistributions in binary form must reproduce the above copyright
10     * notice, this list of conditions and the following disclaimer in the
11     * documentation and/or other materials provided with the distribution.
12     * 3. The name of the author may not be used to endorse or promote products
13     * derived from this software without specific prior written permission.
14     *
15     * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
16     * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
17     * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
18     * ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
19     * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
20     * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
21     * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
22     * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
23     * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
24     * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
25     * SUCH DAMAGE.
26     *
27     *
28 dpavlin 24 * $Id: cpu_alpha_instr.c,v 1.11 2006/06/03 06:46:44 debug Exp $
29 dpavlin 14 *
30     * Alpha instructions.
31     *
32     * Individual functions should keep track of cpu->n_translated_instrs.
33     * (If no instruction was executed, then it should be decreased. If, say, 4
34     * instructions were combined into one function and executed, then it should
35     * be increased by 3.)
36     */
37    
38    
39 dpavlin 22 #include "float_emul.h"
40    
41    
42 dpavlin 14 /*
43     * nop: Do nothing.
44     */
45     X(nop)
46     {
47     }
48    
49    
50     /*
51     * call_pal: PALcode call
52     *
53     * arg[0] = pal nr
54     */
55     X(call_pal)
56     {
57     /* Synchronize PC first: */
58     uint64_t old_pc, low_pc = ((size_t)ic - (size_t)
59     cpu->cd.alpha.cur_ic_page) / sizeof(struct alpha_instr_call);
60     cpu->pc &= ~((ALPHA_IC_ENTRIES_PER_PAGE-1) <<
61     ALPHA_INSTR_ALIGNMENT_SHIFT);
62     cpu->pc += (low_pc << ALPHA_INSTR_ALIGNMENT_SHIFT);
63     old_pc = cpu->pc;
64    
65     alpha_palcode(cpu, ic->arg[0]);
66    
67     if (!cpu->running) {
68     cpu->running_translated = 0;
69     cpu->n_translated_instrs --;
70     cpu->cd.alpha.next_ic = &nothing_call;
71     } else if (cpu->pc != old_pc) {
72     /* The PC value was changed by the palcode call. */
73     /* Find the new physical page and update the translation
74     pointers: */
75     alpha_pc_to_pointers(cpu);
76     }
77     }
78    
79    
80     /*
81     * jsr: Jump to SubRoutine
82     *
83     * arg[0] = ptr to uint64_t where to store return PC
84     * arg[1] = ptr to uint64_t of new PC
85     */
86     X(jsr)
87     {
88     uint64_t old_pc = cpu->pc, low_pc;
89     uint64_t mask_within_page = ((ALPHA_IC_ENTRIES_PER_PAGE-1)
90     << ALPHA_INSTR_ALIGNMENT_SHIFT) |
91     ((1 << ALPHA_INSTR_ALIGNMENT_SHIFT) - 1);
92    
93     low_pc = ((size_t)ic - (size_t)
94     cpu->cd.alpha.cur_ic_page) / sizeof(struct alpha_instr_call);
95     cpu->pc &= ~((ALPHA_IC_ENTRIES_PER_PAGE-1)
96     << ALPHA_INSTR_ALIGNMENT_SHIFT);
97     cpu->pc += (low_pc << ALPHA_INSTR_ALIGNMENT_SHIFT) + 4;
98    
99     *((int64_t *)ic->arg[0]) = cpu->pc;
100     cpu->pc = *((int64_t *)ic->arg[1]);
101    
102     /*
103     * If this is a jump/return into the same code page as we were
104     * already in, then just set cpu->cd.alpha.next_ic.
105     */
106     if ((old_pc & ~mask_within_page) == (cpu->pc & ~mask_within_page)) {
107     cpu->cd.alpha.next_ic = cpu->cd.alpha.cur_ic_page +
108     ((cpu->pc & mask_within_page) >> 2);
109     } else {
110     /* Find the new physical page and update pointers: */
111     alpha_pc_to_pointers(cpu);
112     }
113     }
114    
115    
116     /*
117     * jsr_trace: Jump to SubRoutine (with function call trace enabled)
118     *
119     * Arguments same as for jsr.
120     */
121     X(jsr_trace)
122     {
123     cpu_functioncall_trace(cpu, *((int64_t *)ic->arg[1]));
124     instr(jsr)(cpu, ic);
125     }
126    
127    
128     /*
129     * jsr_0: JSR/RET, don't store return PC.
130     *
131     * arg[0] = ignored
132     * arg[1] = ptr to uint64_t of new PC
133     */
134     X(jsr_0)
135     {
136     uint64_t old_pc = cpu->pc;
137     uint64_t mask_within_page = ((ALPHA_IC_ENTRIES_PER_PAGE-1)
138     << ALPHA_INSTR_ALIGNMENT_SHIFT)
139     | ((1 << ALPHA_INSTR_ALIGNMENT_SHIFT) - 1);
140    
141     cpu->pc = *((int64_t *)ic->arg[1]);
142    
143     /*
144     * If this is a jump/return into the same code page as we were
145     * already in, then just set cpu->cd.alpha.next_ic.
146     */
147     if ((old_pc & ~mask_within_page) == (cpu->pc & ~mask_within_page)) {
148     cpu->cd.alpha.next_ic = cpu->cd.alpha.cur_ic_page +
149     ((cpu->pc & mask_within_page) >> 2);
150     } else {
151     /* Find the new physical page and update pointers: */
152     alpha_pc_to_pointers(cpu);
153     }
154     }
155    
156    
157     /*
158     * jsr_0_trace: JSR/RET (with function call trace enabled)
159     *
160     * Arguments same as for jsr_0.
161     */
162     X(jsr_0_trace)
163     {
164     cpu_functioncall_trace_return(cpu);
165     instr(jsr_0)(cpu, ic);
166     }
167    
168    
169     /*
170     * br: Branch (to a different translated page)
171     *
172     * arg[0] = relative offset (as an int32_t)
173     */
174     X(br)
175     {
176     uint64_t low_pc;
177    
178     /* Calculate new PC from this instruction + arg[0] */
179     low_pc = ((size_t)ic - (size_t)
180     cpu->cd.alpha.cur_ic_page) / sizeof(struct alpha_instr_call);
181     cpu->pc &= ~((ALPHA_IC_ENTRIES_PER_PAGE-1)
182     << ALPHA_INSTR_ALIGNMENT_SHIFT);
183     cpu->pc += (low_pc << ALPHA_INSTR_ALIGNMENT_SHIFT);
184     cpu->pc += (int32_t)ic->arg[0];
185    
186     /* Find the new physical page and update the translation pointers: */
187     alpha_pc_to_pointers(cpu);
188     }
189    
190    
191     /*
192     * br: Branch (to a different translated page), write return address
193     *
194     * arg[0] = relative offset (as an int32_t)
195     * arg[1] = pointer to uint64_t where to write return address
196     */
197     X(br_return)
198     {
199     uint64_t low_pc;
200    
201     /* Calculate new PC from this instruction + arg[0] */
202     low_pc = ((size_t)ic - (size_t)
203     cpu->cd.alpha.cur_ic_page) / sizeof(struct alpha_instr_call);
204     cpu->pc &= ~((ALPHA_IC_ENTRIES_PER_PAGE-1)
205     << ALPHA_INSTR_ALIGNMENT_SHIFT);
206     cpu->pc += (low_pc << ALPHA_INSTR_ALIGNMENT_SHIFT);
207    
208     /* ... but first, save away the return address: */
209     *((int64_t *)ic->arg[1]) = cpu->pc + 4;
210    
211     cpu->pc += (int32_t)ic->arg[0];
212    
213     /* Find the new physical page and update the translation pointers: */
214     alpha_pc_to_pointers(cpu);
215     }
216    
217    
218     /*
219     * beq: Branch (to a different translated page) if Equal
220     *
221     * arg[0] = relative offset (as an int32_t)
222     * arg[1] = pointer to int64_t register
223     */
224     X(beq)
225     {
226     if (*((int64_t *)ic->arg[1]) == 0)
227     instr(br)(cpu, ic);
228     }
229    
230    
231     /*
232     * blbs: Branch (to a different translated page) if Low Bit Set
233     *
234     * arg[0] = relative offset (as an int32_t)
235     * arg[1] = pointer to int64_t register
236     */
237     X(blbs)
238     {
239     if (*((int64_t *)ic->arg[1]) & 1)
240     instr(br)(cpu, ic);
241     }
242    
243    
244     /*
245     * blbc: Branch (to a different translated page) if Low Bit Clear
246     *
247     * arg[0] = relative offset (as an int32_t)
248     * arg[1] = pointer to int64_t register
249     */
250     X(blbc)
251     {
252     if (!(*((int64_t *)ic->arg[1]) & 1))
253     instr(br)(cpu, ic);
254     }
255    
256    
257     /*
258     * bne: Branch (to a different translated page) if Not Equal
259     *
260     * arg[0] = relative offset (as an int32_t)
261     * arg[1] = pointer to int64_t register
262     */
263     X(bne)
264     {
265     if (*((int64_t *)ic->arg[1]) != 0)
266     instr(br)(cpu, ic);
267     }
268    
269    
270     /*
271     * ble: Branch (to a different translated page) if Less or Equal
272     *
273     * arg[0] = relative offset (as an int32_t)
274     * arg[1] = pointer to int64_t register
275     */
276     X(ble)
277     {
278     if (*((int64_t *)ic->arg[1]) <= 0)
279     instr(br)(cpu, ic);
280     }
281    
282    
283     /*
284     * blt: Branch (to a different translated page) if Less Than
285     *
286     * arg[0] = relative offset (as an int32_t)
287     * arg[1] = pointer to int64_t register
288     */
289     X(blt)
290     {
291     if (*((int64_t *)ic->arg[1]) < 0)
292     instr(br)(cpu, ic);
293     }
294    
295    
296     /*
297     * bge: Branch (to a different translated page) if Greater or Equal
298     *
299     * arg[0] = relative offset (as an int32_t)
300     * arg[1] = pointer to int64_t register
301     */
302     X(bge)
303     {
304     if (*((int64_t *)ic->arg[1]) >= 0)
305     instr(br)(cpu, ic);
306     }
307    
308    
309     /*
310     * bgt: Branch (to a different translated page) if Greater Than
311     *
312     * arg[0] = relative offset (as an int32_t)
313     * arg[1] = pointer to int64_t register
314     */
315     X(bgt)
316     {
317     if (*((int64_t *)ic->arg[1]) > 0)
318     instr(br)(cpu, ic);
319     }
320    
321    
322     /*
323     * br_samepage: Branch (to within the same translated page)
324     *
325     * arg[0] = pointer to new alpha_instr_call
326     */
327     X(br_samepage)
328     {
329     cpu->cd.alpha.next_ic = (struct alpha_instr_call *) ic->arg[0];
330     }
331    
332    
333     /*
334     * br_return_samepage: Branch (to within the same translated page),
335     * and save return address
336     *
337     * arg[0] = pointer to new alpha_instr_call
338     * arg[1] = pointer to uint64_t where to store return address
339     */
340     X(br_return_samepage)
341     {
342     uint64_t low_pc;
343    
344     low_pc = ((size_t)ic - (size_t)
345     cpu->cd.alpha.cur_ic_page) / sizeof(struct alpha_instr_call);
346     cpu->pc &= ~((ALPHA_IC_ENTRIES_PER_PAGE-1)
347     << ALPHA_INSTR_ALIGNMENT_SHIFT);
348     cpu->pc += (low_pc << ALPHA_INSTR_ALIGNMENT_SHIFT);
349     *((int64_t *)ic->arg[1]) = cpu->pc + 4;
350    
351     cpu->cd.alpha.next_ic = (struct alpha_instr_call *) ic->arg[0];
352     }
353    
354    
355     /*
356     * beq_samepage: Branch (to within the same translated page) if Equal
357     *
358     * arg[0] = pointer to new alpha_instr_call
359     * arg[1] = pointer to int64_t register
360     */
361     X(beq_samepage)
362     {
363     if (*((int64_t *)ic->arg[1]) == 0)
364     instr(br_samepage)(cpu, ic);
365     }
366    
367    
368     /*
369     * blbs_samepage: Branch (to within the same translated page) if Low Bit Set
370     *
371     * arg[0] = pointer to new alpha_instr_call
372     * arg[1] = pointer to int64_t register
373     */
374     X(blbs_samepage)
375     {
376     if (*((int64_t *)ic->arg[1]) & 1)
377     instr(br_samepage)(cpu, ic);
378     }
379    
380    
381     /*
382     * blbc_samepage: Branch (to within the same translated page) if Low Bit Clear
383     *
384     * arg[0] = pointer to new alpha_instr_call
385     * arg[1] = pointer to int64_t register
386     */
387     X(blbc_samepage)
388     {
389     if (!(*((int64_t *)ic->arg[1]) & 1))
390     instr(br_samepage)(cpu, ic);
391     }
392    
393    
394     /*
395     * bne_samepage: Branch (to within the same translated page) if Not Equal
396     *
397     * arg[0] = pointer to new alpha_instr_call
398     * arg[1] = pointer to int64_t register
399     */
400     X(bne_samepage)
401     {
402     if (*((int64_t *)ic->arg[1]) != 0)
403     instr(br_samepage)(cpu, ic);
404     }
405    
406    
407     /*
408     * ble_samepage: Branch (to within the same translated page) if Less or Equal
409     *
410     * arg[0] = pointer to new alpha_instr_call
411     * arg[1] = pointer to int64_t register
412     */
413     X(ble_samepage)
414     {
415     if (*((int64_t *)ic->arg[1]) <= 0)
416     instr(br_samepage)(cpu, ic);
417     }
418    
419    
420     /*
421     * blt_samepage: Branch (to within the same translated page) if Less Than
422     *
423     * arg[0] = pointer to new alpha_instr_call
424     * arg[1] = pointer to int64_t register
425     */
426     X(blt_samepage)
427     {
428     if (*((int64_t *)ic->arg[1]) < 0)
429     instr(br_samepage)(cpu, ic);
430     }
431    
432    
433     /*
434     * bge_samepage: Branch (to within the same translated page)
435     * if Greater or Equal
436     *
437     * arg[0] = pointer to new alpha_instr_call
438     * arg[1] = pointer to int64_t register
439     */
440     X(bge_samepage)
441     {
442     if (*((int64_t *)ic->arg[1]) >= 0)
443     instr(br_samepage)(cpu, ic);
444     }
445    
446    
447     /*
448     * bgt_samepage: Branch (to within the same translated page) if Greater Than
449     *
450     * arg[0] = pointer to new alpha_instr_call
451     * arg[1] = pointer to int64_t register
452     */
453     X(bgt_samepage)
454     {
455     if (*((int64_t *)ic->arg[1]) > 0)
456     instr(br_samepage)(cpu, ic);
457     }
458    
459    
460     /*
461 dpavlin 22 * cvttq/c: Convert floating point to quad.
462     *
463     * arg[0] = pointer to rc (destination integer)
464     * arg[2] = pointer to rb (source float)
465     */
466     X(cvttq_c)
467     {
468     struct ieee_float_value fb;
469     ieee_interpret_float_value(reg(ic->arg[2]), &fb, IEEE_FMT_D);
470     reg(ic->arg[0]) = fb.nan? 0 : fb.f;
471     }
472    
473    
474     /*
475     * cvtqt: Convert quad to floating point.
476     *
477     * arg[0] = pointer to rc (destination float)
478     * arg[2] = pointer to rb (source quad integer)
479     */
480     X(cvtqt)
481     {
482     reg(ic->arg[0]) = ieee_store_float_value(reg(ic->arg[2]),
483     IEEE_FMT_D, 0);
484     }
485    
486    
487     /*
488     * fabs, fneg: Floating point absolute value, or negation.
489     *
490     * arg[0] = pointer to rc (destination float)
491     * arg[2] = pointer to rb (source quad integer)
492     */
493     X(fabs)
494     {
495     reg(ic->arg[0]) = reg(ic->arg[2]) & 0x7fffffffffffffffULL;
496     }
497     X(fneg)
498     {
499     reg(ic->arg[0]) = reg(ic->arg[2]) ^ 0x8000000000000000ULL;
500     }
501    
502    
503     /*
504     * addt, subt, mult, divt: Floating point arithmetic.
505     *
506     * arg[0] = pointer to rc (destination)
507     * arg[1] = pointer to ra (source)
508     * arg[2] = pointer to rb (source)
509     */
510     X(addt)
511     {
512     struct ieee_float_value fa, fb;
513     double res;
514     ieee_interpret_float_value(reg(ic->arg[1]), &fa, IEEE_FMT_D);
515     ieee_interpret_float_value(reg(ic->arg[2]), &fb, IEEE_FMT_D);
516     if (fa.nan | fb.nan)
517     res = 0.0;
518     else
519     res = fa.f + fb.f;
520     reg(ic->arg[0]) = ieee_store_float_value(res,
521     IEEE_FMT_D, fa.nan | fb.nan);
522     }
523     X(subt)
524     {
525     struct ieee_float_value fa, fb;
526     double res;
527     ieee_interpret_float_value(reg(ic->arg[1]), &fa, IEEE_FMT_D);
528     ieee_interpret_float_value(reg(ic->arg[2]), &fb, IEEE_FMT_D);
529     if (fa.nan | fb.nan)
530     res = 0.0;
531     else
532     res = fa.f - fb.f;
533     reg(ic->arg[0]) = ieee_store_float_value(res,
534     IEEE_FMT_D, fa.nan | fb.nan);
535     }
536     X(mult)
537     {
538     struct ieee_float_value fa, fb;
539     double res;
540     ieee_interpret_float_value(reg(ic->arg[1]), &fa, IEEE_FMT_D);
541     ieee_interpret_float_value(reg(ic->arg[2]), &fb, IEEE_FMT_D);
542     if (fa.nan | fb.nan)
543     res = 0.0;
544     else
545     res = fa.f * fb.f;
546     reg(ic->arg[0]) = ieee_store_float_value(res,
547     IEEE_FMT_D, fa.nan | fb.nan);
548     }
549     X(divt)
550     {
551     struct ieee_float_value fa, fb;
552     double res;
553     ieee_interpret_float_value(reg(ic->arg[1]), &fa, IEEE_FMT_D);
554     ieee_interpret_float_value(reg(ic->arg[2]), &fb, IEEE_FMT_D);
555     if (fa.nan | fb.nan || fb.f == 0)
556     res = 0.0;
557     else
558     res = fa.f / fb.f;
559     reg(ic->arg[0]) = ieee_store_float_value(res,
560     IEEE_FMT_D, fa.nan | fb.nan || fb.f == 0);
561     }
562     X(cmpteq)
563     {
564     struct ieee_float_value fa, fb;
565     int res = 0;
566     ieee_interpret_float_value(reg(ic->arg[1]), &fa, IEEE_FMT_D);
567     ieee_interpret_float_value(reg(ic->arg[2]), &fb, IEEE_FMT_D);
568     if (fa.nan | fb.nan)
569     res = 0;
570     else
571     res = fa.f == fb.f;
572     reg(ic->arg[0]) = res;
573     }
574     X(cmptlt)
575     {
576     struct ieee_float_value fa, fb;
577     int res = 0;
578     ieee_interpret_float_value(reg(ic->arg[1]), &fa, IEEE_FMT_D);
579     ieee_interpret_float_value(reg(ic->arg[2]), &fb, IEEE_FMT_D);
580     if (fa.nan | fb.nan)
581     res = 0;
582     else
583     res = fa.f < fb.f;
584     reg(ic->arg[0]) = res;
585     }
586     X(cmptle)
587     {
588     struct ieee_float_value fa, fb;
589     int res = 0;
590     ieee_interpret_float_value(reg(ic->arg[1]), &fa, IEEE_FMT_D);
591     ieee_interpret_float_value(reg(ic->arg[2]), &fb, IEEE_FMT_D);
592     if (fa.nan | fb.nan)
593     res = 0;
594     else
595     res = fa.f <= fb.f;
596     reg(ic->arg[0]) = res;
597     }
598    
599    
600     /*
601 dpavlin 14 * mull: Signed Multiply 32x32 => 32.
602     *
603     * arg[0] = pointer to destination uint64_t
604     * arg[1] = pointer to source uint64_t
605     * arg[2] = pointer to source uint64_t
606     */
607     X(mull)
608     {
609     int32_t a = reg(ic->arg[1]);
610     int32_t b = reg(ic->arg[2]);
611     reg(ic->arg[0]) = (int64_t)(int32_t)(a * b);
612     }
613    
614    
615     /*
616     * mulq: Unsigned Multiply 64x64 => 64.
617     *
618     * arg[0] = pointer to destination uint64_t
619     * arg[1] = pointer to source uint64_t
620     * arg[2] = pointer to source uint64_t
621     */
622     X(mulq)
623     {
624     reg(ic->arg[0]) = reg(ic->arg[1]) * reg(ic->arg[2]);
625     }
626    
627    
628     /*
629     * umulh: Unsigned Multiply 64x64 => 128. Store high part in dest reg.
630     *
631     * arg[0] = pointer to destination uint64_t
632     * arg[1] = pointer to source uint64_t
633     * arg[2] = pointer to source uint64_t
634     */
635     X(umulh)
636     {
637     uint64_t reshi = 0, reslo = 0;
638     uint64_t s1 = reg(ic->arg[1]), s2 = reg(ic->arg[2]);
639     int i, bit;
640    
641     for (i=0; i<64; i++) {
642     bit = (s1 & 0x8000000000000000ULL)? 1 : 0;
643     s1 <<= 1;
644    
645     /* If bit in s1 set, then add s2 to reshi/lo: */
646     if (bit) {
647     uint64_t old_reslo = reslo;
648     reslo += s2;
649     if (reslo < old_reslo)
650     reshi ++;
651     }
652    
653     if (i != 63) {
654     reshi <<= 1;
655     reshi += (reslo & 0x8000000000000000ULL? 1 : 0);
656     reslo <<= 1;
657     }
658     }
659    
660     reg(ic->arg[0]) = reshi;
661     }
662    
663    
664     /*
665     * lda: Load address.
666     *
667     * arg[0] = pointer to destination uint64_t
668     * arg[1] = pointer to source uint64_t
669     * arg[2] = offset (possibly as an int32_t)
670     */
671     X(lda)
672     {
673     reg(ic->arg[0]) = reg(ic->arg[1]) + (int64_t)(int32_t)ic->arg[2];
674     }
675    
676    
677     /*
678     * lda_0: Load address compared to the zero register.
679     *
680     * arg[0] = pointer to destination uint64_t
681     * arg[1] = ignored
682     * arg[2] = offset (possibly as an int32_t)
683     */
684     X(lda_0)
685     {
686     reg(ic->arg[0]) = (int64_t)(int32_t)ic->arg[2];
687     }
688    
689    
690     /*
691     * clear: Clear a 64-bit register.
692     *
693     * arg[0] = pointer to destination uint64_t
694     */
695     X(clear)
696     {
697     reg(ic->arg[0]) = 0;
698     }
699    
700    
701     /*
702     * rdcc: Read the Cycle Counter into a 64-bit register.
703     *
704     * arg[0] = pointer to destination uint64_t
705     */
706     X(rdcc)
707     {
708     reg(ic->arg[0]) = cpu->cd.alpha.pcc;
709    
710     /* TODO: actually keep the pcc updated! */
711     cpu->cd.alpha.pcc += 20;
712     }
713    
714    
715     #include "tmp_alpha_misc.c"
716    
717    
718     /*****************************************************************************/
719    
720    
721     X(end_of_page)
722     {
723     /* Update the PC: (offset 0, but on the next page) */
724     cpu->pc &= ~((ALPHA_IC_ENTRIES_PER_PAGE-1)
725     << ALPHA_INSTR_ALIGNMENT_SHIFT);
726     cpu->pc += (ALPHA_IC_ENTRIES_PER_PAGE
727     << ALPHA_INSTR_ALIGNMENT_SHIFT);
728    
729     /* Find the new physical page and update the translation pointers: */
730     alpha_pc_to_pointers(cpu);
731    
732     /* end_of_page doesn't count as an executed instruction: */
733     cpu->n_translated_instrs --;
734     }
735    
736    
737     /*****************************************************************************/
738    
739    
740     /*
741     * alpha_instr_to_be_translated():
742     *
743     * Translate an instruction word into an alpha_instr_call. ic is filled in with
744     * valid data for the translated instruction, or a "nothing" instruction if
745     * there was a translation failure. The newly translated instruction is then
746     * executed.
747     */
748     X(to_be_translated)
749     {
750     uint64_t addr, low_pc;
751     uint32_t iword;
752     unsigned char *page;
753     unsigned char ib[4];
754     void (*samepage_function)(struct cpu *, struct alpha_instr_call *);
755     int opcode, ra, rb, func, rc, imm, load, loadstore_type, fp, llsc;
756    
757     /* Figure out the (virtual) address of the instruction: */
758     low_pc = ((size_t)ic - (size_t)cpu->cd.alpha.cur_ic_page)
759     / sizeof(struct alpha_instr_call);
760     addr = cpu->pc & ~((ALPHA_IC_ENTRIES_PER_PAGE-1) <<
761     ALPHA_INSTR_ALIGNMENT_SHIFT);
762     addr += (low_pc << ALPHA_INSTR_ALIGNMENT_SHIFT);
763     addr &= ~((1 << ALPHA_INSTR_ALIGNMENT_SHIFT) - 1);
764     cpu->pc = addr;
765    
766     /* Read the instruction word from memory: */
767 dpavlin 24 {
768     const uint32_t mask1 = (1 << DYNTRANS_L1N) - 1;
769     const uint32_t mask2 = (1 << DYNTRANS_L2N) - 1;
770     const uint32_t mask3 = (1 << DYNTRANS_L3N) - 1;
771     uint32_t x1 = (addr >> (64-DYNTRANS_L1N)) & mask1;
772     uint32_t x2 = (addr >> (64-DYNTRANS_L1N-DYNTRANS_L2N)) & mask2;
773     uint32_t x3 = (addr >> (64-DYNTRANS_L1N-DYNTRANS_L2N-
774     DYNTRANS_L3N)) & mask3;
775     struct DYNTRANS_L2_64_TABLE *l2 = cpu->cd.alpha.l1_64[x1];
776     struct DYNTRANS_L3_64_TABLE *l3 = l2->l3[x2];
777     page = l3->host_load[x3];
778     }
779 dpavlin 14
780     if (page != NULL) {
781     /* fatal("TRANSLATION HIT!\n"); */
782     memcpy(ib, page + (addr & 8191), sizeof(ib));
783     } else {
784     /* fatal("TRANSLATION MISS!\n"); */
785     if (!cpu->memory_rw(cpu, cpu->mem, addr, &ib[0],
786     sizeof(ib), MEM_READ, CACHE_INSTRUCTION)) {
787     fatal("to_be_translated(): read failed: TODO\n");
788     goto bad;
789     }
790     }
791    
792 dpavlin 24 /* Alpha instruction words are always little-endian. Convert
793     to host order: */
794     iword = LE32_TO_HOST( *((uint32_t *)&ib[0]) );
795 dpavlin 14
796    
797     #define DYNTRANS_TO_BE_TRANSLATED_HEAD
798     #include "cpu_dyntrans.c"
799     #undef DYNTRANS_TO_BE_TRANSLATED_HEAD
800    
801    
802     opcode = (iword >> 26) & 63;
803     ra = (iword >> 21) & 31;
804     rb = (iword >> 16) & 31;
805     func = (iword >> 5) & 0x7ff;
806     rc = iword & 31;
807     imm = iword & 0xffff;
808    
809     switch (opcode) {
810     case 0x00: /* CALL_PAL */
811     ic->f = instr(call_pal);
812     ic->arg[0] = (size_t) (iword & 0x3ffffff);
813     break;
814     case 0x08: /* LDA */
815     case 0x09: /* LDAH */
816     if (ra == ALPHA_ZERO) {
817     ic->f = instr(nop);
818     break;
819     }
820     /* TODO: A special case which is common is to add or subtract
821     a small offset from sp. */
822     ic->f = instr(lda);
823     ic->arg[0] = (size_t) &cpu->cd.alpha.r[ra];
824     ic->arg[1] = (size_t) &cpu->cd.alpha.r[rb];
825     if (rb == ALPHA_ZERO)
826     ic->f = instr(lda_0);
827     ic->arg[2] = (ssize_t)(int16_t)imm;
828     if (opcode == 0x09)
829     ic->arg[2] <<= 16;
830     break;
831     case 0x0b: /* LDQ_U */
832     case 0x0f: /* STQ_U */
833     if (ra == ALPHA_ZERO && opcode == 0x0b) {
834     ic->f = instr(nop);
835     break;
836     }
837     if (opcode == 0x0b)
838     ic->f = instr(ldq_u);
839     else
840     ic->f = instr(stq_u);
841     ic->arg[0] = (size_t) &cpu->cd.alpha.r[ra];
842     ic->arg[1] = (size_t) &cpu->cd.alpha.r[rb];
843     ic->arg[2] = (ssize_t)(int16_t)imm;
844     break;
845     case 0x0a:
846     case 0x0c:
847     case 0x0d:
848     case 0x0e:
849     case 0x22:
850     case 0x23:
851     case 0x26:
852     case 0x27:
853     case 0x28:
854     case 0x29:
855     case 0x2a:
856     case 0x2b:
857     case 0x2c:
858     case 0x2d:
859     case 0x2e:
860     case 0x2f:
861     loadstore_type = 0; fp = 0; load = 0; llsc = 0;
862     switch (opcode) {
863     case 0x0a: loadstore_type = 0; load = 1; break; /* ldbu */
864     case 0x0c: loadstore_type = 1; load = 1; break; /* ldwu */
865     case 0x0d: loadstore_type = 1; break; /* stw */
866     case 0x0e: loadstore_type = 0; break; /* stb */
867     case 0x22: loadstore_type = 2; load = 1; fp = 1; break; /*lds*/
868     case 0x23: loadstore_type = 3; load = 1; fp = 1; break; /*ldt*/
869     case 0x26: loadstore_type = 2; fp = 1; break; /* sts */
870     case 0x27: loadstore_type = 3; fp = 1; break; /* stt */
871     case 0x28: loadstore_type = 2; load = 1; break; /* ldl */
872     case 0x29: loadstore_type = 3; load = 1; break; /* ldq */
873     case 0x2a: loadstore_type = 2; load = llsc = 1; break;/* ldl_l*/
874     case 0x2b: loadstore_type = 3; load = llsc = 1; break;/* ldq_l*/
875     case 0x2c: loadstore_type = 2; break; /* stl */
876     case 0x2d: loadstore_type = 3; break; /* stq */
877     case 0x2e: loadstore_type = 2; llsc = 1; break; /* stl_c */
878     case 0x2f: loadstore_type = 3; llsc = 1; break; /* stq_c */
879     }
880     ic->f = alpha_loadstore[
881     loadstore_type + (imm==0? 4 : 0) + 8 * load
882     + (cpu->machine->dyntrans_alignment_check? 16:0)
883     + 32 * llsc];
884     /* Load to the zero register is treated as a prefetch
885     hint. It is ignored here. */
886     if (load && ra == ALPHA_ZERO) {
887     ic->f = instr(nop);
888     break;
889     }
890     if (fp)
891     ic->arg[0] = (size_t) &cpu->cd.alpha.f[ra];
892     else
893     ic->arg[0] = (size_t) &cpu->cd.alpha.r[ra];
894     ic->arg[1] = (size_t) &cpu->cd.alpha.r[rb];
895     ic->arg[2] = (ssize_t)(int16_t)imm;
896     break;
897     case 0x10:
898     if (rc == ALPHA_ZERO) {
899     ic->f = instr(nop);
900     break;
901     }
902     ic->arg[0] = (size_t) &cpu->cd.alpha.r[rc];
903     ic->arg[1] = (size_t) &cpu->cd.alpha.r[ra];
904     if (func & 0x80)
905     ic->arg[2] = (size_t)((rb << 3) + (func >> 8));
906     else
907     ic->arg[2] = (size_t) &cpu->cd.alpha.r[rb];
908     switch (func & 0xff) {
909     case 0x00: ic->f = instr(addl); break;
910     case 0x02: ic->f = instr(s4addl); break;
911     case 0x09: ic->f = instr(subl); break;
912     case 0x0b: ic->f = instr(s4subl); break;
913 dpavlin 24 case 0x0f: ic->f = instr(cmpbge); break;
914 dpavlin 14 case 0x12: ic->f = instr(s8addl); break;
915     case 0x1b: ic->f = instr(s8subl); break;
916     case 0x1d: ic->f = instr(cmpult); break;
917     case 0x20: ic->f = instr(addq); break;
918     case 0x22: ic->f = instr(s4addq); break;
919     case 0x29: ic->f = instr(subq); break;
920     case 0x2b: ic->f = instr(s4subq); break;
921     case 0x2d: ic->f = instr(cmpeq); break;
922     case 0x32: ic->f = instr(s8addq); break;
923     case 0x3b: ic->f = instr(s8subq); break;
924     case 0x3d: ic->f = instr(cmpule); break;
925     case 0x4d: ic->f = instr(cmplt); break;
926     case 0x6d: ic->f = instr(cmple); break;
927    
928     case 0x80: ic->f = instr(addl_imm); break;
929     case 0x82: ic->f = instr(s4addl_imm); break;
930     case 0x89: ic->f = instr(subl_imm); break;
931     case 0x8b: ic->f = instr(s4subl_imm); break;
932 dpavlin 24 case 0x8f: ic->f = instr(cmpbge_imm); break;
933 dpavlin 14 case 0x92: ic->f = instr(s8addl_imm); break;
934     case 0x9b: ic->f = instr(s8subl_imm); break;
935     case 0x9d: ic->f = instr(cmpult_imm); break;
936     case 0xa0: ic->f = instr(addq_imm); break;
937     case 0xa2: ic->f = instr(s4addq_imm); break;
938     case 0xa9: ic->f = instr(subq_imm); break;
939     case 0xab: ic->f = instr(s4subq_imm); break;
940     case 0xad: ic->f = instr(cmpeq_imm); break;
941     case 0xb2: ic->f = instr(s8addq_imm); break;
942     case 0xbb: ic->f = instr(s8subq_imm); break;
943     case 0xbd: ic->f = instr(cmpule_imm); break;
944     case 0xcd: ic->f = instr(cmplt_imm); break;
945     case 0xed: ic->f = instr(cmple_imm); break;
946    
947     default:fatal("[ Alpha: unimplemented function 0x%03x for"
948     " opcode 0x%02x ]\n", func, opcode);
949     goto bad;
950     }
951     break;
952     case 0x11:
953     if (rc == ALPHA_ZERO) {
954     ic->f = instr(nop);
955     break;
956     }
957     ic->arg[0] = (size_t) &cpu->cd.alpha.r[rc];
958     ic->arg[1] = (size_t) &cpu->cd.alpha.r[ra];
959     if (func & 0x80)
960     ic->arg[2] = (size_t)((rb << 3) + (func >> 8));
961     else
962     ic->arg[2] = (size_t) &cpu->cd.alpha.r[rb];
963     switch (func & 0xff) {
964     case 0x00: ic->f = instr(and); break;
965     case 0x08: ic->f = instr(andnot); break;
966     case 0x14: ic->f = instr(cmovlbs); break;
967     case 0x16: ic->f = instr(cmovlbc); break;
968     case 0x20: ic->f = instr(or);
969     if (ra == ALPHA_ZERO || rb == ALPHA_ZERO) {
970     if (ra == ALPHA_ZERO)
971     ra = rb;
972     ic->f = alpha_mov_r_r[ra + rc*32];
973     }
974     break;
975     case 0x24: ic->f = instr(cmoveq); break;
976     case 0x26: ic->f = instr(cmovne); break;
977     case 0x28: ic->f = instr(ornot); break;
978     case 0x40: ic->f = instr(xor); break;
979     case 0x44: ic->f = instr(cmovlt); break;
980     case 0x46: ic->f = instr(cmovge); break;
981     case 0x48: ic->f = instr(xornot); break;
982     case 0x64: ic->f = instr(cmovle); break;
983     case 0x66: ic->f = instr(cmovgt); break;
984     case 0x80: ic->f = instr(and_imm); break;
985     case 0x88: ic->f = instr(andnot_imm); break;
986     case 0x94: ic->f = instr(cmovlbs_imm); break;
987     case 0x96: ic->f = instr(cmovlbc_imm); break;
988     case 0xa0: ic->f = instr(or_imm); break;
989     case 0xa4: ic->f = instr(cmoveq_imm); break;
990     case 0xa6: ic->f = instr(cmovne_imm); break;
991     case 0xa8: ic->f = instr(ornot_imm); break;
992     case 0xc0: ic->f = instr(xor_imm); break;
993     case 0xc4: ic->f = instr(cmovlt_imm); break;
994     case 0xc6: ic->f = instr(cmovge_imm); break;
995     case 0xc8: ic->f = instr(xornot_imm); break;
996     case 0xe4: ic->f = instr(cmovle_imm); break;
997     case 0xe6: ic->f = instr(cmovgt_imm); break;
998     default:fatal("[ Alpha: unimplemented function 0x%03x for"
999     " opcode 0x%02x ]\n", func, opcode);
1000     goto bad;
1001     }
1002     break;
1003     case 0x12:
1004     if (rc == ALPHA_ZERO) {
1005     ic->f = instr(nop);
1006     break;
1007     }
1008     ic->arg[0] = (size_t) &cpu->cd.alpha.r[rc];
1009     ic->arg[1] = (size_t) &cpu->cd.alpha.r[ra];
1010     if (func & 0x80)
1011     ic->arg[2] = (size_t)((rb << 3) + (func >> 8));
1012     else
1013     ic->arg[2] = (size_t) &cpu->cd.alpha.r[rb];
1014     switch (func & 0xff) {
1015     case 0x02: ic->f = instr(mskbl); break;
1016     case 0x06: ic->f = instr(extbl); break;
1017     case 0x0b: ic->f = instr(insbl); break;
1018     case 0x12: ic->f = instr(mskwl); break;
1019     case 0x16: ic->f = instr(extwl); break;
1020     case 0x1b: ic->f = instr(inswl); break;
1021     case 0x22: ic->f = instr(mskll); break;
1022     case 0x26: ic->f = instr(extll); break;
1023     case 0x2b: ic->f = instr(insll); break;
1024     case 0x30: ic->f = instr(zap); break;
1025     case 0x31: ic->f = instr(zapnot); break;
1026     case 0x32: ic->f = instr(mskql); break;
1027     case 0x34: ic->f = instr(srl); break;
1028     case 0x36: ic->f = instr(extql); break;
1029     case 0x39: ic->f = instr(sll); break;
1030     case 0x3b: ic->f = instr(insql); break;
1031     case 0x3c: ic->f = instr(sra); break;
1032     case 0x52: ic->f = instr(mskwh); break;
1033     case 0x57: ic->f = instr(inswh); break;
1034     case 0x5a: ic->f = instr(extwh); break;
1035     case 0x62: ic->f = instr(msklh); break;
1036     case 0x67: ic->f = instr(inslh); break;
1037     case 0x6a: ic->f = instr(extlh); break;
1038     case 0x72: ic->f = instr(mskqh); break;
1039     case 0x77: ic->f = instr(insqh); break;
1040     case 0x7a: ic->f = instr(extqh); break;
1041     case 0x82: ic->f = instr(mskbl_imm); break;
1042     case 0x86: ic->f = instr(extbl_imm); break;
1043     case 0x8b: ic->f = instr(insbl_imm); break;
1044     case 0x92: ic->f = instr(mskwl_imm); break;
1045     case 0x96: ic->f = instr(extwl_imm); break;
1046     case 0x9b: ic->f = instr(inswl_imm); break;
1047     case 0xa2: ic->f = instr(mskll_imm); break;
1048     case 0xa6: ic->f = instr(extll_imm); break;
1049     case 0xab: ic->f = instr(insll_imm); break;
1050     case 0xb0: ic->f = instr(zap_imm); break;
1051     case 0xb1: ic->f = instr(zapnot_imm); break;
1052     case 0xb2: ic->f = instr(mskql_imm); break;
1053     case 0xb4: ic->f = instr(srl_imm); break;
1054     case 0xb6: ic->f = instr(extql_imm); break;
1055     case 0xb9: ic->f = instr(sll_imm); break;
1056     case 0xbb: ic->f = instr(insql_imm); break;
1057     case 0xbc: ic->f = instr(sra_imm); break;
1058     case 0xd2: ic->f = instr(mskwh_imm); break;
1059     case 0xd7: ic->f = instr(inswh_imm); break;
1060     case 0xda: ic->f = instr(extwh_imm); break;
1061     case 0xe2: ic->f = instr(msklh_imm); break;
1062     case 0xe7: ic->f = instr(inslh_imm); break;
1063     case 0xea: ic->f = instr(extlh_imm); break;
1064     case 0xf2: ic->f = instr(mskqh_imm); break;
1065     case 0xf7: ic->f = instr(insqh_imm); break;
1066     case 0xfa: ic->f = instr(extqh_imm); break;
1067     default:fatal("[ Alpha: unimplemented function 0x%03x for"
1068     " opcode 0x%02x ]\n", func, opcode);
1069     goto bad;
1070     }
1071     break;
1072     case 0x13:
1073     if (rc == ALPHA_ZERO) {
1074     ic->f = instr(nop);
1075     break;
1076     }
1077     ic->arg[0] = (size_t) &cpu->cd.alpha.r[rc];
1078     ic->arg[1] = (size_t) &cpu->cd.alpha.r[ra];
1079     if (func & 0x80)
1080     ic->arg[2] = (size_t)((rb << 3) + (func >> 8));
1081     else
1082     ic->arg[2] = (size_t) &cpu->cd.alpha.r[rb];
1083     switch (func & 0xff) {
1084     case 0x00: ic->f = instr(mull); break;
1085     case 0x20: ic->f = instr(mulq); break;
1086     case 0x30: ic->f = instr(umulh); break;
1087     default:fatal("[ Alpha: unimplemented function 0x%03x for"
1088     " opcode 0x%02x ]\n", func, opcode);
1089     goto bad;
1090     }
1091     break;
1092     case 0x16:
1093     if (rc == ALPHA_ZERO) {
1094     ic->f = instr(nop);
1095     break;
1096     }
1097     ic->arg[0] = (size_t) &cpu->cd.alpha.f[rc];
1098     ic->arg[1] = (size_t) &cpu->cd.alpha.f[ra];
1099     ic->arg[2] = (size_t) &cpu->cd.alpha.f[rb];
1100     switch (func & 0x7ff) {
1101 dpavlin 22 case 0x02f: ic->f = instr(cvttq_c); break;
1102     case 0x0a0: ic->f = instr(addt); break;
1103     case 0x0a1: ic->f = instr(subt); break;
1104     case 0x0a2: ic->f = instr(mult); break;
1105     case 0x0a3: ic->f = instr(divt); break;
1106     case 0x0a5: ic->f = instr(cmpteq); break;
1107     case 0x0a6: ic->f = instr(cmptlt); break;
1108     case 0x0a7: ic->f = instr(cmptle); break;
1109     case 0x0be: ic->f = instr(cvtqt); break;
1110 dpavlin 14 default:fatal("[ Alpha: unimplemented function 0x%03x for"
1111     " opcode 0x%02x ]\n", func, opcode);
1112     goto bad;
1113     }
1114     break;
1115     case 0x17:
1116     if (rc == ALPHA_ZERO) {
1117     ic->f = instr(nop);
1118     break;
1119     }
1120     ic->arg[0] = (size_t) &cpu->cd.alpha.f[rc];
1121     ic->arg[1] = (size_t) &cpu->cd.alpha.f[ra];
1122     ic->arg[2] = (size_t) &cpu->cd.alpha.f[rb];
1123     switch (func & 0x7ff) {
1124     case 0x020:
1125 dpavlin 22 /* fabs (or fclr): */
1126 dpavlin 14 if (ra == 31 && rb == 31)
1127     ic->f = instr(clear);
1128 dpavlin 22 else
1129     ic->f = instr(fabs);
1130 dpavlin 14 break;
1131 dpavlin 22 case 0x021:
1132     ic->f = instr(fneg);
1133     break;
1134 dpavlin 14 default:fatal("[ Alpha: unimplemented function 0x%03x for"
1135     " opcode 0x%02x ]\n", func, opcode);
1136     goto bad;
1137     }
1138     break;
1139     case 0x18:
1140     switch (iword & 0xffff) {
1141     case 0x4000: /* mb */
1142     case 0x4400: /* wmb */
1143     ic->f = instr(nop);
1144     break;
1145     case 0xc000: /* rdcc ra */
1146     if (ra == ALPHA_ZERO) {
1147     ic->f = instr(nop);
1148     break;
1149     }
1150     ic->arg[0] = (size_t) &cpu->cd.alpha.r[ra];
1151     ic->f = instr(rdcc);
1152     break;
1153     default:fatal("[ Alpha: unimplemented function 0x%03x for"
1154     " opcode 0x%02x ]\n", func, opcode);
1155     goto bad;
1156     }
1157     break;
1158     case 0x1a:
1159     switch ((iword >> 14) & 3) {
1160     case 0: /* JMP */
1161     case 1: /* JSR */
1162     case 2: /* RET */
1163     ic->arg[0] = (size_t) &cpu->cd.alpha.r[ra];
1164     ic->arg[1] = (size_t) &cpu->cd.alpha.r[rb];
1165     if (ra == ALPHA_ZERO) {
1166     if (cpu->machine->show_trace_tree &&
1167     rb == ALPHA_RA)
1168     ic->f = instr(jsr_0_trace);
1169     else
1170     ic->f = instr(jsr_0);
1171     } else {
1172     if (cpu->machine->show_trace_tree)
1173     ic->f = instr(jsr_trace);
1174     else
1175     ic->f = instr(jsr);
1176     }
1177     break;
1178     default:fatal("[ Alpha: unimpl JSR type %i, ra=%i rb=%i ]\n",
1179     ((iword >> 14) & 3), ra, rb);
1180     goto bad;
1181     }
1182     break;
1183 dpavlin 22 case 0x30: /* BR */
1184     case 0x31: /* FBEQ */
1185     case 0x34: /* BSR */
1186     case 0x35: /* FBNE */
1187 dpavlin 14 case 0x38: /* BLBC */
1188 dpavlin 22 case 0x39: /* BEQ */
1189     case 0x3a: /* BLT */
1190     case 0x3b: /* BLE */
1191 dpavlin 14 case 0x3c: /* BLBS */
1192 dpavlin 22 case 0x3d: /* BNE */
1193     case 0x3e: /* BGE */
1194     case 0x3f: /* BGT */
1195 dpavlin 14 /* To avoid a GCC warning: */
1196     samepage_function = instr(nop);
1197 dpavlin 22 fp = 0;
1198 dpavlin 14 switch (opcode) {
1199     case 0x30:
1200     case 0x34:
1201     ic->f = instr(br);
1202     samepage_function = instr(br_samepage);
1203     if (ra != ALPHA_ZERO) {
1204     ic->f = instr(br_return);
1205     samepage_function = instr(br_return_samepage);
1206     }
1207     break;
1208     case 0x38:
1209     ic->f = instr(blbc);
1210     samepage_function = instr(blbc_samepage);
1211     break;
1212 dpavlin 22 case 0x31:
1213     fp = 1;
1214 dpavlin 14 case 0x39:
1215     ic->f = instr(beq);
1216     samepage_function = instr(beq_samepage);
1217     break;
1218     case 0x3a:
1219     ic->f = instr(blt);
1220     samepage_function = instr(blt_samepage);
1221     break;
1222     case 0x3b:
1223     ic->f = instr(ble);
1224     samepage_function = instr(ble_samepage);
1225     break;
1226     case 0x3c:
1227     ic->f = instr(blbs);
1228     samepage_function = instr(blbs_samepage);
1229     break;
1230 dpavlin 22 case 0x35:
1231     fp = 1;
1232 dpavlin 14 case 0x3d:
1233     ic->f = instr(bne);
1234     samepage_function = instr(bne_samepage);
1235     break;
1236     case 0x3e:
1237     ic->f = instr(bge);
1238     samepage_function = instr(bge_samepage);
1239     break;
1240     case 0x3f:
1241     ic->f = instr(bgt);
1242     samepage_function = instr(bgt_samepage);
1243     break;
1244     }
1245 dpavlin 22 if (fp)
1246     ic->arg[1] = (size_t) &cpu->cd.alpha.f[ra];
1247     else
1248     ic->arg[1] = (size_t) &cpu->cd.alpha.r[ra];
1249 dpavlin 14 ic->arg[0] = (iword & 0x001fffff) << 2;
1250     /* Sign-extend: */
1251     if (ic->arg[0] & 0x00400000)
1252     ic->arg[0] |= 0xffffffffff800000ULL;
1253     /* Branches are calculated as PC + 4 + offset. */
1254     ic->arg[0] = (size_t)(ic->arg[0] + 4);
1255     /* Special case: branch within the same page: */
1256     {
1257     uint64_t mask_within_page =
1258     ((ALPHA_IC_ENTRIES_PER_PAGE-1) << 2) | 3;
1259     uint64_t old_pc = addr;
1260     uint64_t new_pc = old_pc + (int32_t)ic->arg[0];
1261     if ((old_pc & ~mask_within_page) ==
1262     (new_pc & ~mask_within_page)) {
1263     ic->f = samepage_function;
1264     ic->arg[0] = (size_t) (
1265     cpu->cd.alpha.cur_ic_page +
1266     ((new_pc & mask_within_page) >> 2));
1267     }
1268     }
1269     break;
1270     default:fatal("[ UNIMPLEMENTED Alpha opcode 0x%x ]\n", opcode);
1271     goto bad;
1272     }
1273    
1274    
1275     #define DYNTRANS_TO_BE_TRANSLATED_TAIL
1276     #include "cpu_dyntrans.c"
1277     #undef DYNTRANS_TO_BE_TRANSLATED_TAIL
1278     }
1279    

  ViewVC Help
Powered by ViewVC 1.1.26