1/*	$NetBSD: fpu.c,v 1.29 2019/03/01 11:06:55 pgoyette Exp $ */
2
3/*
4 * Copyright (c) 1992, 1993
5 *	The Regents of the University of California.  All rights reserved.
6 *
7 * This software was developed by the Computer Systems Engineering group
8 * at Lawrence Berkeley Laboratory under DARPA contract BG 91-66 and
9 * contributed to Berkeley.
10 *
11 * All advertising materials mentioning features or use of this software
12 * must display the following acknowledgement:
13 *	This product includes software developed by the University of
14 *	California, Lawrence Berkeley Laboratory.
15 *
16 * Redistribution and use in source and binary forms, with or without
17 * modification, are permitted provided that the following conditions
18 * are met:
19 * 1. Redistributions of source code must retain the above copyright
20 *    notice, this list of conditions and the following disclaimer.
21 * 2. Redistributions in binary form must reproduce the above copyright
22 *    notice, this list of conditions and the following disclaimer in the
23 *    documentation and/or other materials provided with the distribution.
24 * 3. Neither the name of the University nor the names of its contributors
25 *    may be used to endorse or promote products derived from this software
26 *    without specific prior written permission.
27 *
28 * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
29 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
30 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
31 * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
32 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
33 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
34 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
35 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
36 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
37 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
38 * SUCH DAMAGE.
39 *
40 *	@(#)fpu.c	8.1 (Berkeley) 6/11/93
41 */
42
43#include <sys/cdefs.h>
44__KERNEL_RCSID(0, "$NetBSD: fpu.c,v 1.29 2019/03/01 11:06:55 pgoyette Exp $");
45
46#include <sys/param.h>
47#include <sys/proc.h>
48#include <sys/signal.h>
49#include <sys/systm.h>
50#include <sys/syslog.h>
51#include <sys/signalvar.h>
52#include <sys/compat_stub.h>
53
54#include <machine/instr.h>
55#include <machine/reg.h>
56
57#include <sparc/fpu/fpu_emu.h>
58#include <sparc/fpu/fpu_extern.h>
59
60int fpe_debug = 0;
61
62#ifdef DEBUG
63/*
64 * Dump a `fpn' structure.
65 */
66void
67fpu_dumpfpn(struct fpn *fp)
68{
69	static const char *class[] = {
70		"SNAN", "QNAN", "ZERO", "NUM", "INF"
71	};
72
73	printf("%s %c.%x %x %x %xE%d", class[fp->fp_class + 2],
74		fp->fp_sign ? '-' : ' ',
75		fp->fp_mant[0],	fp->fp_mant[1],
76		fp->fp_mant[2], fp->fp_mant[3],
77		fp->fp_exp);
78}
79#endif
80
81/*
82 * fpu_execute returns the following error numbers (0 = no error):
83 */
84#define	FPE		1	/* take a floating point exception */
85#define	NOTFPU		2	/* not an FPU instruction */
86
87/*
88 * Translate current exceptions into `first' exception.  The
89 * bits go the wrong way for ffs() (0x10 is most important, etc).
90 * There are only 5, so do it the obvious way.
91 */
92#define	X1(x) x
93#define	X2(x) x,x
94#define	X4(x) x,x,x,x
95#define	X8(x) X4(x),X4(x)
96#define	X16(x) X8(x),X8(x)
97
98static char cx_to_trapx[] = {
99	X1(FSR_NX),
100	X2(FSR_DZ),
101	X4(FSR_UF),
102	X8(FSR_OF),
103	X16(FSR_NV)
104};
105static u_char fpu_codes_native[] = {
106	X1(FPE_FLTRES),
107	X2(FPE_FLTDIV),
108	X4(FPE_FLTUND),
109	X8(FPE_FLTOVF),
110	X16(FPE_FLTINV)
111};
112static u_char fpu_codes_sunos[] = {
113	X1(FPE_FLTINEX_TRAP),
114	X2(FPE_FLTDIV_TRAP),
115	X4(FPE_FLTUND_TRAP),
116	X8(FPE_FLTOVF_TRAP),
117	X16(FPE_FLTOPERR_TRAP)
118};
119
120/* Note: SVR4(Solaris) FPE_* codes happen to be compatible with ours */
121
122/*
123 * The FPU gave us an exception.  Clean up the mess.  Note that the
124 * fp queue can only have FPops in it, never load/store FP registers
125 * nor FBfcc instructions.  Experiments with `crashme' prove that
126 * unknown FPops do enter the queue, however.
127 */
128int
129fpu_cleanup(
130	struct lwp *l,
131#ifndef SUN4U
132	struct fpstate *fs
133#else /* SUN4U */
134	struct fpstate64 *fs
135#endif /* SUN4U */
136	)
137{
138	int i, fsr = fs->fs_fsr, error;
139	struct proc *p = l->l_proc;
140	union instr instr;
141	struct fpemu fe;
142	u_char *fpu_codes;
143	int code = 0;
144	int ret;
145	const struct emul *sunos_emul;
146
147	MODULE_HOOK_CALL(get_emul_sunos_hook, (&sunos_emul), enosys(), ret);
148
149	if (ret == 0 && p->p_emul == sunos_emul)
150		fpu_codes = fpu_codes_sunos;
151	else
152		fpu_codes = fpu_codes_native;
153
154	switch ((fsr >> FSR_FTT_SHIFT) & FSR_FTT_MASK) {
155
156	case FSR_TT_NONE:
157		panic("fpu_cleanup: No fault");	/* ??? */
158		break;
159
160	case FSR_TT_IEEE:
161		DPRINTF(FPE_INSN, ("fpu_cleanup: FSR_TT_IEEE\n"));
162		/* XXX missing trap address! */
163		if ((i = fsr & FSR_CX) == 0)
164			panic("fpu ieee trap, but no exception");
165		code = fpu_codes[i - 1];
166		break;		/* XXX should return, but queue remains */
167
168	case FSR_TT_UNFIN:
169		DPRINTF(FPE_INSN, ("fpu_cleanup: FSR_TT_UNFIN\n"));
170#ifdef SUN4U
171		if (fs->fs_qsize == 0) {
172			printf("fpu_cleanup: unfinished fpop");
173			/* The book sez reexecute or emulate. */
174			return (0);
175		}
176		break;
177
178#endif /* SUN4U */
179	case FSR_TT_UNIMP:
180		DPRINTF(FPE_INSN, ("fpu_cleanup: FSR_TT_UNIMP\n"));
181		if (fs->fs_qsize == 0)
182			panic("fpu_cleanup: unimplemented fpop");
183		break;
184
185	case FSR_TT_SEQ:
186		panic("fpu sequence error");
187		/* NOTREACHED */
188
189	case FSR_TT_HWERR:
190		DPRINTF(FPE_INSN, ("fpu_cleanup: FSR_TT_HWERR\n"));
191		log(LOG_ERR, "fpu hardware error (%s[%d])\n",
192		    p->p_comm, p->p_pid);
193		uprintf("%s[%d]: fpu hardware error\n", p->p_comm, p->p_pid);
194		code = SI_NOINFO;
195		goto out;
196
197	default:
198		printf("fsr=0x%x\n", fsr);
199		panic("fpu error");
200	}
201
202	/* emulate the instructions left in the queue */
203	fe.fe_fpstate = fs;
204	for (i = 0; i < fs->fs_qsize; i++) {
205		instr.i_int = fs->fs_queue[i].fq_instr;
206		if (instr.i_any.i_op != IOP_reg ||
207		    (instr.i_op3.i_op3 != IOP3_FPop1 &&
208		     instr.i_op3.i_op3 != IOP3_FPop2))
209			panic("bogus fpu queue");
210		error = fpu_execute(&fe, instr);
211		if (error == 0)
212			continue;
213
214		switch (error) {
215		case FPE:
216			code = fpu_codes[(fs->fs_fsr & FSR_CX) - 1];
217			break;
218
219		case NOTFPU:
220#ifdef SUN4U
221#ifdef DEBUG
222			printf("fpu_cleanup: not an FPU error -- sending SIGILL\n");
223#endif
224#endif /* SUN4U */
225			code = SI_NOINFO;
226			break;
227
228		default:
229			panic("fpu_cleanup 3");
230			/* NOTREACHED */
231		}
232		/* XXX should stop here, but queue remains */
233	}
234out:
235	fs->fs_qsize = 0;
236	return (code);
237}
238
239#ifdef notyet
240/*
241 * If we have no FPU at all (are there any machines like this out
242 * there!?) we have to emulate each instruction, and we need a pointer
243 * to the trapframe so that we can step over them and do FBfcc's.
244 * We know the `queue' is empty, though; we just want to emulate
245 * the instruction at tf->tf_pc.
246 */
247fpu_emulate(l, tf, fs)
248	struct lwp *l;
249	struct trapframe *tf;
250#ifndef SUN4U
251	struct fpstate *fs;
252#else /* SUN4U */
253	struct fpstate64 *fs;
254#endif /* SUN4U */
255{
256
257	do {
258		fetch instr from pc
259		decode
260		if (integer instr) {
261			struct pcb *pcb = lwp_getpcb(l);
262			/*
263			 * We do this here, rather than earlier, to avoid
264			 * losing even more badly than usual.
265			 */
266			if (pcb->pcb_uw) {
267				write_user_windows();
268				if (rwindow_save(l))
269					sigexit(l, SIGILL);
270			}
271			if (loadstore) {
272				do_it;
273				pc = npc, npc += 4
274			} else if (fbfcc) {
275				do_annul_stuff;
276			} else
277				return;
278		} else if (fpu instr) {
279			fe.fe_fsr = fs->fs_fsr &= ~FSR_CX;
280			error = fpu_execute(&fe, fs, instr);
281			switch (error) {
282				etc;
283			}
284		} else
285			return;
286		if (want to reschedule)
287			return;
288	} while (error == 0);
289}
290#endif
291
292/*
293 * Execute an FPU instruction (one that runs entirely in the FPU; not
294 * FBfcc or STF, for instance).  On return, fe->fe_fs->fs_fsr will be
295 * modified to reflect the setting the hardware would have left.
296 *
297 * Note that we do not catch all illegal opcodes, so you can, for instance,
298 * multiply two integers this way.
299 */
300int
301fpu_execute(struct fpemu *fe, union instr instr)
302{
303	struct fpn *fp;
304#ifndef SUN4U
305	int opf, rs1, rs2, rd, type, mask, fsr, cx;
306	struct fpstate *fs;
307#else /* SUN4U */
308	int opf, rs1, rs2, rd, type, mask, fsr, cx, i, cond;
309	struct fpstate64 *fs;
310#endif /* SUN4U */
311	u_int space[4];
312
313	/*
314	 * `Decode' and execute instruction.  Start with no exceptions.
315	 * The type of any i_opf opcode is in the bottom two bits, so we
316	 * squish them out here.
317	 */
318	opf = instr.i_opf.i_opf;
319	/*
320	 * The low two bits of the opf field for floating point insns usually
321	 * correspond to the operation width:
322	 *
323	 *	0:	Invalid
324	 *	1:	Single precision float
325	 *	2:	Double precision float
326	 *	3:	Quad precision float
327	 *
328	 * The exceptions are the integer to float conversion instructions.
329	 *
330	 * For double and quad precision, the low bit if the rs or rd field
331	 * is actually the high bit of the register number.
332	 */
333
334	type = opf & 3;
335	mask = 0x3 >> (3 - type);
336
337	rs1 = instr.i_opf.i_rs1;
338	rs1 = (rs1 & ~mask) | ((rs1 & mask & 0x1) << 5);
339	rs2 = instr.i_opf.i_rs2;
340	rs2 = (rs2 & ~mask) | ((rs2 & mask & 0x1) << 5);
341	rd = instr.i_opf.i_rd;
342	rd = (rd & ~mask) | ((rd & mask & 0x1) << 5);
343#ifdef DIAGNOSTIC
344	if ((rs1 | rs2 | rd) & mask)
345		/* This may be an FPU insn but it is illegal. */
346		return (NOTFPU);
347#endif
348	fs = fe->fe_fpstate;
349	fe->fe_fsr = fs->fs_fsr & ~FSR_CX;
350	fe->fe_cx = 0;
351#ifdef SUN4U
352	/*
353	 * Check to see if we're dealing with a fancy cmove and handle
354	 * it first.
355	 */
356	if (instr.i_op3.i_op3 == IOP3_FPop2 && (opf&0xff0) != (FCMP&0xff0)) {
357		switch (opf >>= 2) {
358		case FMVFC0 >> 2:
359			DPRINTF(FPE_INSN, ("fpu_execute: FMVFC0\n"));
360			cond = (fs->fs_fsr>>FSR_FCC_SHIFT)&FSR_FCC_MASK;
361			if (instr.i_fmovcc.i_cond != cond) return(0); /* success */
362			rs1 = fs->fs_regs[rs2];
363			goto mov;
364		case FMVFC1 >> 2:
365			DPRINTF(FPE_INSN, ("fpu_execute: FMVFC1\n"));
366			cond = (fs->fs_fsr>>FSR_FCC1_SHIFT)&FSR_FCC_MASK;
367			if (instr.i_fmovcc.i_cond != cond) return(0); /* success */
368			rs1 = fs->fs_regs[rs2];
369			goto mov;
370		case FMVFC2 >> 2:
371			DPRINTF(FPE_INSN, ("fpu_execute: FMVFC2\n"));
372			cond = (fs->fs_fsr>>FSR_FCC2_SHIFT)&FSR_FCC_MASK;
373			if (instr.i_fmovcc.i_cond != cond) return(0); /* success */
374			rs1 = fs->fs_regs[rs2];
375			goto mov;
376		case FMVFC3 >> 2:
377			DPRINTF(FPE_INSN, ("fpu_execute: FMVFC3\n"));
378			cond = (fs->fs_fsr>>FSR_FCC3_SHIFT)&FSR_FCC_MASK;
379			if (instr.i_fmovcc.i_cond != cond) return(0); /* success */
380			rs1 = fs->fs_regs[rs2];
381			goto mov;
382		case FMVIC >> 2:
383			/* Presume we're curlwp */
384			DPRINTF(FPE_INSN, ("fpu_execute: FMVIC\n"));
385			cond = (curlwp->l_md.md_tf->tf_tstate>>TSTATE_CCR_SHIFT)&PSR_ICC;
386			if (instr.i_fmovcc.i_cond != cond) return(0); /* success */
387			rs1 = fs->fs_regs[rs2];
388			goto mov;
389		case FMVXC >> 2:
390			/* Presume we're curlwp */
391			DPRINTF(FPE_INSN, ("fpu_execute: FMVXC\n"));
392			cond = (curlwp->l_md.md_tf->tf_tstate>>(TSTATE_CCR_SHIFT+XCC_SHIFT))&PSR_ICC;
393			if (instr.i_fmovcc.i_cond != cond) return(0); /* success */
394			rs1 = fs->fs_regs[rs2];
395			goto mov;
396		case FMVRZ >> 2:
397			/* Presume we're curlwp */
398			DPRINTF(FPE_INSN, ("fpu_execute: FMVRZ\n"));
399			rs1 = instr.i_fmovr.i_rs1;
400			if (rs1 != 0 && (int64_t)curlwp->l_md.md_tf->tf_global[rs1] != 0)
401				return (0); /* success */
402			rs1 = fs->fs_regs[rs2];
403			goto mov;
404		case FMVRLEZ >> 2:
405			/* Presume we're curlwp */
406			DPRINTF(FPE_INSN, ("fpu_execute: FMVRLEZ\n"));
407			rs1 = instr.i_fmovr.i_rs1;
408			if (rs1 != 0 && (int64_t)curlwp->l_md.md_tf->tf_global[rs1] > 0)
409				return (0); /* success */
410			rs1 = fs->fs_regs[rs2];
411			goto mov;
412		case FMVRLZ >> 2:
413			/* Presume we're curlwp */
414			DPRINTF(FPE_INSN, ("fpu_execute: FMVRLZ\n"));
415			rs1 = instr.i_fmovr.i_rs1;
416			if (rs1 == 0 || (int64_t)curlwp->l_md.md_tf->tf_global[rs1] >= 0)
417				return (0); /* success */
418			rs1 = fs->fs_regs[rs2];
419			goto mov;
420		case FMVRNZ >> 2:
421			/* Presume we're curlwp */
422			DPRINTF(FPE_INSN, ("fpu_execute: FMVRNZ\n"));
423			rs1 = instr.i_fmovr.i_rs1;
424			if (rs1 == 0 || (int64_t)curlwp->l_md.md_tf->tf_global[rs1] == 0)
425				return (0); /* success */
426			rs1 = fs->fs_regs[rs2];
427			goto mov;
428		case FMVRGZ >> 2:
429			/* Presume we're curlwp */
430			DPRINTF(FPE_INSN, ("fpu_execute: FMVRGZ\n"));
431			rs1 = instr.i_fmovr.i_rs1;
432			if (rs1 == 0 || (int64_t)curlwp->l_md.md_tf->tf_global[rs1] <= 0)
433				return (0); /* success */
434			rs1 = fs->fs_regs[rs2];
435			goto mov;
436		case FMVRGEZ >> 2:
437			/* Presume we're curlwp */
438			DPRINTF(FPE_INSN, ("fpu_execute: FMVRGEZ\n"));
439			rs1 = instr.i_fmovr.i_rs1;
440			if (rs1 != 0 && (int64_t)curlwp->l_md.md_tf->tf_global[rs1] < 0)
441				return (0); /* success */
442			rs1 = fs->fs_regs[rs2];
443			goto mov;
444		default:
445			DPRINTF(FPE_INSN,
446				("fpu_execute: unknown v9 FP inst %x opf %x\n",
447					instr.i_int, opf));
448			return (NOTFPU);
449		}
450	}
451#endif /* SUN4U */
452	switch (opf >>= 2) {
453
454	default:
455		DPRINTF(FPE_INSN,
456			("fpu_execute: unknown basic FP inst %x opf %x\n",
457				instr.i_int, opf));
458		return (NOTFPU);
459
460	case FMOV >> 2:		/* these should all be pretty obvious */
461		DPRINTF(FPE_INSN, ("fpu_execute: FMOV\n"));
462		rs1 = fs->fs_regs[rs2];
463		goto mov;
464
465	case FNEG >> 2:
466		DPRINTF(FPE_INSN, ("fpu_execute: FNEG\n"));
467		rs1 = fs->fs_regs[rs2] ^ (1 << 31);
468		goto mov;
469
470	case FABS >> 2:
471		DPRINTF(FPE_INSN, ("fpu_execute: FABS\n"));
472		rs1 = fs->fs_regs[rs2] & ~(1 << 31);
473	mov:
474#ifndef SUN4U
475		fs->fs_regs[rd] = rs1;
476#else /* SUN4U */
477		i = 1<<(type-1);
478		fs->fs_regs[rd++] = rs1;
479		while (--i > 0)
480			fs->fs_regs[rd++] = fs->fs_regs[++rs2];
481#endif /* SUN4U */
482		fs->fs_fsr = fe->fe_fsr;
483		return (0);	/* success */
484
485	case FSQRT >> 2:
486		DPRINTF(FPE_INSN, ("fpu_execute: FSQRT\n"));
487		fpu_explode(fe, &fe->fe_f1, type, rs2);
488		fp = fpu_sqrt(fe);
489		break;
490
491	case FADD >> 2:
492		DPRINTF(FPE_INSN, ("fpu_execute: FADD\n"));
493		fpu_explode(fe, &fe->fe_f1, type, rs1);
494		fpu_explode(fe, &fe->fe_f2, type, rs2);
495		fp = fpu_add(fe);
496		break;
497
498	case FSUB >> 2:
499		DPRINTF(FPE_INSN, ("fpu_execute: FSUB\n"));
500		fpu_explode(fe, &fe->fe_f1, type, rs1);
501		fpu_explode(fe, &fe->fe_f2, type, rs2);
502		fp = fpu_sub(fe);
503		break;
504
505	case FMUL >> 2:
506		DPRINTF(FPE_INSN, ("fpu_execute: FMUL\n"));
507		fpu_explode(fe, &fe->fe_f1, type, rs1);
508		fpu_explode(fe, &fe->fe_f2, type, rs2);
509		fp = fpu_mul(fe);
510		break;
511
512	case FDIV >> 2:
513		DPRINTF(FPE_INSN, ("fpu_execute: FDIV\n"));
514		fpu_explode(fe, &fe->fe_f1, type, rs1);
515		fpu_explode(fe, &fe->fe_f2, type, rs2);
516		fp = fpu_div(fe);
517		break;
518
519	case FCMP >> 2:
520		DPRINTF(FPE_INSN, ("fpu_execute: FCMP\n"));
521		fpu_explode(fe, &fe->fe_f1, type, rs1);
522		fpu_explode(fe, &fe->fe_f2, type, rs2);
523		fpu_compare(fe, 0);
524		goto cmpdone;
525
526	case FCMPE >> 2:
527		DPRINTF(FPE_INSN, ("fpu_execute: FCMPE\n"));
528		fpu_explode(fe, &fe->fe_f1, type, rs1);
529		fpu_explode(fe, &fe->fe_f2, type, rs2);
530		fpu_compare(fe, 1);
531	cmpdone:
532		/*
533		 * The only possible exception here is NV; catch it
534		 * early and get out, as there is no result register.
535		 */
536		cx = fe->fe_cx;
537		fsr = fe->fe_fsr | (cx << FSR_CX_SHIFT);
538		if (cx != 0) {
539			if (fsr & (FSR_NV << FSR_TEM_SHIFT)) {
540				fs->fs_fsr = (fsr & ~FSR_FTT) |
541				    (FSR_TT_IEEE << FSR_FTT_SHIFT);
542				return (FPE);
543			}
544			fsr |= FSR_NV << FSR_AX_SHIFT;
545		}
546		fs->fs_fsr = fsr;
547		return (0);
548
549	case FSMULD >> 2:
550	case FDMULX >> 2:
551		DPRINTF(FPE_INSN, ("fpu_execute: FSMULx\n"));
552		if (type == FTYPE_EXT)
553			return (NOTFPU);
554		fpu_explode(fe, &fe->fe_f1, type, rs1);
555		fpu_explode(fe, &fe->fe_f2, type, rs2);
556		type++;	/* single to double, or double to quad */
557		fp = fpu_mul(fe);
558		break;
559
560#ifdef SUN4U
561	case FXTOS >> 2:
562	case FXTOD >> 2:
563	case FXTOQ >> 2:
564		DPRINTF(FPE_INSN, ("fpu_execute: FXTOx\n"));
565		type = FTYPE_LNG;
566		fpu_explode(fe, fp = &fe->fe_f1, type, rs2);
567		type = opf & 3;	/* sneaky; depends on instruction encoding */
568		break;
569
570	case FTOX >> 2:
571		DPRINTF(FPE_INSN, ("fpu_execute: FTOX\n"));
572		fpu_explode(fe, fp = &fe->fe_f1, type, rs2);
573		type = FTYPE_LNG;
574		/* Recalculate destination register */
575		rd = instr.i_opf.i_rd;
576		break;
577
578#endif /* SUN4U */
579	case FTOI >> 2:
580		DPRINTF(FPE_INSN, ("fpu_execute: FTOI\n"));
581		fpu_explode(fe, fp = &fe->fe_f1, type, rs2);
582		type = FTYPE_INT;
583		/* Recalculate destination register */
584		rd = instr.i_opf.i_rd;
585		break;
586
587	case FTOS >> 2:
588	case FTOD >> 2:
589	case FTOQ >> 2:
590		DPRINTF(FPE_INSN, ("fpu_execute: FTOx\n"));
591		fpu_explode(fe, fp = &fe->fe_f1, type, rs2);
592		/* Recalculate rd with correct type info. */
593		type = opf & 3;	/* sneaky; depends on instruction encoding */
594		mask = 0x3 >> (3 - type);
595		rd = instr.i_opf.i_rd;
596		rd = (rd & ~mask) | ((rd & mask & 0x1) << 5);
597		break;
598	}
599
600	/*
601	 * ALU operation is complete.  Collapse the result and then check
602	 * for exceptions.  If we got any, and they are enabled, do not
603	 * alter the destination register, just stop with an exception.
604	 * Otherwise set new current exceptions and accrue.
605	 */
606	fpu_implode(fe, fp, type, space);
607	cx = fe->fe_cx;
608	fsr = fe->fe_fsr;
609	if (cx != 0) {
610		mask = (fsr >> FSR_TEM_SHIFT) & FSR_TEM_MASK;
611		if (cx & mask) {
612			/* not accrued??? */
613			fs->fs_fsr = (fsr & ~FSR_FTT) |
614			    (FSR_TT_IEEE << FSR_FTT_SHIFT) |
615			    (cx_to_trapx[(cx & mask) - 1] << FSR_CX_SHIFT);
616			return (FPE);
617		}
618		fsr |= (cx << FSR_CX_SHIFT) | (cx << FSR_AX_SHIFT);
619	}
620	fs->fs_fsr = fsr;
621	DPRINTF(FPE_REG, ("-> %c%d\n", (type == FTYPE_LNG) ? 'x' :
622		((type == FTYPE_INT) ? 'i' :
623			((type == FTYPE_SNG) ? 's' :
624				((type == FTYPE_DBL) ? 'd' :
625					((type == FTYPE_EXT) ? 'q' : '?')))),
626		rd));
627	fs->fs_regs[rd] = space[0];
628	if (type >= FTYPE_DBL || type == FTYPE_LNG) {
629		fs->fs_regs[rd + 1] = space[1];
630		if (type > FTYPE_DBL) {
631			fs->fs_regs[rd + 2] = space[2];
632			fs->fs_regs[rd + 3] = space[3];
633		}
634	}
635	return (0);	/* success */
636}
637