xref: /openbmc/linux/arch/m68k/fpsp040/scale.S (revision 1da177e4)
1|
2|	scale.sa 3.3 7/30/91
3|
4|	The entry point sSCALE computes the destination operand
5|	scaled by the source operand.  If the absolute value of
6|	the source operand is (>= 2^14) an overflow or underflow
7|	is returned.
8|
9|	The entry point sscale is called from do_func to emulate
10|	the fscale unimplemented instruction.
11|
12|	Input: Double-extended destination operand in FPTEMP,
13|		double-extended source operand in ETEMP.
14|
15|	Output: The function returns scale(X,Y) to fp0.
16|
17|	Modifies: fp0.
18|
19|	Algorithm:
20|
21|		Copyright (C) Motorola, Inc. 1990
22|			All Rights Reserved
23|
24|	THIS IS UNPUBLISHED PROPRIETARY SOURCE CODE OF MOTOROLA
25|	The copyright notice above does not evidence any
26|	actual or intended publication of such source code.
27
28|SCALE    idnt    2,1 | Motorola 040 Floating Point Software Package
29
30	|section	8
31
32#include "fpsp.h"
33
34	|xref	t_ovfl2
35	|xref	t_unfl
36	|xref	round
37	|xref	t_resdnrm
38
39SRC_BNDS: .short	0x3fff,0x400c
40
41|
42| This entry point is used by the unimplemented instruction exception
43| handler.
44|
45|
46|
47|	FSCALE
48|
49	.global	sscale
50sscale:
51	fmovel		#0,%fpcr		|clr user enabled exc
52	clrl		%d1
53	movew		FPTEMP(%a6),%d1	|get dest exponent
54	smi		L_SCR1(%a6)	|use L_SCR1 to hold sign
55	andil		#0x7fff,%d1	|strip sign
56	movew		ETEMP(%a6),%d0	|check src bounds
57	andiw		#0x7fff,%d0	|clr sign bit
58	cmp2w		SRC_BNDS,%d0
59	bccs		src_in
60	cmpiw		#0x400c,%d0	|test for too large
61	bge		src_out
62|
63| The source input is below 1, so we check for denormalized numbers
64| and set unfl.
65|
66src_small:
67	moveb		DTAG(%a6),%d0
68	andib		#0xe0,%d0
69	tstb		%d0
70	beqs		no_denorm
71	st		STORE_FLG(%a6)	|dest already contains result
72	orl		#unfl_mask,USER_FPSR(%a6) |set UNFL
73den_done:
74	leal		FPTEMP(%a6),%a0
75	bra		t_resdnrm
76no_denorm:
77	fmovel		USER_FPCR(%a6),%FPCR
78	fmovex		FPTEMP(%a6),%fp0	|simply return dest
79	rts
80
81
82|
83| Source is within 2^14 range.  To perform the int operation,
84| move it to d0.
85|
86src_in:
87	fmovex		ETEMP(%a6),%fp0	|move in src for int
88	fmovel		#rz_mode,%fpcr	|force rz for src conversion
89	fmovel		%fp0,%d0		|int src to d0
90	fmovel		#0,%FPSR		|clr status from above
91	tstw		ETEMP(%a6)	|check src sign
92	blt		src_neg
93|
94| Source is positive.  Add the src to the dest exponent.
95| The result can be denormalized, if src = 0, or overflow,
96| if the result of the add sets a bit in the upper word.
97|
98src_pos:
99	tstw		%d1		|check for denorm
100	beq		dst_dnrm
101	addl		%d0,%d1		|add src to dest exp
102	beqs		denorm		|if zero, result is denorm
103	cmpil		#0x7fff,%d1	|test for overflow
104	bges		ovfl
105	tstb		L_SCR1(%a6)
106	beqs		spos_pos
107	orw		#0x8000,%d1
108spos_pos:
109	movew		%d1,FPTEMP(%a6)	|result in FPTEMP
110	fmovel		USER_FPCR(%a6),%FPCR
111	fmovex		FPTEMP(%a6),%fp0	|write result to fp0
112	rts
113ovfl:
114	tstb		L_SCR1(%a6)
115	beqs		sovl_pos
116	orw		#0x8000,%d1
117sovl_pos:
118	movew		FPTEMP(%a6),ETEMP(%a6)	|result in ETEMP
119	movel		FPTEMP_HI(%a6),ETEMP_HI(%a6)
120	movel		FPTEMP_LO(%a6),ETEMP_LO(%a6)
121	bra		t_ovfl2
122
123denorm:
124	tstb		L_SCR1(%a6)
125	beqs		den_pos
126	orw		#0x8000,%d1
127den_pos:
128	tstl		FPTEMP_HI(%a6)	|check j bit
129	blts		nden_exit	|if set, not denorm
130	movew		%d1,ETEMP(%a6)	|input expected in ETEMP
131	movel		FPTEMP_HI(%a6),ETEMP_HI(%a6)
132	movel		FPTEMP_LO(%a6),ETEMP_LO(%a6)
133	orl		#unfl_bit,USER_FPSR(%a6)	|set unfl
134	leal		ETEMP(%a6),%a0
135	bra		t_resdnrm
136nden_exit:
137	movew		%d1,FPTEMP(%a6)	|result in FPTEMP
138	fmovel		USER_FPCR(%a6),%FPCR
139	fmovex		FPTEMP(%a6),%fp0	|write result to fp0
140	rts
141
142|
143| Source is negative.  Add the src to the dest exponent.
144| (The result exponent will be reduced).  The result can be
145| denormalized.
146|
147src_neg:
148	addl		%d0,%d1		|add src to dest
149	beqs		denorm		|if zero, result is denorm
150	blts		fix_dnrm	|if negative, result is
151|					;needing denormalization
152	tstb		L_SCR1(%a6)
153	beqs		sneg_pos
154	orw		#0x8000,%d1
155sneg_pos:
156	movew		%d1,FPTEMP(%a6)	|result in FPTEMP
157	fmovel		USER_FPCR(%a6),%FPCR
158	fmovex		FPTEMP(%a6),%fp0	|write result to fp0
159	rts
160
161
162|
163| The result exponent is below denorm value.  Test for catastrophic
164| underflow and force zero if true.  If not, try to shift the
165| mantissa right until a zero exponent exists.
166|
167fix_dnrm:
168	cmpiw		#0xffc0,%d1	|lower bound for normalization
169	blt		fix_unfl	|if lower, catastrophic unfl
170	movew		%d1,%d0		|use d0 for exp
171	movel		%d2,-(%a7)	|free d2 for norm
172	movel		FPTEMP_HI(%a6),%d1
173	movel		FPTEMP_LO(%a6),%d2
174	clrl		L_SCR2(%a6)
175fix_loop:
176	addw		#1,%d0		|drive d0 to 0
177	lsrl		#1,%d1		|while shifting the
178	roxrl		#1,%d2		|mantissa to the right
179	bccs		no_carry
180	st		L_SCR2(%a6)	|use L_SCR2 to capture inex
181no_carry:
182	tstw		%d0		|it is finished when
183	blts		fix_loop	|d0 is zero or the mantissa
184	tstb		L_SCR2(%a6)
185	beqs		tst_zero
186	orl		#unfl_inx_mask,USER_FPSR(%a6)
187|					;set unfl, aunfl, ainex
188|
189| Test for zero. If zero, simply use fmove to return +/- zero
190| to the fpu.
191|
192tst_zero:
193	clrw		FPTEMP_EX(%a6)
194	tstb		L_SCR1(%a6)	|test for sign
195	beqs		tst_con
196	orw		#0x8000,FPTEMP_EX(%a6) |set sign bit
197tst_con:
198	movel		%d1,FPTEMP_HI(%a6)
199	movel		%d2,FPTEMP_LO(%a6)
200	movel		(%a7)+,%d2
201	tstl		%d1
202	bnes		not_zero
203	tstl		FPTEMP_LO(%a6)
204	bnes		not_zero
205|
206| Result is zero.  Check for rounding mode to set lsb.  If the
207| mode is rp, and the zero is positive, return smallest denorm.
208| If the mode is rm, and the zero is negative, return smallest
209| negative denorm.
210|
211	btstb		#5,FPCR_MODE(%a6) |test if rm or rp
212	beqs		no_dir
213	btstb		#4,FPCR_MODE(%a6) |check which one
214	beqs		zer_rm
215zer_rp:
216	tstb		L_SCR1(%a6)	|check sign
217	bnes		no_dir		|if set, neg op, no inc
218	movel		#1,FPTEMP_LO(%a6) |set lsb
219	bras		sm_dnrm
220zer_rm:
221	tstb		L_SCR1(%a6)	|check sign
222	beqs		no_dir		|if clr, neg op, no inc
223	movel		#1,FPTEMP_LO(%a6) |set lsb
224	orl		#neg_mask,USER_FPSR(%a6) |set N
225	bras		sm_dnrm
226no_dir:
227	fmovel		USER_FPCR(%a6),%FPCR
228	fmovex		FPTEMP(%a6),%fp0	|use fmove to set cc's
229	rts
230
231|
232| The rounding mode changed the zero to a smallest denorm. Call
233| t_resdnrm with exceptional operand in ETEMP.
234|
235sm_dnrm:
236	movel		FPTEMP_EX(%a6),ETEMP_EX(%a6)
237	movel		FPTEMP_HI(%a6),ETEMP_HI(%a6)
238	movel		FPTEMP_LO(%a6),ETEMP_LO(%a6)
239	leal		ETEMP(%a6),%a0
240	bra		t_resdnrm
241
242|
243| Result is still denormalized.
244|
245not_zero:
246	orl		#unfl_mask,USER_FPSR(%a6) |set unfl
247	tstb		L_SCR1(%a6)	|check for sign
248	beqs		fix_exit
249	orl		#neg_mask,USER_FPSR(%a6) |set N
250fix_exit:
251	bras		sm_dnrm
252
253
254|
255| The result has underflowed to zero. Return zero and set
256| unfl, aunfl, and ainex.
257|
258fix_unfl:
259	orl		#unfl_inx_mask,USER_FPSR(%a6)
260	btstb		#5,FPCR_MODE(%a6) |test if rm or rp
261	beqs		no_dir2
262	btstb		#4,FPCR_MODE(%a6) |check which one
263	beqs		zer_rm2
264zer_rp2:
265	tstb		L_SCR1(%a6)	|check sign
266	bnes		no_dir2		|if set, neg op, no inc
267	clrl		FPTEMP_EX(%a6)
268	clrl		FPTEMP_HI(%a6)
269	movel		#1,FPTEMP_LO(%a6) |set lsb
270	bras		sm_dnrm		|return smallest denorm
271zer_rm2:
272	tstb		L_SCR1(%a6)	|check sign
273	beqs		no_dir2		|if clr, neg op, no inc
274	movew		#0x8000,FPTEMP_EX(%a6)
275	clrl		FPTEMP_HI(%a6)
276	movel		#1,FPTEMP_LO(%a6) |set lsb
277	orl		#neg_mask,USER_FPSR(%a6) |set N
278	bra		sm_dnrm		|return smallest denorm
279
280no_dir2:
281	tstb		L_SCR1(%a6)
282	bges		pos_zero
283neg_zero:
284	clrl		FP_SCR1(%a6)	|clear the exceptional operand
285	clrl		FP_SCR1+4(%a6)	|for gen_except.
286	clrl		FP_SCR1+8(%a6)
287	fmoves		#0x80000000,%fp0
288	rts
289pos_zero:
290	clrl		FP_SCR1(%a6)	|clear the exceptional operand
291	clrl		FP_SCR1+4(%a6)	|for gen_except.
292	clrl		FP_SCR1+8(%a6)
293	fmoves		#0x00000000,%fp0
294	rts
295
296|
297| The destination is a denormalized number.  It must be handled
298| by first shifting the bits in the mantissa until it is normalized,
299| then adding the remainder of the source to the exponent.
300|
301dst_dnrm:
302	moveml		%d2/%d3,-(%a7)
303	movew		FPTEMP_EX(%a6),%d1
304	movel		FPTEMP_HI(%a6),%d2
305	movel		FPTEMP_LO(%a6),%d3
306dst_loop:
307	tstl		%d2		|test for normalized result
308	blts		dst_norm	|exit loop if so
309	tstl		%d0		|otherwise, test shift count
310	beqs		dst_fin		|if zero, shifting is done
311	subil		#1,%d0		|dec src
312	lsll		#1,%d3
313	roxll		#1,%d2
314	bras		dst_loop
315|
316| Destination became normalized.  Simply add the remaining
317| portion of the src to the exponent.
318|
319dst_norm:
320	addw		%d0,%d1		|dst is normalized; add src
321	tstb		L_SCR1(%a6)
322	beqs		dnrm_pos
323	orl		#0x8000,%d1
324dnrm_pos:
325	movemw		%d1,FPTEMP_EX(%a6)
326	moveml		%d2,FPTEMP_HI(%a6)
327	moveml		%d3,FPTEMP_LO(%a6)
328	fmovel		USER_FPCR(%a6),%FPCR
329	fmovex		FPTEMP(%a6),%fp0
330	moveml		(%a7)+,%d2/%d3
331	rts
332
333|
334| Destination remained denormalized.  Call t_excdnrm with
335| exceptional operand in ETEMP.
336|
337dst_fin:
338	tstb		L_SCR1(%a6)	|check for sign
339	beqs		dst_exit
340	orl		#neg_mask,USER_FPSR(%a6) |set N
341	orl		#0x8000,%d1
342dst_exit:
343	movemw		%d1,ETEMP_EX(%a6)
344	moveml		%d2,ETEMP_HI(%a6)
345	moveml		%d3,ETEMP_LO(%a6)
346	orl		#unfl_mask,USER_FPSR(%a6) |set unfl
347	moveml		(%a7)+,%d2/%d3
348	leal		ETEMP(%a6),%a0
349	bra		t_resdnrm
350
351|
352| Source is outside of 2^14 range.  Test the sign and branch
353| to the appropriate exception handler.
354|
355src_out:
356	tstb		L_SCR1(%a6)
357	beqs		scro_pos
358	orl		#0x8000,%d1
359scro_pos:
360	movel		FPTEMP_HI(%a6),ETEMP_HI(%a6)
361	movel		FPTEMP_LO(%a6),ETEMP_LO(%a6)
362	tstw		ETEMP(%a6)
363	blts		res_neg
364res_pos:
365	movew		%d1,ETEMP(%a6)	|result in ETEMP
366	bra		t_ovfl2
367res_neg:
368	movew		%d1,ETEMP(%a6)	|result in ETEMP
369	leal		ETEMP(%a6),%a0
370	bra		t_unfl
371	|end
372