/[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 32 - (hide annotations)
Mon Oct 8 16:20:58 2007 UTC (16 years, 7 months ago) by dpavlin
File MIME type: text/plain
File size: 33909 byte(s)
++ trunk/HISTORY	(local)
$Id: HISTORY,v 1.1421 2006/11/06 05:32:37 debug Exp $
20060816	Adding a framework for emulated/virtual timers (src/timer.c),
		using only setitimer().
		Rewriting the mc146818 to use the new timer framework.
20060817	Adding a call to gettimeofday() every now and then (once every
		second, at the moment) to resynch the timer if it drifts.
		Beginning to convert the ISA timer interrupt mechanism (8253
		and 8259) to use the new timer framework.
		Removing the -I command line option.
20060819	Adding the -I command line option again, with new semantics.
		Working on Footbridge timer interrupts; NetBSD/NetWinder and
		NetBSD/CATS now run at correct speed, but unfortunately with
		HUGE delays during bootup.
20060821	Some minor m68k updates. Adding the first instruction: nop. :)
		Minor Alpha emulation updates.
20060822	Adding a FreeBSD development specific YAMON environment
		variable ("khz") (as suggested by Bruce M. Simpson).
		Moving YAMON environment variable initialization from
		machine_evbmips.c into promemul/yamon.c, and adding some more
		variables.
		Continuing on the LCA PCI bus controller (for Alpha machines).
20060823	Continuing on the timer stuff: experimenting with MIPS count/
		compare interrupts connected to the timer framework.
20060825	Adding bogus SCSI commands 0x51 (SCSICDROM_READ_DISCINFO) and
		0x52 (SCSICDROM_READ_TRACKINFO) to the SCSI emulation layer,
		to allow NetBSD/pmax 4.0_BETA to be installed from CDROM.
		Minor updates to the LCA PCI controller.
20060827	Implementing a CHIP8 cpu mode, and a corresponding CHIP8
		machine, for fun. Disassembly support for all instructions,
		and most of the common instructions have been implemented: mvi,
		mov_imm, add_imm, jmp, rand, cls, sprite, skeq_imm, jsr,
		skne_imm, bcd, rts, ldr, str, mov, or, and, xor, add, sub,
		font, ssound, sdelay, gdelay, bogus skup/skpr, skeq, skne.
20060828	Beginning to convert the CHIP8 cpu in the CHIP8 machine to a
		(more correct) RCA 180x cpu. (Disassembly for all 1802
		instructions has been implemented, but no execution yet, and
		no 1805 extended instructions.)
20060829	Minor Alpha emulation updates.
20060830	Beginning to experiment a little with PCI IDE for SGI O2.
		Fixing the cursor key mappings for MobilePro 770 emulation.
		Fixing the LK201 warning caused by recent NetBSD/pmax.
		The MIPS R41xx standby, suspend, and hibernate instructions now
		behave like the RM52xx/MIPS32/MIPS64 wait instruction.
		Fixing dev_wdc so it calculates correct (64-bit) offsets before
		giving them to diskimage_access().
20060831	Continuing on Alpha emulation (OSF1 PALcode).
20060901	Minor Alpha updates; beginning on virtual memory pagetables.
		Removed the limit for max nr of devices (in preparation for
		allowing devices' base addresses to be changed during runtime).
		Adding a hack for MIPS [d]mfc0 select 0 (except the count
		register), so that the coproc register is simply copied.
		The MIPS suspend instruction now exits the emulator, instead
		of being treated as a wait instruction (this causes NetBSD/
		hpcmips to get correct 'halt' behavior).
		The VR41xx RTC now returns correct time.
		Connecting the VR41xx timer to the timer framework (fixed at
		128 Hz, for now).
		Continuing on SPARC emulation, adding more instructions:
		restore, ba_xcc, ble. The rectangle drawing demo works :)
		Removing the last traces of the old ENABLE_CACHE_EMULATION
		MIPS stuff (not usable with dyntrans anyway).
20060902	Splitting up src/net.c into several smaller files in its own
		subdirectory (src/net/).
20060903	Cleanup of the files in src/net/, to make them less ugly.
20060904	Continuing on the 'settings' subsystem.
		Minor progress on the SPARC emulation mode.
20060905	Cleanup of various things, and connecting the settings
		infrastructure to various subsystems (emul, machine, cpu, etc).
		Changing the lk201 mouse update routine to not rely on any
		emulated hardware framebuffer cursor coordinates, but instead
		always do (semi-usable) relative movements.
20060906	Continuing on the lk201 mouse stuff. Mouse behaviour with
		multiple framebuffers (which was working in Ultrix) is now
		semi-broken (but it still works, in a way).
		Moving the documentation about networking into its own file
		(networking.html), and refreshing it a bit. Adding an example
		of how to use ethernet frame direct-access (udp_snoop).
20060907	Continuing on the settings infrastructure.
20060908	Minor updates to SH emulation: for 32-bit emulation: delay
		slots and the 'jsr @Rn' instruction. I'm putting 64-bit SH5 on
		ice, for now.
20060909-10	Implementing some more 32-bit SH instructions. Removing the
		64-bit mode completely. Enough has now been implemented to run
		the rectangle drawing demo. :-)
20060912	Adding more SH instructions.
20060916	Continuing on SH emulation (some more instructions: div0u,
		div1, rotcl/rotcr, more mov instructions, dt, braf, sets, sett,
		tst_imm, dmuls.l, subc, ldc_rm_vbr, movt, clrt, clrs, clrmac).
		Continuing on the settings subsystem (beginning on reading/
		writing settings, removing bugs, and connecting more cpus to
		the framework).
20060919	More work on SH emulation; adding an ldc banked instruction,
		and attaching a 640x480 framebuffer to the Dreamcast machine
		mode (NetBSD/dreamcast prints the NetBSD copyright banner :-),
		and then panics).
20060920	Continuing on the settings subsystem.
20060921	Fixing the Footbridge timer stuff so that NetBSD/cats and
		NetBSD/netwinder boot up without the delays.
20060922	Temporarily hardcoding MIPS timer interrupt to 100 Hz. With
		'wait' support disabled, NetBSD/malta and Linux/malta run at
		correct speed.
20060923	Connecting dev_gt to the timer framework, so that NetBSD/cobalt
		runs at correct speed.
		Moving SH4-specific memory mapped registers into its own
		device (dev_sh4.c).
		Running with -N now prints "idling" instead of bogus nr of
		instrs/second (which isn't valid anyway) while idling.
20060924	Algor emulation should now run at correct speed.
		Adding disassembly support for some MIPS64 revision 2
		instructions: ext, dext, dextm, dextu.
20060926	The timer framework now works also when the MIPS wait
		instruction is used.
20060928	Re-implementing checks for coprocessor availability for MIPS
		cop0 instructions. (Thanks to Carl van Schaik for noticing the
		lack of cop0 availability checks.)
20060929	Implementing an instruction combination hack which treats
		NetBSD/pmax' idle loop as a wait-like instruction.
20060930	The ENTRYHI_R_MASK was missing in (at least) memory_mips_v2p.c,
		causing TLB lookups to sometimes succeed when they should have
		failed. (A big thank you to Juli Mallett for noticing the
		problem.)
		Adding disassembly support for more MIPS64 revision 2 opcodes
		(seb, seh, wsbh, jalr.hb, jr.hb, synci, ins, dins, dinsu,
		dinsm, dsbh, dshd, ror, dror, rorv, drorv, dror32). Also
		implementing seb, seh, dsbh, dshd, and wsbh.
		Implementing an instruction combination hack for Linux/pmax'
		idle loop, similar to the NetBSD/pmax case.
20061001	Changing the NetBSD/sgimips install instructions to extract
		files from an iso image, instead of downloading them via ftp.
20061002	More-than-31-bit userland addresses in memory_mips_v2p.c were
		not actually working; applying a fix from Carl van Schaik to
		enable them to work + making some other updates (adding kuseg
		support).
		Fixing hpcmips (vr41xx) timer initialization.
		Experimenting with O(n)->O(1) reduction in the MIPS TLB lookup
		loop. Seems to work both for R3000 and non-R3000.
20061003	Continuing a little on SH emulation (adding more control
		registers; mini-cleanup of memory_sh.c).
20061004	Beginning on a dev_rtc, a clock/timer device for the test
		machines; also adding a demo, and some documentation.
		Fixing a bug in SH "mov.w @(disp,pc),Rn" (the result wasn't
		sign-extended), and adding the addc and ldtlb instructions.
20061005	Contining on SH emulation: virtual to physical address
		translation, and a skeleton exception mechanism.
20061006	Adding more SH instructions (various loads and stores, rte,
		negc, muls.w, various privileged register-move instructions).
20061007	More SH instructions: various move instructions, trapa, div0s,
		float, fdiv, ftrc.
		Continuing on dev_rtc; removing the rtc demo.
20061008	Adding a dummy Dreamcast PROM module. (Homebrew Dreamcast
		programs using KOS libs need this.)
		Adding more SH instructions: "stc vbr,rn", rotl, rotr, fsca,
		fmul, fadd, various floating-point moves, etc. A 256-byte
		demo for Dreamcast runs :-)
20061012	Adding the SH "lds Rm,pr" and bsr instructions.
20061013	More SH instructions: "sts fpscr,rn", tas.b, and some more
		floating point instructions, cmp/str, and more moves.
		Adding a dummy dev_pvr (Dreamcast graphics controller).
20061014	Generalizing the expression evaluator (used in the built-in
		debugger) to support parentheses and +-*/%^&|.
20061015	Removing the experimental tlb index hint code in
		mips_memory_v2p.c, since it didn't really have any effect.
20061017	Minor SH updates; adding the "sts pr,Rn", fcmp/gt, fneg,
		frchg, and some other instructions. Fixing missing sign-
		extension in an 8-bit load instruction.
20061019	Adding a simple dev_dreamcast_rtc.
		Implementing memory-mapped access to the SH ITLB/UTLB arrays.
20061021	Continuing on various SH and Dreamcast things: sh4 timers,
		debug messages for dev_pvr, fixing some virtual address
		translation bugs, adding the bsrf instruction.
		The NetBSD/dreamcast GENERIC_MD kernel now reaches userland :)
		Adding a dummy dev_dreamcast_asic.c (not really useful yet).
		Implementing simple support for Store Queues.
		Beginning on the PVR Tile Accelerator.
20061022	Generalizing the PVR framebuffer to support off-screen drawing,
		multiple bit-depths, etc. (A small speed penalty, but most
		likely worth it.)
		Adding more SH instructions (mulu.w, fcmp/eq, fsub, fmac,
		fschg, and some more); correcting bugs in "fsca" and "float".
20061024	Adding the SH ftrv (matrix * vector) instruction. Marcus
		Comstedt's "tatest" example runs :) (wireframe only).
		Correcting disassembly for SH floating point instructions that
		use the xd* registers.
		Adding the SH fsts instruction.
		In memory_device_dyntrans_access(), only the currently used
		range is now invalidated, and not the entire device range.
20061025	Adding a dummy AVR32 cpu mode skeleton.
20061026	Various Dreamcast updates; beginning on a Maple bus controller.
20061027	Continuing on the Maple bus. A bogus Controller, Keyboard, and
		Mouse can now be detected by NetBSD and KOS homebrew programs.
		Cleaning up the SH4 Timer Management Unit, and beginning on
		SH4 interrupts.
		Implementing the Dreamcast SYSASIC.
20061028	Continuing on the SYSASIC.
		Adding the SH fsqrt instruction.
		memory_sh.c now actually scans the ITLB.
		Fixing a bug in dev_sh4.c, related to associative writes into
		the memory-mapped UTLB array. NetBSD/dreamcast now reaches
		userland stably, and prints the "Terminal type?" message :-]
		Implementing enough of the Dreamcast keyboard to make NetBSD
		accept it for input.
		Enabling SuperH for stable (non-development) builds.
		Adding NetBSD/dreamcast to the documentation, although it
		doesn't support root-on-nfs yet.
20061029	Changing usleep(1) calls in the debugger to to usleep(10000)
		(according to Brian Foley, this makes GXemul run better on
		MacOS X).
		Making the Maple "Controller" do something (enough to barely
		interact with dcircus.elf).
20061030-31	Some progress on the PVR. More test programs start running (but
		with strange output).
		Various other SH4-related updates.
20061102	Various Dreamcast and SH4 updates; more KOS demos run now.
20061104	Adding a skeleton dev_mb8696x.c (the Dreamcast's LAN adapter).
20061105	Continuing on the MB8696x; NetBSD/dreamcast detects it as mbe0.
		Testing for the release.

==============  RELEASE 0.4.3  ==============


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

  ViewVC Help
Powered by ViewVC 1.1.26