round.sa revision 1.2
1*	MOTOROLA MICROPROCESSOR & MEMORY TECHNOLOGY GROUP
2*	M68000 Hi-Performance Microprocessor Division
3*	M68040 Software Package 
4*
5*	M68040 Software Package Copyright (c) 1993, 1994 Motorola Inc.
6*	All rights reserved.
7*
8*	THE SOFTWARE is provided on an "AS IS" basis and without warranty.
9*	To the maximum extent permitted by applicable law,
10*	MOTOROLA DISCLAIMS ALL WARRANTIES WHETHER EXPRESS OR IMPLIED,
11*	INCLUDING IMPLIED WARRANTIES OF MERCHANTABILITY OR FITNESS FOR A
12*	PARTICULAR PURPOSE and any warranty against infringement with
13*	regard to the SOFTWARE (INCLUDING ANY MODIFIED VERSIONS THEREOF)
14*	and any accompanying written materials. 
15*
16*	To the maximum extent permitted by applicable law,
17*	IN NO EVENT SHALL MOTOROLA BE LIABLE FOR ANY DAMAGES WHATSOEVER
18*	(INCLUDING WITHOUT LIMITATION, DAMAGES FOR LOSS OF BUSINESS
19*	PROFITS, BUSINESS INTERRUPTION, LOSS OF BUSINESS INFORMATION, OR
20*	OTHER PECUNIARY LOSS) ARISING OF THE USE OR INABILITY TO USE THE
21*	SOFTWARE.  Motorola assumes no responsibility for the maintenance
22*	and support of the SOFTWARE.  
23*
24*	You are hereby granted a copyright license to use, modify, and
25*	distribute the SOFTWARE so long as this entire notice is retained
26*	without alteration in any modified and/or redistributed versions,
27*	and that such modified versions are clearly identified as such.
28*	No licenses are granted by implication, estoppel or otherwise
29*	under any patents or trademarks of Motorola, Inc.
30
31*
32*	round.sa 3.4 7/29/91
33*
34*	handle rounding and normalization tasks
35*
36
37ROUND	IDNT    2,1 Motorola 040 Floating Point Software Package
38
39	section	8
40
41	include	fpsp.h
42
43*
44*	round --- round result according to precision/mode
45*
46*	a0 points to the input operand in the internal extended format 
47*	d1(high word) contains rounding precision:
48*		ext = $0000xxxx
49*		sgl = $0001xxxx
50*		dbl = $0002xxxx
51*	d1(low word) contains rounding mode:
52*		RN  = $xxxx0000
53*		RZ  = $xxxx0001
54*		RM  = $xxxx0010
55*		RP  = $xxxx0011
56*	d0{31:29} contains the g,r,s bits (extended)
57*
58*	On return the value pointed to by a0 is correctly rounded,
59*	a0 is preserved and the g-r-s bits in d0 are cleared.
60*	The result is not typed - the tag field is invalid.  The
61*	result is still in the internal extended format.
62*
63*	The INEX bit of USER_FPSR will be set if the rounded result was
64*	inexact (i.e. if any of the g-r-s bits were set).
65*
66
67	xdef	round
68round:
69* If g=r=s=0 then result is exact and round is done, else set 
70* the inex flag in status reg and continue.  
71*
72	bsr.b	ext_grs			;this subroutine looks at the 
73*					:rounding precision and sets 
74*					;the appropriate g-r-s bits.
75	tst.l	d0			;if grs are zero, go force
76	bne.w	rnd_cont		;lower bits to zero for size
77	
78	swap	d1			;set up d1.w for round prec.
79	bra.w	truncate
80
81rnd_cont:
82*
83* Use rounding mode as an index into a jump table for these modes.
84*
85	or.l	#inx2a_mask,USER_FPSR(a6) ;set inex2/ainex
86	lea	mode_tab,a1
87	move.l	(a1,d1.w*4),a1
88	jmp	(a1)
89*
90* Jump table indexed by rounding mode in d1.w.  All following assumes
91* grs != 0.
92*
93mode_tab:
94	dc.l	rnd_near
95	dc.l	rnd_zero
96	dc.l	rnd_mnus
97	dc.l	rnd_plus
98*
99*	ROUND PLUS INFINITY
100*
101*	If sign of fp number = 0 (positive), then add 1 to l.
102*
103rnd_plus:
104	swap 	d1			;set up d1 for round prec.
105	tst.b	LOCAL_SGN(a0)		;check for sign
106	bmi.w	truncate		;if positive then truncate
107	move.l	#$ffffffff,d0		;force g,r,s to be all f's
108	lea	add_to_l,a1
109	move.l	(a1,d1.w*4),a1
110	jmp	(a1)
111*
112*	ROUND MINUS INFINITY
113*
114*	If sign of fp number = 1 (negative), then add 1 to l.
115*
116rnd_mnus:
117	swap 	d1			;set up d1 for round prec.
118	tst.b	LOCAL_SGN(a0)		;check for sign	
119	bpl.w	truncate		;if negative then truncate
120	move.l	#$ffffffff,d0		;force g,r,s to be all f's
121	lea	add_to_l,a1
122	move.l	(a1,d1.w*4),a1
123	jmp	(a1)
124*
125*	ROUND ZERO
126*
127*	Always truncate.
128rnd_zero:
129	swap 	d1			;set up d1 for round prec.
130	bra.w	truncate
131*
132*
133*	ROUND NEAREST
134*
135*	If (g=1), then add 1 to l and if (r=s=0), then clear l
136*	Note that this will round to even in case of a tie.
137*
138rnd_near:
139	swap 	d1			;set up d1 for round prec.
140	add.l	d0,d0			;shift g-bit to c-bit
141	bcc.w	truncate		;if (g=1) then
142	lea	add_to_l,a1
143	move.l	(a1,d1.w*4),a1
144	jmp	(a1)
145
146*
147*	ext_grs --- extract guard, round and sticky bits
148*
149* Input:	d1 =		PREC:ROUND
150* Output:  	d0{31:29}=	guard, round, sticky
151*
152* The ext_grs extract the guard/round/sticky bits according to the
153* selected rounding precision. It is called by the round subroutine
154* only.  All registers except d0 are kept intact. d0 becomes an 
155* updated guard,round,sticky in d0{31:29}
156*
157* Notes: the ext_grs uses the round PREC, and therefore has to swap d1
158*	 prior to usage, and needs to restore d1 to original.
159*
160ext_grs:
161	swap	d1			;have d1.w point to round precision
162	tst.w	d1
163	bne.b	sgl_or_dbl
164	bra.b	end_ext_grs
165 
166sgl_or_dbl:
167	movem.l	d2/d3,-(a7)		;make some temp registers
168	cmpi.w	#1,d1
169	bne.b	grs_dbl
170grs_sgl:
171	bfextu	LOCAL_HI(a0){24:2},d3	;sgl prec. g-r are 2 bits right
172	move.l	#30,d2			;of the sgl prec. limits
173	lsl.l	d2,d3			;shift g-r bits to MSB of d3
174	move.l	LOCAL_HI(a0),d2		;get word 2 for s-bit test
175	andi.l	#$0000003f,d2		;s bit is the or of all other 
176	bne.b	st_stky			;bits to the right of g-r
177	tst.l	LOCAL_LO(a0)		;test lower mantissa
178	bne.b	st_stky			;if any are set, set sticky
179	tst.l	d0			;test original g,r,s
180	bne.b	st_stky			;if any are set, set sticky
181	bra.b	end_sd			;if words 3 and 4 are clr, exit
182grs_dbl:    
183	bfextu	LOCAL_LO(a0){21:2},d3	;dbl-prec. g-r are 2 bits right
184	move.l	#30,d2			;of the dbl prec. limits
185	lsl.l	d2,d3			;shift g-r bits to the MSB of d3
186	move.l	LOCAL_LO(a0),d2		;get lower mantissa  for s-bit test
187	andi.l	#$000001ff,d2		;s bit is the or-ing of all 
188	bne.b	st_stky			;other bits to the right of g-r
189	tst.l	d0			;test word original g,r,s
190	bne.b	st_stky			;if any are set, set sticky
191	bra.b	end_sd			;if clear, exit
192st_stky:
193	bset	#rnd_stky_bit,d3
194end_sd:
195	move.l	d3,d0			;return grs to d0
196	movem.l	(a7)+,d2/d3		;restore scratch registers
197end_ext_grs:
198	swap	d1			;restore d1 to original
199	rts
200
201********************  Local Equates
202ad_1_sgl equ	$00000100	constant to add 1 to l-bit in sgl prec
203ad_1_dbl equ	$00000800	constant to add 1 to l-bit in dbl prec
204
205
206*Jump table for adding 1 to the l-bit indexed by rnd prec
207
208add_to_l:
209	dc.l	add_ext
210	dc.l	add_sgl
211	dc.l	add_dbl
212	dc.l	add_dbl
213*
214*	ADD SINGLE
215*
216add_sgl:
217	add.l	#ad_1_sgl,LOCAL_HI(a0)
218	bcc.b	scc_clr			;no mantissa overflow
219	roxr.w  LOCAL_HI(a0)		;shift v-bit back in
220	roxr.w  LOCAL_HI+2(a0)		;shift v-bit back in
221	add.w	#$1,LOCAL_EX(a0)	;and incr exponent
222scc_clr:
223	tst.l	d0			;test for rs = 0
224	bne.b	sgl_done
225	andi.w  #$fe00,LOCAL_HI+2(a0)	;clear the l-bit
226sgl_done:
227	andi.l	#$ffffff00,LOCAL_HI(a0) ;truncate bits beyond sgl limit
228	clr.l	LOCAL_LO(a0)		;clear d2
229	rts
230
231*
232*	ADD EXTENDED
233*
234add_ext:
235	addq.l  #1,LOCAL_LO(a0)		;add 1 to l-bit
236	bcc.b	xcc_clr			;test for carry out
237	addq.l  #1,LOCAL_HI(a0)		;propogate carry
238	bcc.b	xcc_clr
239	roxr.w  LOCAL_HI(a0)		;mant is 0 so restore v-bit
240	roxr.w  LOCAL_HI+2(a0)		;mant is 0 so restore v-bit
241	roxr.w	LOCAL_LO(a0)
242	roxr.w	LOCAL_LO+2(a0)
243	add.w	#$1,LOCAL_EX(a0)	;and inc exp
244xcc_clr:
245	tst.l	d0			;test rs = 0
246	bne.b	add_ext_done
247	andi.b	#$fe,LOCAL_LO+3(a0)	;clear the l bit
248add_ext_done:
249	rts
250*
251*	ADD DOUBLE
252*
253add_dbl:
254	add.l	#ad_1_dbl,LOCAL_LO(a0)
255	bcc.b	dcc_clr
256	addq.l	#1,LOCAL_HI(a0)		;propogate carry
257	bcc.b	dcc_clr
258	roxr.w	LOCAL_HI(a0)		;mant is 0 so restore v-bit
259	roxr.w	LOCAL_HI+2(a0)		;mant is 0 so restore v-bit
260	roxr.w	LOCAL_LO(a0)
261	roxr.w	LOCAL_LO+2(a0)
262	add.w	#$1,LOCAL_EX(a0)	;incr exponent
263dcc_clr:
264	tst.l	d0			;test for rs = 0
265	bne.b	dbl_done
266	andi.w	#$f000,LOCAL_LO+2(a0)	;clear the l-bit
267
268dbl_done:
269	andi.l	#$fffff800,LOCAL_LO(a0) ;truncate bits beyond dbl limit
270	rts
271
272error:
273	rts
274*
275* Truncate all other bits
276*
277trunct:
278	dc.l	end_rnd
279	dc.l	sgl_done
280	dc.l	dbl_done
281	dc.l	dbl_done
282
283truncate:
284	lea	trunct,a1
285	move.l	(a1,d1.w*4),a1
286	jmp	(a1)
287
288end_rnd:
289	rts
290
291*
292*	NORMALIZE
293*
294* These routines (nrm_zero & nrm_set) normalize the unnorm.  This 
295* is done by shifting the mantissa left while decrementing the 
296* exponent.
297*
298* NRM_SET shifts and decrements until there is a 1 set in the integer 
299* bit of the mantissa (msb in d1).
300*
301* NRM_ZERO shifts and decrements until there is a 1 set in the integer 
302* bit of the mantissa (msb in d1) unless this would mean the exponent 
303* would go less than 0.  In that case the number becomes a denorm - the 
304* exponent (d0) is set to 0 and the mantissa (d1 & d2) is not 
305* normalized.
306*
307* Note that both routines have been optimized (for the worst case) and 
308* therefore do not have the easy to follow decrement/shift loop.
309*
310*	NRM_ZERO
311*
312*	Distance to first 1 bit in mantissa = X
313*	Distance to 0 from exponent = Y
314*	If X < Y
315*	Then
316*	  nrm_set
317*	Else
318*	  shift mantissa by Y
319*	  set exponent = 0
320*
321*input:
322*	FP_SCR1 = exponent, ms mantissa part, ls mantissa part
323*output:
324*	L_SCR1{4} = fpte15 or ete15 bit
325*
326	xdef	nrm_zero
327nrm_zero:
328	move.w	LOCAL_EX(a0),d0
329	cmp.w   #64,d0          ;see if exp > 64 
330	bmi.b	d0_less
331	bsr	nrm_set		;exp > 64 so exp won't exceed 0 
332	rts
333d0_less:
334	movem.l	d2/d3/d5/d6,-(a7)
335	move.l	LOCAL_HI(a0),d1
336	move.l	LOCAL_LO(a0),d2
337
338	bfffo	d1{0:32},d3	;get the distance to the first 1 
339*				;in ms mant
340	beq.b	ms_clr		;branch if no bits were set
341	cmp.w	d3,d0		;of X>Y
342	bmi.b	greater		;then exp will go past 0 (neg) if 
343*				;it is just shifted
344	bsr	nrm_set		;else exp won't go past 0
345	movem.l	(a7)+,d2/d3/d5/d6
346	rts	
347greater:
348	move.l	d2,d6		;save ls mant in d6
349	lsl.l	d0,d2		;shift ls mant by count
350	lsl.l	d0,d1		;shift ms mant by count
351	move.l	#32,d5
352	sub.l	d0,d5		;make op a denorm by shifting bits 
353	lsr.l	d5,d6		;by the number in the exp, then 
354*				;set exp = 0.
355	or.l	d6,d1		;shift the ls mant bits into the ms mant
356	clr.l	d0		;same as if decremented exp to 0 
357*				;while shifting
358	move.w	d0,LOCAL_EX(a0)
359	move.l	d1,LOCAL_HI(a0)
360	move.l	d2,LOCAL_LO(a0)
361	movem.l	(a7)+,d2/d3/d5/d6
362	rts
363ms_clr:
364	bfffo	d2{0:32},d3	;check if any bits set in ls mant
365	beq.b	all_clr		;branch if none set
366	add.w	#32,d3
367	cmp.w	d3,d0		;if X>Y
368	bmi.b	greater		;then branch
369	bsr	nrm_set		;else exp won't go past 0
370	movem.l	(a7)+,d2/d3/d5/d6
371	rts
372all_clr:
373	clr.w	LOCAL_EX(a0)	;no mantissa bits set. Set exp = 0.
374	movem.l	(a7)+,d2/d3/d5/d6
375	rts
376*
377*	NRM_SET
378*
379	xdef	nrm_set
380nrm_set:
381	move.l	d7,-(a7)
382	bfffo	LOCAL_HI(a0){0:32},d7 ;find first 1 in ms mant to d7)
383	beq.b	lower		;branch if ms mant is all 0's
384
385	move.l	d6,-(a7)
386
387	sub.w	d7,LOCAL_EX(a0)	;sub exponent by count
388	move.l	LOCAL_HI(a0),d0	;d0 has ms mant
389	move.l	LOCAL_LO(a0),d1 ;d1 has ls mant
390
391	lsl.l	d7,d0		;shift first 1 to j bit position
392	move.l	d1,d6		;copy ls mant into d6
393	lsl.l	d7,d6		;shift ls mant by count
394	move.l	d6,LOCAL_LO(a0)	;store ls mant into memory
395	moveq.l	#32,d6
396	sub.l	d7,d6		;continue shift
397	lsr.l	d6,d1		;shift off all bits but those that will
398*				;be shifted into ms mant
399	or.l	d1,d0		;shift the ls mant bits into the ms mant
400	move.l	d0,LOCAL_HI(a0)	;store ms mant into memory
401	movem.l	(a7)+,d7/d6	;restore registers
402	rts
403
404*
405* We get here if ms mant was = 0, and we assume ls mant has bits 
406* set (otherwise this would have been tagged a zero not a denorm).
407*
408lower:
409	move.w	LOCAL_EX(a0),d0	;d0 has exponent
410	move.l	LOCAL_LO(a0),d1	;d1 has ls mant
411	sub.w	#32,d0		;account for ms mant being all zeros
412	bfffo	d1{0:32},d7	;find first 1 in ls mant to d7)
413	sub.w	d7,d0		;subtract shift count from exp
414	lsl.l	d7,d1		;shift first 1 to integer bit in ms mant
415	move.w	d0,LOCAL_EX(a0)	;store ms mant
416	move.l	d1,LOCAL_HI(a0)	;store exp
417	clr.l	LOCAL_LO(a0)	;clear ls mant
418	move.l	(a7)+,d7
419	rts
420*
421*	denorm --- denormalize an intermediate result
422*
423*	Used by underflow.
424*
425* Input: 
426*	a0	 points to the operand to be denormalized
427*		 (in the internal extended format)
428*		 
429*	d0: 	 rounding precision
430* Output:
431*	a0	 points to the denormalized result
432*		 (in the internal extended format)
433*
434*	d0 	is guard,round,sticky
435*
436* d0 comes into this routine with the rounding precision. It 
437* is then loaded with the denormalized exponent threshold for the 
438* rounding precision.
439*
440
441	xdef	denorm
442denorm:
443	btst.b	#6,LOCAL_EX(a0)	;check for exponents between $7fff-$4000
444	beq.b	no_sgn_ext	
445	bset.b	#7,LOCAL_EX(a0)	;sign extend if it is so
446no_sgn_ext:
447
448	tst.b	d0		;if 0 then extended precision
449	bne.b	not_ext		;else branch
450
451	clr.l	d1		;load d1 with ext threshold
452	clr.l	d0		;clear the sticky flag
453	bsr	dnrm_lp		;denormalize the number
454	tst.b	d1		;check for inex
455	beq.w	no_inex		;if clr, no inex
456	bra.b	dnrm_inex	;if set, set inex
457
458not_ext:
459	cmpi.l	#1,d0		;if 1 then single precision
460	beq.b	load_sgl	;else must be 2, double prec
461
462load_dbl:
463	move.w	#dbl_thresh,d1	;put copy of threshold in d1
464	move.l	d1,d0		;copy d1 into d0
465	sub.w	LOCAL_EX(a0),d0	;diff = threshold - exp
466	cmp.w	#67,d0		;if diff > 67 (mant + grs bits)
467	bpl.b	chk_stky	;then branch (all bits would be 
468*				; shifted off in denorm routine)
469	clr.l	d0		;else clear the sticky flag
470	bsr	dnrm_lp		;denormalize the number
471	tst.b	d1		;check flag
472	beq.b	no_inex		;if clr, no inex
473	bra.b	dnrm_inex	;if set, set inex
474
475load_sgl:
476	move.w	#sgl_thresh,d1	;put copy of threshold in d1
477	move.l	d1,d0		;copy d1 into d0
478	sub.w	LOCAL_EX(a0),d0	;diff = threshold - exp
479	cmp.w	#67,d0		;if diff > 67 (mant + grs bits)
480	bpl.b	chk_stky	;then branch (all bits would be 
481*				; shifted off in denorm routine)
482	clr.l	d0		;else clear the sticky flag
483	bsr	dnrm_lp		;denormalize the number
484	tst.b	d1		;check flag
485	beq.b	no_inex		;if clr, no inex
486	bra.b	dnrm_inex	;if set, set inex
487
488chk_stky:
489	tst.l	LOCAL_HI(a0)	;check for any bits set
490	bne.b	set_stky
491	tst.l	LOCAL_LO(a0)	;check for any bits set
492	bne.b	set_stky
493	bra.b	clr_mant
494set_stky:
495	or.l	#inx2a_mask,USER_FPSR(a6) ;set inex2/ainex
496	move.l	#$20000000,d0	;set sticky bit in return value
497clr_mant:
498	move.w	d1,LOCAL_EX(a0)		;load exp with threshold
499	clr.l	LOCAL_HI(a0) 	;set d1 = 0 (ms mantissa)
500	clr.l	LOCAL_LO(a0)		;set d2 = 0 (ms mantissa)
501	rts
502dnrm_inex:
503	or.l	#inx2a_mask,USER_FPSR(a6) ;set inex2/ainex
504no_inex:
505	rts
506
507*
508*	dnrm_lp --- normalize exponent/mantissa to specified threshhold
509*
510* Input:
511*	a0		points to the operand to be denormalized
512*	d0{31:29} 	initial guard,round,sticky
513*	d1{15:0}	denormalization threshold
514* Output:
515*	a0		points to the denormalized operand
516*	d0{31:29}	final guard,round,sticky
517*	d1.b		inexact flag:  all ones means inexact result
518*
519* The LOCAL_LO and LOCAL_GRS parts of the value are copied to FP_SCR2
520* so that bfext can be used to extract the new low part of the mantissa.
521* Dnrm_lp can be called with a0 pointing to ETEMP or WBTEMP and there 
522* is no LOCAL_GRS scratch word following it on the fsave frame.
523*
524	xdef	dnrm_lp
525dnrm_lp:
526	move.l	d2,-(sp)		;save d2 for temp use
527	btst.b	#E3,E_BYTE(a6)		;test for type E3 exception
528	beq.b	not_E3			;not type E3 exception
529	bfextu	WBTEMP_GRS(a6){6:3},d2	;extract guard,round, sticky  bit
530	move.l	#29,d0
531	lsl.l	d0,d2			;shift g,r,s to their postions
532	move.l	d2,d0
533not_E3:
534	move.l	(sp)+,d2		;restore d2
535	move.l	LOCAL_LO(a0),FP_SCR2+LOCAL_LO(a6)
536	move.l	d0,FP_SCR2+LOCAL_GRS(a6)
537	move.l	d1,d0			;copy the denorm threshold
538	sub.w	LOCAL_EX(a0),d1		;d1 = threshold - uns exponent
539	ble.b	no_lp			;d1 <= 0
540	cmp.w	#32,d1			
541	blt.b	case_1			;0 = d1 < 32 
542	cmp.w	#64,d1
543	blt.b	case_2			;32 <= d1 < 64
544	bra.w	case_3			;d1 >= 64
545*
546* No normalization necessary
547*
548no_lp:
549	clr.b	d1			;set no inex2 reported
550	move.l	FP_SCR2+LOCAL_GRS(a6),d0	;restore original g,r,s
551	rts
552*
553* case (0<d1<32)
554*
555case_1:
556	move.l	d2,-(sp)
557	move.w	d0,LOCAL_EX(a0)		;exponent = denorm threshold
558	move.l	#32,d0
559	sub.w	d1,d0			;d0 = 32 - d1
560	bfextu	LOCAL_EX(a0){d0:32},d2
561	bfextu	d2{d1:d0},d2		;d2 = new LOCAL_HI
562	bfextu	LOCAL_HI(a0){d0:32},d1	;d1 = new LOCAL_LO
563	bfextu	FP_SCR2+LOCAL_LO(a6){d0:32},d0	;d0 = new G,R,S
564	move.l	d2,LOCAL_HI(a0)		;store new LOCAL_HI
565	move.l	d1,LOCAL_LO(a0)		;store new LOCAL_LO
566	clr.b	d1
567	bftst	d0{2:30}	
568	beq.b	c1nstky
569	bset.l	#rnd_stky_bit,d0
570	st.b	d1
571c1nstky:
572	move.l	FP_SCR2+LOCAL_GRS(a6),d2	;restore original g,r,s
573	andi.l	#$e0000000,d2		;clear all but G,R,S
574	tst.l	d2			;test if original G,R,S are clear
575	beq.b	grs_clear
576	or.l	#$20000000,d0		;set sticky bit in d0
577grs_clear:
578	andi.l	#$e0000000,d0		;clear all but G,R,S
579	move.l	(sp)+,d2
580	rts
581*
582* case (32<=d1<64)
583*
584case_2:
585	move.l	d2,-(sp)
586	move.w	d0,LOCAL_EX(a0)		;unsigned exponent = threshold
587	sub.w	#32,d1			;d1 now between 0 and 32
588	move.l	#32,d0
589	sub.w	d1,d0			;d0 = 32 - d1
590	bfextu	LOCAL_EX(a0){d0:32},d2
591	bfextu	d2{d1:d0},d2		;d2 = new LOCAL_LO
592	bfextu	LOCAL_HI(a0){d0:32},d1	;d1 = new G,R,S
593	bftst	d1{2:30}
594	bne.b	c2_sstky		;bra if sticky bit to be set
595	bftst	FP_SCR2+LOCAL_LO(a6){d0:32}
596	bne.b	c2_sstky		;bra if sticky bit to be set
597	move.l	d1,d0
598	clr.b	d1
599	bra.b	end_c2
600c2_sstky:
601	move.l	d1,d0
602	bset.l	#rnd_stky_bit,d0
603	st.b	d1
604end_c2:
605	clr.l	LOCAL_HI(a0)		;store LOCAL_HI = 0
606	move.l	d2,LOCAL_LO(a0)		;store LOCAL_LO
607	move.l	FP_SCR2+LOCAL_GRS(a6),d2	;restore original g,r,s
608	andi.l	#$e0000000,d2		;clear all but G,R,S
609	tst.l	d2			;test if original G,R,S are clear
610	beq.b	clear_grs		
611	or.l	#$20000000,d0		;set sticky bit in d0
612clear_grs:
613	andi.l	#$e0000000,d0		;get rid of all but G,R,S
614	move.l	(sp)+,d2
615	rts
616*
617* d1 >= 64 Force the exponent to be the denorm threshold with the
618* correct sign.
619*
620case_3:
621	move.w	d0,LOCAL_EX(a0)
622	tst.w	LOCAL_SGN(a0)
623	bge.b	c3con
624c3neg:
625	or.l	#$80000000,LOCAL_EX(a0)
626c3con:
627	cmp.w	#64,d1
628	beq.b	sixty_four
629	cmp.w	#65,d1
630	beq.b	sixty_five
631*
632* Shift value is out of range.  Set d1 for inex2 flag and
633* return a zero with the given threshold.
634*
635	clr.l	LOCAL_HI(a0)
636	clr.l	LOCAL_LO(a0)
637	move.l	#$20000000,d0
638	st.b	d1
639	rts
640
641sixty_four:
642	move.l	LOCAL_HI(a0),d0
643	bfextu	d0{2:30},d1
644	andi.l	#$c0000000,d0
645	bra.b	c3com
646	
647sixty_five:
648	move.l	LOCAL_HI(a0),d0
649	bfextu	d0{1:31},d1
650	andi.l	#$80000000,d0
651	lsr.l	#1,d0			;shift high bit into R bit
652
653c3com:
654	tst.l	d1
655	bne.b	c3ssticky
656	tst.l	LOCAL_LO(a0)
657	bne.b	c3ssticky
658	tst.b	FP_SCR2+LOCAL_GRS(a6)
659	bne.b	c3ssticky
660	clr.b	d1
661	bra.b	c3end
662
663c3ssticky:
664	bset.l	#rnd_stky_bit,d0
665	st.b	d1
666c3end:
667	clr.l	LOCAL_HI(a0)
668	clr.l	LOCAL_LO(a0)
669	rts
670
671	end
672