1*16ebabc4Splunky /*	Id: softfloat.c,v 1.1 2012/01/01 16:20:55 ragge Exp 	*/
2*16ebabc4Splunky /*	$NetBSD: softfloat.c,v 1.1.1.1 2012/01/11 20:33:21 plunky Exp $	*/
3*16ebabc4Splunky 
4*16ebabc4Splunky /*
5*16ebabc4Splunky  * Copyright (c) 2008 Anders Magnusson. All rights reserved.
6*16ebabc4Splunky  *
7*16ebabc4Splunky  * Redistribution and use in source and binary forms, with or without
8*16ebabc4Splunky  * modification, are permitted provided that the following conditions
9*16ebabc4Splunky  * are met:
10*16ebabc4Splunky  * 1. Redistributions of source code must retain the above copyright
11*16ebabc4Splunky  *    notice, this list of conditions and the following disclaimer.
12*16ebabc4Splunky  * 2. Redistributions in binary form must reproduce the above copyright
13*16ebabc4Splunky  *    notice, this list of conditions and the following disclaimer in the
14*16ebabc4Splunky  *    documentation and/or other materials provided with the distribution.
15*16ebabc4Splunky  * 3. The name of the author may not be used to endorse or promote products
16*16ebabc4Splunky  *    derived from this software without specific prior written permission
17*16ebabc4Splunky  *
18*16ebabc4Splunky  * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
19*16ebabc4Splunky  * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
20*16ebabc4Splunky  * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
21*16ebabc4Splunky  * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
22*16ebabc4Splunky  * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
23*16ebabc4Splunky  * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
24*16ebabc4Splunky  * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
25*16ebabc4Splunky  * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
26*16ebabc4Splunky  * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
27*16ebabc4Splunky  * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
28*16ebabc4Splunky  */
29*16ebabc4Splunky 
30*16ebabc4Splunky #ifdef SOFTFLOAT
31*16ebabc4Splunky 
32*16ebabc4Splunky #include "pass1.h"
33*16ebabc4Splunky 
34*16ebabc4Splunky 
35*16ebabc4Splunky /*
36*16ebabc4Splunky  * Floating point emulation to be used when cross-compiling.
37*16ebabc4Splunky  * Currently only supports F- and D-float, used in DEC machines.
38*16ebabc4Splunky  * Should be trivial to add other emulations.
39*16ebabc4Splunky  *
40*16ebabc4Splunky  * XXX - assumes that:
41*16ebabc4Splunky  *	- long long is (at least) 64 bits
42*16ebabc4Splunky  *	- int is at least 32 bits.
43*16ebabc4Splunky  *	- short is 16 bits.
44*16ebabc4Splunky  */
45*16ebabc4Splunky 
46*16ebabc4Splunky #ifdef FDFLOAT
47*16ebabc4Splunky 
48*16ebabc4Splunky /*
49*16ebabc4Splunky  * Useful macros to manipulate the float.
50*16ebabc4Splunky  */
51*16ebabc4Splunky #define DSIGN(w)	(((w).fd1 >> 15) & 1)
52*16ebabc4Splunky #define DSIGNSET(w,s)	((w).fd1 = (s << 15) | ((w).fd1 & 077777))
53*16ebabc4Splunky #define DEXP(w)		(((w).fd1 >> 7) & 0377)
54*16ebabc4Splunky #define DEXPSET(w,e)	((w).fd1 = (((e) & 0377) << 7) | ((w).fd1 & 0100177))
55*16ebabc4Splunky #define DMANTH(w)	((w).fd1 & 0177)
56*16ebabc4Splunky #define DMANTHSET(w,m)	((w).fd1 = ((m) & 0177) | ((w).fd1 & 0177600))
57*16ebabc4Splunky 
58*16ebabc4Splunky typedef unsigned int lword;
59*16ebabc4Splunky typedef unsigned long long dword;
60*16ebabc4Splunky 
61*16ebabc4Splunky #define MAXMANT 0x100000000000000LL
62*16ebabc4Splunky 
63*16ebabc4Splunky /*
64*16ebabc4Splunky  * Returns a zero dfloat.
65*16ebabc4Splunky  */
66*16ebabc4Splunky static SF
nulldf(void)67*16ebabc4Splunky nulldf(void)
68*16ebabc4Splunky {
69*16ebabc4Splunky 	SF rv;
70*16ebabc4Splunky 
71*16ebabc4Splunky 	rv.fd1 = rv.fd2 = rv.fd3 = rv.fd4 = 0;
72*16ebabc4Splunky 	return rv;
73*16ebabc4Splunky }
74*16ebabc4Splunky 
75*16ebabc4Splunky /*
76*16ebabc4Splunky  * Convert a (u)longlong to dfloat.
77*16ebabc4Splunky  * XXX - fails on too large (> 55 bits) numbers.
78*16ebabc4Splunky  */
79*16ebabc4Splunky SF
soft_cast(CONSZ ll,TWORD t)80*16ebabc4Splunky soft_cast(CONSZ ll, TWORD t)
81*16ebabc4Splunky {
82*16ebabc4Splunky 	int i;
83*16ebabc4Splunky 	SF rv;
84*16ebabc4Splunky 
85*16ebabc4Splunky 	rv = nulldf();
86*16ebabc4Splunky 	if (ll == 0)
87*16ebabc4Splunky 		return rv;  /* fp is zero */
88*16ebabc4Splunky 	if (ll < 0)
89*16ebabc4Splunky 		DSIGNSET(rv,1), ll = -ll;
90*16ebabc4Splunky 	for (i = 0; ll > 0; i++, ll <<= 1)
91*16ebabc4Splunky 		;
92*16ebabc4Splunky 	DEXPSET(rv, 192-i);
93*16ebabc4Splunky 	DMANTHSET(rv, ll >> 56);
94*16ebabc4Splunky 	rv.fd2 = ll >> 40;
95*16ebabc4Splunky 	rv.fd3 = ll >> 24;
96*16ebabc4Splunky 	rv.fd4 = ll >> 8;
97*16ebabc4Splunky 	return rv;
98*16ebabc4Splunky }
99*16ebabc4Splunky 
100*16ebabc4Splunky /*
101*16ebabc4Splunky  * multiply two dfloat. Use chop, not round.
102*16ebabc4Splunky  */
103*16ebabc4Splunky SF
soft_mul(SF p1,SF p2)104*16ebabc4Splunky soft_mul(SF p1, SF p2)
105*16ebabc4Splunky {
106*16ebabc4Splunky 	SF rv;
107*16ebabc4Splunky 	lword a1[2], a2[2], res[4];
108*16ebabc4Splunky 	dword sum;
109*16ebabc4Splunky 
110*16ebabc4Splunky 	res[0] = res[1] = res[2] = res[3] = 0;
111*16ebabc4Splunky 
112*16ebabc4Splunky 	/* move mantissa into lwords */
113*16ebabc4Splunky 	a1[0] = p1.fd4 | (p1.fd3 << 16);
114*16ebabc4Splunky 	a1[1] = p1.fd2 | DMANTH(p1) << 16 | 0x800000;
115*16ebabc4Splunky 
116*16ebabc4Splunky 	a2[0] = p2.fd4 | (p2.fd3 << 16);
117*16ebabc4Splunky 	a2[1] = p2.fd2 | DMANTH(p2) << 16 | 0x800000;
118*16ebabc4Splunky 
119*16ebabc4Splunky #define MULONE(x,y,r) sum += (dword)a1[x] * (dword)a2[y]; sum += res[r]; \
120*16ebabc4Splunky 	res[r] = sum; sum >>= 32;
121*16ebabc4Splunky 
122*16ebabc4Splunky 	sum = 0;
123*16ebabc4Splunky 	MULONE(0, 0, 0);
124*16ebabc4Splunky 	MULONE(1, 0, 1);
125*16ebabc4Splunky 	res[2] = sum;
126*16ebabc4Splunky 	sum = 0;
127*16ebabc4Splunky 	MULONE(0, 1, 1);
128*16ebabc4Splunky 	MULONE(1, 1, 2);
129*16ebabc4Splunky 	res[3] = sum;
130*16ebabc4Splunky 
131*16ebabc4Splunky 	rv.fd1 = 0;
132*16ebabc4Splunky 	DSIGNSET(rv, DSIGN(p1) ^ DSIGN(p2));
133*16ebabc4Splunky 	DEXPSET(rv, DEXP(p1) + DEXP(p2) - 128);
134*16ebabc4Splunky 	if (res[3] & 0x8000) {
135*16ebabc4Splunky 		res[3] = (res[3] << 8) | (res[2] >> 24);
136*16ebabc4Splunky 		res[2] = (res[2] << 8) | (res[1] >> 24);
137*16ebabc4Splunky 	} else {
138*16ebabc4Splunky 		DEXPSET(rv, DEXP(rv) - 1);
139*16ebabc4Splunky 		res[3] = (res[3] << 9) | (res[2] >> 23);
140*16ebabc4Splunky 		res[2] = (res[2] << 9) | (res[1] >> 23);
141*16ebabc4Splunky 	}
142*16ebabc4Splunky 	DMANTHSET(rv, res[3] >> 16);
143*16ebabc4Splunky 	rv.fd2 = res[3];
144*16ebabc4Splunky 	rv.fd3 = res[2] >> 16;
145*16ebabc4Splunky 	rv.fd4 = res[2];
146*16ebabc4Splunky 	return rv;
147*16ebabc4Splunky }
148*16ebabc4Splunky 
149*16ebabc4Splunky SF
soft_div(SF t,SF n)150*16ebabc4Splunky soft_div(SF t, SF n)
151*16ebabc4Splunky {
152*16ebabc4Splunky 	SF rv;
153*16ebabc4Splunky 	dword T, N, K;
154*16ebabc4Splunky 	int c;
155*16ebabc4Splunky 
156*16ebabc4Splunky #define SHL(x,b) ((dword)(x) << b)
157*16ebabc4Splunky 	T = SHL(1,55) | SHL(DMANTH(t), 48) |
158*16ebabc4Splunky 	    SHL(t.fd2, 32) | SHL(t.fd3, 16) | t.fd4;
159*16ebabc4Splunky 	N = SHL(1,55) | SHL(DMANTH(n), 48) |
160*16ebabc4Splunky 	    SHL(n.fd2, 32) | SHL(n.fd3, 16) | n.fd4;
161*16ebabc4Splunky 
162*16ebabc4Splunky 	c = T > N;
163*16ebabc4Splunky 	for (K = 0; (K & 0x80000000000000ULL) == 0; ) {
164*16ebabc4Splunky 		if (T >= N) {
165*16ebabc4Splunky 			T -= N;
166*16ebabc4Splunky 			K |= 1;
167*16ebabc4Splunky 		}
168*16ebabc4Splunky 		T <<= 1;
169*16ebabc4Splunky 		K <<= 1;
170*16ebabc4Splunky 	}
171*16ebabc4Splunky 	rv.fd1 = 0;
172*16ebabc4Splunky 	DSIGNSET(rv, DSIGN(t) ^ DSIGN(n));
173*16ebabc4Splunky 	DEXPSET(rv, DEXP(t) - DEXP(n) + 128 + c);
174*16ebabc4Splunky 	DMANTHSET(rv, K >> 48);
175*16ebabc4Splunky 	rv.fd2 = K >> 32;
176*16ebabc4Splunky 	rv.fd3 = K >> 16;
177*16ebabc4Splunky 	rv.fd4 = K;
178*16ebabc4Splunky 	return rv;
179*16ebabc4Splunky }
180*16ebabc4Splunky 
181*16ebabc4Splunky /*
182*16ebabc4Splunky  * Negate a float number. Easy.
183*16ebabc4Splunky  */
184*16ebabc4Splunky SF
soft_neg(SF sf)185*16ebabc4Splunky soft_neg(SF sf)
186*16ebabc4Splunky {
187*16ebabc4Splunky 	int sign = DSIGN(sf) == 0;
188*16ebabc4Splunky 	DSIGNSET(sf, sign);
189*16ebabc4Splunky 	return sf;
190*16ebabc4Splunky }
191*16ebabc4Splunky 
192*16ebabc4Splunky /*
193*16ebabc4Splunky  * Return true if fp number is zero.
194*16ebabc4Splunky  */
195*16ebabc4Splunky int
soft_isz(SF sf)196*16ebabc4Splunky soft_isz(SF sf)
197*16ebabc4Splunky {
198*16ebabc4Splunky 	return (DEXP(sf) == 0);
199*16ebabc4Splunky }
200*16ebabc4Splunky 
201*16ebabc4Splunky int
soft_cmp_eq(SF x1,SF x2)202*16ebabc4Splunky soft_cmp_eq(SF x1, SF x2)
203*16ebabc4Splunky {
204*16ebabc4Splunky 	cerror("soft_cmp_eq");
205*16ebabc4Splunky 	return 0;
206*16ebabc4Splunky }
207*16ebabc4Splunky 
208*16ebabc4Splunky int
soft_cmp_ne(SF x1,SF x2)209*16ebabc4Splunky soft_cmp_ne(SF x1, SF x2)
210*16ebabc4Splunky {
211*16ebabc4Splunky 	cerror("soft_cmp_ne");
212*16ebabc4Splunky 	return 0;
213*16ebabc4Splunky }
214*16ebabc4Splunky 
215*16ebabc4Splunky int
soft_cmp_le(SF x1,SF x2)216*16ebabc4Splunky soft_cmp_le(SF x1, SF x2)
217*16ebabc4Splunky {
218*16ebabc4Splunky 	cerror("soft_cmp_le");
219*16ebabc4Splunky 	return 0;
220*16ebabc4Splunky }
221*16ebabc4Splunky 
222*16ebabc4Splunky int
soft_cmp_lt(SF x1,SF x2)223*16ebabc4Splunky soft_cmp_lt(SF x1, SF x2)
224*16ebabc4Splunky {
225*16ebabc4Splunky 	cerror("soft_cmp_lt");
226*16ebabc4Splunky 	return 0;
227*16ebabc4Splunky }
228*16ebabc4Splunky 
229*16ebabc4Splunky int
soft_cmp_ge(SF x1,SF x2)230*16ebabc4Splunky soft_cmp_ge(SF x1, SF x2)
231*16ebabc4Splunky {
232*16ebabc4Splunky 	cerror("soft_cmp_ge");
233*16ebabc4Splunky 	return 0;
234*16ebabc4Splunky }
235*16ebabc4Splunky 
236*16ebabc4Splunky int
soft_cmp_gt(SF x1,SF x2)237*16ebabc4Splunky soft_cmp_gt(SF x1, SF x2)
238*16ebabc4Splunky {
239*16ebabc4Splunky 	cerror("soft_cmp_gt");
240*16ebabc4Splunky 	return 0;
241*16ebabc4Splunky }
242*16ebabc4Splunky 
243*16ebabc4Splunky /*
244*16ebabc4Splunky  * Convert a fp number to a CONSZ.
245*16ebabc4Splunky  */
246*16ebabc4Splunky CONSZ
soft_val(SF sf)247*16ebabc4Splunky soft_val(SF sf)
248*16ebabc4Splunky {
249*16ebabc4Splunky 	CONSZ mant;
250*16ebabc4Splunky 	int exp = DEXP(sf) - 128;
251*16ebabc4Splunky 
252*16ebabc4Splunky 	mant = SHL(1,55) | SHL(DMANTH(sf), 48) |
253*16ebabc4Splunky             SHL(sf.fd2, 32) | SHL(sf.fd3, 16) | sf.fd4;
254*16ebabc4Splunky 
255*16ebabc4Splunky 	while (exp < 0)
256*16ebabc4Splunky 		mant >>= 1, exp++;
257*16ebabc4Splunky 	while (exp > 0)
258*16ebabc4Splunky 		mant <<= 1, exp--;
259*16ebabc4Splunky 	return mant;
260*16ebabc4Splunky }
261*16ebabc4Splunky 
262*16ebabc4Splunky SF
soft_plus(SF x1,SF x2)263*16ebabc4Splunky soft_plus(SF x1, SF x2)
264*16ebabc4Splunky {
265*16ebabc4Splunky 	cerror("soft_plus");
266*16ebabc4Splunky 	return x1;
267*16ebabc4Splunky }
268*16ebabc4Splunky 
269*16ebabc4Splunky SF
soft_minus(SF x1,SF x2)270*16ebabc4Splunky soft_minus(SF x1, SF x2)
271*16ebabc4Splunky {
272*16ebabc4Splunky 	cerror("soft_minus");
273*16ebabc4Splunky 	return x1;
274*16ebabc4Splunky }
275*16ebabc4Splunky 
276*16ebabc4Splunky /*
277*16ebabc4Splunky  * Convert a hex constant to floating point number.
278*16ebabc4Splunky  */
279*16ebabc4Splunky NODE *
fhexcon(char * s)280*16ebabc4Splunky fhexcon(char *s)
281*16ebabc4Splunky {
282*16ebabc4Splunky 	cerror("fhexcon");
283*16ebabc4Splunky 	return NULL;
284*16ebabc4Splunky }
285*16ebabc4Splunky 
286*16ebabc4Splunky /*
287*16ebabc4Splunky  * Convert a floating-point constant to D-float and store it in a NODE.
288*16ebabc4Splunky  */
289*16ebabc4Splunky NODE *
floatcon(char * s)290*16ebabc4Splunky floatcon(char *s)
291*16ebabc4Splunky {
292*16ebabc4Splunky 	NODE *p;
293*16ebabc4Splunky 	dword mant;
294*16ebabc4Splunky 	SF fl, flexp, exp5;
295*16ebabc4Splunky 	int exp, negexp, bexp;
296*16ebabc4Splunky 
297*16ebabc4Splunky 	exp = 0;
298*16ebabc4Splunky 	mant = 0;
299*16ebabc4Splunky #define ADDTO(sum, val) sum = sum * 10 + val - '0'
300*16ebabc4Splunky 	for (; *s >= '0' && *s <= '9'; s++) {
301*16ebabc4Splunky 		if (mant<MAXMANT)
302*16ebabc4Splunky 			ADDTO(mant, *s);
303*16ebabc4Splunky 		else
304*16ebabc4Splunky 			exp++;
305*16ebabc4Splunky 	}
306*16ebabc4Splunky 	if (*s == '.') {
307*16ebabc4Splunky 		for (s++; *s >= '0' && *s <= '9'; s++) {
308*16ebabc4Splunky 			if (mant<MAXMANT) {
309*16ebabc4Splunky 				ADDTO(mant, *s);
310*16ebabc4Splunky 				exp--;
311*16ebabc4Splunky 			}
312*16ebabc4Splunky 		}
313*16ebabc4Splunky 	}
314*16ebabc4Splunky 
315*16ebabc4Splunky 	if ((*s == 'E') || (*s == 'e')) {
316*16ebabc4Splunky 		int eexp = 0, sign = 0;
317*16ebabc4Splunky 		s++;
318*16ebabc4Splunky 		if (*s == '+')
319*16ebabc4Splunky 			s++;
320*16ebabc4Splunky 		else if (*s=='-')
321*16ebabc4Splunky 			sign = 1, s++;
322*16ebabc4Splunky 
323*16ebabc4Splunky 		for (; *s >= '0' && *s <= '9'; s++)
324*16ebabc4Splunky 			ADDTO(eexp, *s);
325*16ebabc4Splunky 		if (sign)
326*16ebabc4Splunky 			eexp = -eexp;
327*16ebabc4Splunky 		exp = exp + eexp;
328*16ebabc4Splunky 	}
329*16ebabc4Splunky 
330*16ebabc4Splunky 	negexp = 1;
331*16ebabc4Splunky 	if (exp<0) {
332*16ebabc4Splunky 		negexp = -1;
333*16ebabc4Splunky 		exp = -exp;
334*16ebabc4Splunky 	}
335*16ebabc4Splunky 
336*16ebabc4Splunky 
337*16ebabc4Splunky 	flexp = soft_cast(1, INT);
338*16ebabc4Splunky 	exp5 = soft_cast(5, INT);
339*16ebabc4Splunky 	bexp = exp;
340*16ebabc4Splunky 	fl = soft_cast(mant, INT);
341*16ebabc4Splunky 
342*16ebabc4Splunky 	for (; exp; exp >>= 1) {
343*16ebabc4Splunky 		if (exp&01)
344*16ebabc4Splunky 			flexp = soft_mul(flexp, exp5);
345*16ebabc4Splunky 		exp5 = soft_mul(exp5, exp5);
346*16ebabc4Splunky 	}
347*16ebabc4Splunky 	if (negexp<0)
348*16ebabc4Splunky 		fl = soft_div(fl, flexp);
349*16ebabc4Splunky 	else
350*16ebabc4Splunky 		fl = soft_mul(fl, flexp);
351*16ebabc4Splunky 
352*16ebabc4Splunky 	DEXPSET(fl, DEXP(fl) + negexp*bexp);
353*16ebabc4Splunky 	p = block(FCON, NIL, NIL, DOUBLE, 0, MKSUE(DOUBLE)); /* XXX type */
354*16ebabc4Splunky 	p->n_dcon = fl;
355*16ebabc4Splunky 	return p;
356*16ebabc4Splunky }
357*16ebabc4Splunky #else
358*16ebabc4Splunky #error missing softfloat definition
359*16ebabc4Splunky #endif
360*16ebabc4Splunky #endif
361