cachepc-linux

Fork of AMDESE/linux with modifications for CachePC side-channel attack
git clone https://git.sinitax.com/sinitax/cachepc-linux
Log | Files | Refs | README | LICENSE | sfeed.txt

util.S (17089B)


      1|
      2|	util.sa 3.7 7/29/91
      3|
      4|	This file contains routines used by other programs.
      5|
      6|	ovf_res: used by overflow to force the correct
      7|		 result. ovf_r_k, ovf_r_x2, ovf_r_x3 are
      8|		 derivatives of this routine.
      9|	get_fline: get user's opcode word
     10|	g_dfmtou: returns the destination format.
     11|	g_opcls: returns the opclass of the float instruction.
     12|	g_rndpr: returns the rounding precision.
     13|	reg_dest: write byte, word, or long data to Dn
     14|
     15|
     16|		Copyright (C) Motorola, Inc. 1990
     17|			All Rights Reserved
     18|
     19|       For details on the license for this file, please see the
     20|       file, README, in this same directory.
     21
     22|UTIL	idnt    2,1 | Motorola 040 Floating Point Software Package
     23
     24	|section	8
     25
     26#include "fpsp.h"
     27
     28	|xref	mem_read
     29
     30	.global	g_dfmtou
     31	.global	g_opcls
     32	.global	g_rndpr
     33	.global	get_fline
     34	.global	reg_dest
     35
     36|
     37| Final result table for ovf_res. Note that the negative counterparts
     38| are unnecessary as ovf_res always returns the sign separately from
     39| the exponent.
     40|					;+inf
     41EXT_PINF:	.long	0x7fff0000,0x00000000,0x00000000,0x00000000
     42|					;largest +ext
     43EXT_PLRG:	.long	0x7ffe0000,0xffffffff,0xffffffff,0x00000000
     44|					;largest magnitude +sgl in ext
     45SGL_PLRG:	.long	0x407e0000,0xffffff00,0x00000000,0x00000000
     46|					;largest magnitude +dbl in ext
     47DBL_PLRG:	.long	0x43fe0000,0xffffffff,0xfffff800,0x00000000
     48|					;largest -ext
     49
     50tblovfl:
     51	.long	EXT_RN
     52	.long	EXT_RZ
     53	.long	EXT_RM
     54	.long	EXT_RP
     55	.long	SGL_RN
     56	.long	SGL_RZ
     57	.long	SGL_RM
     58	.long	SGL_RP
     59	.long	DBL_RN
     60	.long	DBL_RZ
     61	.long	DBL_RM
     62	.long	DBL_RP
     63	.long	error
     64	.long	error
     65	.long	error
     66	.long	error
     67
     68
     69|
     70|	ovf_r_k --- overflow result calculation
     71|
     72| This entry point is used by kernel_ex.
     73|
     74| This forces the destination precision to be extended
     75|
     76| Input:	operand in ETEMP
     77| Output:	a result is in ETEMP (internal extended format)
     78|
     79	.global	ovf_r_k
     80ovf_r_k:
     81	lea	ETEMP(%a6),%a0	|a0 points to source operand
     82	bclrb	#sign_bit,ETEMP_EX(%a6)
     83	sne	ETEMP_SGN(%a6)	|convert to internal IEEE format
     84
     85|
     86|	ovf_r_x2 --- overflow result calculation
     87|
     88| This entry point used by x_ovfl.  (opclass 0 and 2)
     89|
     90| Input		a0  points to an operand in the internal extended format
     91| Output	a0  points to the result in the internal extended format
     92|
     93| This sets the round precision according to the user's FPCR unless the
     94| instruction is fsgldiv or fsglmul or fsadd, fdadd, fsub, fdsub, fsmul,
     95| fdmul, fsdiv, fddiv, fssqrt, fsmove, fdmove, fsabs, fdabs, fsneg, fdneg.
     96| If the instruction is fsgldiv of fsglmul, the rounding precision must be
     97| extended.  If the instruction is not fsgldiv or fsglmul but a force-
     98| precision instruction, the rounding precision is then set to the force
     99| precision.
    100
    101	.global	ovf_r_x2
    102ovf_r_x2:
    103	btstb	#E3,E_BYTE(%a6)		|check for nu exception
    104	beql	ovf_e1_exc		|it is cu exception
    105ovf_e3_exc:
    106	movew	CMDREG3B(%a6),%d0		|get the command word
    107	andiw	#0x00000060,%d0		|clear all bits except 6 and 5
    108	cmpil	#0x00000040,%d0
    109	beql	ovff_sgl		|force precision is single
    110	cmpil	#0x00000060,%d0
    111	beql	ovff_dbl		|force precision is double
    112	movew	CMDREG3B(%a6),%d0		|get the command word again
    113	andil	#0x7f,%d0			|clear all except operation
    114	cmpil	#0x33,%d0
    115	beql	ovf_fsgl		|fsglmul or fsgldiv
    116	cmpil	#0x30,%d0
    117	beql	ovf_fsgl
    118	bra	ovf_fpcr		|instruction is none of the above
    119|					;use FPCR
    120ovf_e1_exc:
    121	movew	CMDREG1B(%a6),%d0		|get command word
    122	andil	#0x00000044,%d0		|clear all bits except 6 and 2
    123	cmpil	#0x00000040,%d0
    124	beql	ovff_sgl		|the instruction is force single
    125	cmpil	#0x00000044,%d0
    126	beql	ovff_dbl		|the instruction is force double
    127	movew	CMDREG1B(%a6),%d0		|again get the command word
    128	andil	#0x0000007f,%d0		|clear all except the op code
    129	cmpil	#0x00000027,%d0
    130	beql	ovf_fsgl		|fsglmul
    131	cmpil	#0x00000024,%d0
    132	beql	ovf_fsgl		|fsgldiv
    133	bra	ovf_fpcr		|none of the above, use FPCR
    134|
    135|
    136| Inst is either fsgldiv or fsglmul.  Force extended precision.
    137|
    138ovf_fsgl:
    139	clrl	%d0
    140	bra	ovf_res
    141
    142ovff_sgl:
    143	movel	#0x00000001,%d0		|set single
    144	bra	ovf_res
    145ovff_dbl:
    146	movel	#0x00000002,%d0		|set double
    147	bra	ovf_res
    148|
    149| The precision is in the fpcr.
    150|
    151ovf_fpcr:
    152	bfextu	FPCR_MODE(%a6){#0:#2},%d0 |set round precision
    153	bra	ovf_res
    154
    155|
    156|
    157|	ovf_r_x3 --- overflow result calculation
    158|
    159| This entry point used by x_ovfl. (opclass 3 only)
    160|
    161| Input		a0  points to an operand in the internal extended format
    162| Output	a0  points to the result in the internal extended format
    163|
    164| This sets the round precision according to the destination size.
    165|
    166	.global	ovf_r_x3
    167ovf_r_x3:
    168	bsr	g_dfmtou	|get dest fmt in d0{1:0}
    169|				;for fmovout, the destination format
    170|				;is the rounding precision
    171
    172|
    173|	ovf_res --- overflow result calculation
    174|
    175| Input:
    176|	a0	points to operand in internal extended format
    177| Output:
    178|	a0	points to result in internal extended format
    179|
    180	.global	ovf_res
    181ovf_res:
    182	lsll	#2,%d0		|move round precision to d0{3:2}
    183	bfextu	FPCR_MODE(%a6){#2:#2},%d1 |set round mode
    184	orl	%d1,%d0		|index is fmt:mode in d0{3:0}
    185	leal	tblovfl,%a1	|load a1 with table address
    186	movel	%a1@(%d0:l:4),%a1	|use d0 as index to the table
    187	jmp	(%a1)		|go to the correct routine
    188|
    189|case DEST_FMT = EXT
    190|
    191EXT_RN:
    192	leal	EXT_PINF,%a1	|answer is +/- infinity
    193	bsetb	#inf_bit,FPSR_CC(%a6)
    194	bra	set_sign	|now go set the sign
    195EXT_RZ:
    196	leal	EXT_PLRG,%a1	|answer is +/- large number
    197	bra	set_sign	|now go set the sign
    198EXT_RM:
    199	tstb	LOCAL_SGN(%a0)	|if negative overflow
    200	beqs	e_rm_pos
    201e_rm_neg:
    202	leal	EXT_PINF,%a1	|answer is negative infinity
    203	orl	#neginf_mask,USER_FPSR(%a6)
    204	bra	end_ovfr
    205e_rm_pos:
    206	leal	EXT_PLRG,%a1	|answer is large positive number
    207	bra	end_ovfr
    208EXT_RP:
    209	tstb	LOCAL_SGN(%a0)	|if negative overflow
    210	beqs	e_rp_pos
    211e_rp_neg:
    212	leal	EXT_PLRG,%a1	|answer is large negative number
    213	bsetb	#neg_bit,FPSR_CC(%a6)
    214	bra	end_ovfr
    215e_rp_pos:
    216	leal	EXT_PINF,%a1	|answer is positive infinity
    217	bsetb	#inf_bit,FPSR_CC(%a6)
    218	bra	end_ovfr
    219|
    220|case DEST_FMT = DBL
    221|
    222DBL_RN:
    223	leal	EXT_PINF,%a1	|answer is +/- infinity
    224	bsetb	#inf_bit,FPSR_CC(%a6)
    225	bra	set_sign
    226DBL_RZ:
    227	leal	DBL_PLRG,%a1	|answer is +/- large number
    228	bra	set_sign	|now go set the sign
    229DBL_RM:
    230	tstb	LOCAL_SGN(%a0)	|if negative overflow
    231	beqs	d_rm_pos
    232d_rm_neg:
    233	leal	EXT_PINF,%a1	|answer is negative infinity
    234	orl	#neginf_mask,USER_FPSR(%a6)
    235	bra	end_ovfr	|inf is same for all precisions (ext,dbl,sgl)
    236d_rm_pos:
    237	leal	DBL_PLRG,%a1	|answer is large positive number
    238	bra	end_ovfr
    239DBL_RP:
    240	tstb	LOCAL_SGN(%a0)	|if negative overflow
    241	beqs	d_rp_pos
    242d_rp_neg:
    243	leal	DBL_PLRG,%a1	|answer is large negative number
    244	bsetb	#neg_bit,FPSR_CC(%a6)
    245	bra	end_ovfr
    246d_rp_pos:
    247	leal	EXT_PINF,%a1	|answer is positive infinity
    248	bsetb	#inf_bit,FPSR_CC(%a6)
    249	bra	end_ovfr
    250|
    251|case DEST_FMT = SGL
    252|
    253SGL_RN:
    254	leal	EXT_PINF,%a1	|answer is +/-  infinity
    255	bsetb	#inf_bit,FPSR_CC(%a6)
    256	bras	set_sign
    257SGL_RZ:
    258	leal	SGL_PLRG,%a1	|answer is +/- large number
    259	bras	set_sign
    260SGL_RM:
    261	tstb	LOCAL_SGN(%a0)	|if negative overflow
    262	beqs	s_rm_pos
    263s_rm_neg:
    264	leal	EXT_PINF,%a1	|answer is negative infinity
    265	orl	#neginf_mask,USER_FPSR(%a6)
    266	bras	end_ovfr
    267s_rm_pos:
    268	leal	SGL_PLRG,%a1	|answer is large positive number
    269	bras	end_ovfr
    270SGL_RP:
    271	tstb	LOCAL_SGN(%a0)	|if negative overflow
    272	beqs	s_rp_pos
    273s_rp_neg:
    274	leal	SGL_PLRG,%a1	|answer is large negative number
    275	bsetb	#neg_bit,FPSR_CC(%a6)
    276	bras	end_ovfr
    277s_rp_pos:
    278	leal	EXT_PINF,%a1	|answer is positive infinity
    279	bsetb	#inf_bit,FPSR_CC(%a6)
    280	bras	end_ovfr
    281
    282set_sign:
    283	tstb	LOCAL_SGN(%a0)	|if negative overflow
    284	beqs	end_ovfr
    285neg_sign:
    286	bsetb	#neg_bit,FPSR_CC(%a6)
    287
    288end_ovfr:
    289	movew	LOCAL_EX(%a1),LOCAL_EX(%a0) |do not overwrite sign
    290	movel	LOCAL_HI(%a1),LOCAL_HI(%a0)
    291	movel	LOCAL_LO(%a1),LOCAL_LO(%a0)
    292	rts
    293
    294
    295|
    296|	ERROR
    297|
    298error:
    299	rts
    300|
    301|	get_fline --- get f-line opcode of interrupted instruction
    302|
    303|	Returns opcode in the low word of d0.
    304|
    305get_fline:
    306	movel	USER_FPIAR(%a6),%a0	|opcode address
    307	movel	#0,-(%a7)	|reserve a word on the stack
    308	leal	2(%a7),%a1	|point to low word of temporary
    309	movel	#2,%d0		|count
    310	bsrl	mem_read
    311	movel	(%a7)+,%d0
    312	rts
    313|
    314|	g_rndpr --- put rounding precision in d0{1:0}
    315|
    316|	valid return codes are:
    317|		00 - extended
    318|		01 - single
    319|		10 - double
    320|
    321| begin
    322| get rounding precision (cmdreg3b{6:5})
    323| begin
    324|  case	opclass = 011 (move out)
    325|	get destination format - this is the also the rounding precision
    326|
    327|  case	opclass = 0x0
    328|	if E3
    329|	    *case RndPr(from cmdreg3b{6:5} = 11  then RND_PREC = DBL
    330|	    *case RndPr(from cmdreg3b{6:5} = 10  then RND_PREC = SGL
    331|	     case RndPr(from cmdreg3b{6:5} = 00 | 01
    332|		use precision from FPCR{7:6}
    333|			case 00 then RND_PREC = EXT
    334|			case 01 then RND_PREC = SGL
    335|			case 10 then RND_PREC = DBL
    336|	else E1
    337|	     use precision in FPCR{7:6}
    338|	     case 00 then RND_PREC = EXT
    339|	     case 01 then RND_PREC = SGL
    340|	     case 10 then RND_PREC = DBL
    341| end
    342|
    343g_rndpr:
    344	bsr	g_opcls		|get opclass in d0{2:0}
    345	cmpw	#0x0003,%d0	|check for opclass 011
    346	bnes	op_0x0
    347
    348|
    349| For move out instructions (opclass 011) the destination format
    350| is the same as the rounding precision.  Pass results from g_dfmtou.
    351|
    352	bsr	g_dfmtou
    353	rts
    354op_0x0:
    355	btstb	#E3,E_BYTE(%a6)
    356	beql	unf_e1_exc	|branch to e1 underflow
    357unf_e3_exc:
    358	movel	CMDREG3B(%a6),%d0	|rounding precision in d0{10:9}
    359	bfextu	%d0{#9:#2},%d0	|move the rounding prec bits to d0{1:0}
    360	cmpil	#0x2,%d0
    361	beql	unff_sgl	|force precision is single
    362	cmpil	#0x3,%d0		|force precision is double
    363	beql	unff_dbl
    364	movew	CMDREG3B(%a6),%d0	|get the command word again
    365	andil	#0x7f,%d0		|clear all except operation
    366	cmpil	#0x33,%d0
    367	beql	unf_fsgl	|fsglmul or fsgldiv
    368	cmpil	#0x30,%d0
    369	beql	unf_fsgl	|fsgldiv or fsglmul
    370	bra	unf_fpcr
    371unf_e1_exc:
    372	movel	CMDREG1B(%a6),%d0	|get 32 bits off the stack, 1st 16 bits
    373|				;are the command word
    374	andil	#0x00440000,%d0	|clear all bits except bits 6 and 2
    375	cmpil	#0x00400000,%d0
    376	beql	unff_sgl	|force single
    377	cmpil	#0x00440000,%d0	|force double
    378	beql	unff_dbl
    379	movel	CMDREG1B(%a6),%d0	|get the command word again
    380	andil	#0x007f0000,%d0	|clear all bits except the operation
    381	cmpil	#0x00270000,%d0
    382	beql	unf_fsgl	|fsglmul
    383	cmpil	#0x00240000,%d0
    384	beql	unf_fsgl	|fsgldiv
    385	bra	unf_fpcr
    386
    387|
    388| Convert to return format.  The values from cmdreg3b and the return
    389| values are:
    390|	cmdreg3b	return	     precision
    391|	--------	------	     ---------
    392|	  00,01		  0		ext
    393|	   10		  1		sgl
    394|	   11		  2		dbl
    395| Force single
    396|
    397unff_sgl:
    398	movel	#1,%d0		|return 1
    399	rts
    400|
    401| Force double
    402|
    403unff_dbl:
    404	movel	#2,%d0		|return 2
    405	rts
    406|
    407| Force extended
    408|
    409unf_fsgl:
    410	movel	#0,%d0
    411	rts
    412|
    413| Get rounding precision set in FPCR{7:6}.
    414|
    415unf_fpcr:
    416	movel	USER_FPCR(%a6),%d0 |rounding precision bits in d0{7:6}
    417	bfextu	%d0{#24:#2},%d0	|move the rounding prec bits to d0{1:0}
    418	rts
    419|
    420|	g_opcls --- put opclass in d0{2:0}
    421|
    422g_opcls:
    423	btstb	#E3,E_BYTE(%a6)
    424	beqs	opc_1b		|if set, go to cmdreg1b
    425opc_3b:
    426	clrl	%d0		|if E3, only opclass 0x0 is possible
    427	rts
    428opc_1b:
    429	movel	CMDREG1B(%a6),%d0
    430	bfextu	%d0{#0:#3},%d0	|shift opclass bits d0{31:29} to d0{2:0}
    431	rts
    432|
    433|	g_dfmtou --- put destination format in d0{1:0}
    434|
    435|	If E1, the format is from cmdreg1b{12:10}
    436|	If E3, the format is extended.
    437|
    438|	Dest. Fmt.
    439|		extended  010 -> 00
    440|		single    001 -> 01
    441|		double    101 -> 10
    442|
    443g_dfmtou:
    444	btstb	#E3,E_BYTE(%a6)
    445	beqs	op011
    446	clrl	%d0		|if E1, size is always ext
    447	rts
    448op011:
    449	movel	CMDREG1B(%a6),%d0
    450	bfextu	%d0{#3:#3},%d0	|dest fmt from cmdreg1b{12:10}
    451	cmpb	#1,%d0		|check for single
    452	bnes	not_sgl
    453	movel	#1,%d0
    454	rts
    455not_sgl:
    456	cmpb	#5,%d0		|check for double
    457	bnes	not_dbl
    458	movel	#2,%d0
    459	rts
    460not_dbl:
    461	clrl	%d0		|must be extended
    462	rts
    463
    464|
    465|
    466| Final result table for unf_sub. Note that the negative counterparts
    467| are unnecessary as unf_sub always returns the sign separately from
    468| the exponent.
    469|					;+zero
    470EXT_PZRO:	.long	0x00000000,0x00000000,0x00000000,0x00000000
    471|					;+zero
    472SGL_PZRO:	.long	0x3f810000,0x00000000,0x00000000,0x00000000
    473|					;+zero
    474DBL_PZRO:	.long	0x3c010000,0x00000000,0x00000000,0x00000000
    475|					;smallest +ext denorm
    476EXT_PSML:	.long	0x00000000,0x00000000,0x00000001,0x00000000
    477|					;smallest +sgl denorm
    478SGL_PSML:	.long	0x3f810000,0x00000100,0x00000000,0x00000000
    479|					;smallest +dbl denorm
    480DBL_PSML:	.long	0x3c010000,0x00000000,0x00000800,0x00000000
    481|
    482|	UNF_SUB --- underflow result calculation
    483|
    484| Input:
    485|	d0	contains round precision
    486|	a0	points to input operand in the internal extended format
    487|
    488| Output:
    489|	a0	points to correct internal extended precision result.
    490|
    491
    492tblunf:
    493	.long	uEXT_RN
    494	.long	uEXT_RZ
    495	.long	uEXT_RM
    496	.long	uEXT_RP
    497	.long	uSGL_RN
    498	.long	uSGL_RZ
    499	.long	uSGL_RM
    500	.long	uSGL_RP
    501	.long	uDBL_RN
    502	.long	uDBL_RZ
    503	.long	uDBL_RM
    504	.long	uDBL_RP
    505	.long	uDBL_RN
    506	.long	uDBL_RZ
    507	.long	uDBL_RM
    508	.long	uDBL_RP
    509
    510	.global	unf_sub
    511unf_sub:
    512	lsll	#2,%d0		|move round precision to d0{3:2}
    513	bfextu	FPCR_MODE(%a6){#2:#2},%d1 |set round mode
    514	orl	%d1,%d0		|index is fmt:mode in d0{3:0}
    515	leal	tblunf,%a1	|load a1 with table address
    516	movel	%a1@(%d0:l:4),%a1	|use d0 as index to the table
    517	jmp	(%a1)		|go to the correct routine
    518|
    519|case DEST_FMT = EXT
    520|
    521uEXT_RN:
    522	leal	EXT_PZRO,%a1	|answer is +/- zero
    523	bsetb	#z_bit,FPSR_CC(%a6)
    524	bra	uset_sign	|now go set the sign
    525uEXT_RZ:
    526	leal	EXT_PZRO,%a1	|answer is +/- zero
    527	bsetb	#z_bit,FPSR_CC(%a6)
    528	bra	uset_sign	|now go set the sign
    529uEXT_RM:
    530	tstb	LOCAL_SGN(%a0)	|if negative underflow
    531	beqs	ue_rm_pos
    532ue_rm_neg:
    533	leal	EXT_PSML,%a1	|answer is negative smallest denorm
    534	bsetb	#neg_bit,FPSR_CC(%a6)
    535	bra	end_unfr
    536ue_rm_pos:
    537	leal	EXT_PZRO,%a1	|answer is positive zero
    538	bsetb	#z_bit,FPSR_CC(%a6)
    539	bra	end_unfr
    540uEXT_RP:
    541	tstb	LOCAL_SGN(%a0)	|if negative underflow
    542	beqs	ue_rp_pos
    543ue_rp_neg:
    544	leal	EXT_PZRO,%a1	|answer is negative zero
    545	oril	#negz_mask,USER_FPSR(%a6)
    546	bra	end_unfr
    547ue_rp_pos:
    548	leal	EXT_PSML,%a1	|answer is positive smallest denorm
    549	bra	end_unfr
    550|
    551|case DEST_FMT = DBL
    552|
    553uDBL_RN:
    554	leal	DBL_PZRO,%a1	|answer is +/- zero
    555	bsetb	#z_bit,FPSR_CC(%a6)
    556	bra	uset_sign
    557uDBL_RZ:
    558	leal	DBL_PZRO,%a1	|answer is +/- zero
    559	bsetb	#z_bit,FPSR_CC(%a6)
    560	bra	uset_sign	|now go set the sign
    561uDBL_RM:
    562	tstb	LOCAL_SGN(%a0)	|if negative overflow
    563	beqs	ud_rm_pos
    564ud_rm_neg:
    565	leal	DBL_PSML,%a1	|answer is smallest denormalized negative
    566	bsetb	#neg_bit,FPSR_CC(%a6)
    567	bra	end_unfr
    568ud_rm_pos:
    569	leal	DBL_PZRO,%a1	|answer is positive zero
    570	bsetb	#z_bit,FPSR_CC(%a6)
    571	bra	end_unfr
    572uDBL_RP:
    573	tstb	LOCAL_SGN(%a0)	|if negative overflow
    574	beqs	ud_rp_pos
    575ud_rp_neg:
    576	leal	DBL_PZRO,%a1	|answer is negative zero
    577	oril	#negz_mask,USER_FPSR(%a6)
    578	bra	end_unfr
    579ud_rp_pos:
    580	leal	DBL_PSML,%a1	|answer is smallest denormalized negative
    581	bra	end_unfr
    582|
    583|case DEST_FMT = SGL
    584|
    585uSGL_RN:
    586	leal	SGL_PZRO,%a1	|answer is +/- zero
    587	bsetb	#z_bit,FPSR_CC(%a6)
    588	bras	uset_sign
    589uSGL_RZ:
    590	leal	SGL_PZRO,%a1	|answer is +/- zero
    591	bsetb	#z_bit,FPSR_CC(%a6)
    592	bras	uset_sign
    593uSGL_RM:
    594	tstb	LOCAL_SGN(%a0)	|if negative overflow
    595	beqs	us_rm_pos
    596us_rm_neg:
    597	leal	SGL_PSML,%a1	|answer is smallest denormalized negative
    598	bsetb	#neg_bit,FPSR_CC(%a6)
    599	bras	end_unfr
    600us_rm_pos:
    601	leal	SGL_PZRO,%a1	|answer is positive zero
    602	bsetb	#z_bit,FPSR_CC(%a6)
    603	bras	end_unfr
    604uSGL_RP:
    605	tstb	LOCAL_SGN(%a0)	|if negative overflow
    606	beqs	us_rp_pos
    607us_rp_neg:
    608	leal	SGL_PZRO,%a1	|answer is negative zero
    609	oril	#negz_mask,USER_FPSR(%a6)
    610	bras	end_unfr
    611us_rp_pos:
    612	leal	SGL_PSML,%a1	|answer is smallest denormalized positive
    613	bras	end_unfr
    614
    615uset_sign:
    616	tstb	LOCAL_SGN(%a0)	|if negative overflow
    617	beqs	end_unfr
    618uneg_sign:
    619	bsetb	#neg_bit,FPSR_CC(%a6)
    620
    621end_unfr:
    622	movew	LOCAL_EX(%a1),LOCAL_EX(%a0) |be careful not to overwrite sign
    623	movel	LOCAL_HI(%a1),LOCAL_HI(%a0)
    624	movel	LOCAL_LO(%a1),LOCAL_LO(%a0)
    625	rts
    626|
    627|	reg_dest --- write byte, word, or long data to Dn
    628|
    629|
    630| Input:
    631|	L_SCR1: Data
    632|	d1:     data size and dest register number formatted as:
    633|
    634|	32		5    4     3     2     1     0
    635|       -----------------------------------------------
    636|       |        0        |    Size   |  Dest Reg #   |
    637|       -----------------------------------------------
    638|
    639|	Size is:
    640|		0 - Byte
    641|		1 - Word
    642|		2 - Long/Single
    643|
    644pregdst:
    645	.long	byte_d0
    646	.long	byte_d1
    647	.long	byte_d2
    648	.long	byte_d3
    649	.long	byte_d4
    650	.long	byte_d5
    651	.long	byte_d6
    652	.long	byte_d7
    653	.long	word_d0
    654	.long	word_d1
    655	.long	word_d2
    656	.long	word_d3
    657	.long	word_d4
    658	.long	word_d5
    659	.long	word_d6
    660	.long	word_d7
    661	.long	long_d0
    662	.long	long_d1
    663	.long	long_d2
    664	.long	long_d3
    665	.long	long_d4
    666	.long	long_d5
    667	.long	long_d6
    668	.long	long_d7
    669
    670reg_dest:
    671	leal	pregdst,%a0
    672	movel	%a0@(%d1:l:4),%a0
    673	jmp	(%a0)
    674
    675byte_d0:
    676	moveb	L_SCR1(%a6),USER_D0+3(%a6)
    677	rts
    678byte_d1:
    679	moveb	L_SCR1(%a6),USER_D1+3(%a6)
    680	rts
    681byte_d2:
    682	moveb	L_SCR1(%a6),%d2
    683	rts
    684byte_d3:
    685	moveb	L_SCR1(%a6),%d3
    686	rts
    687byte_d4:
    688	moveb	L_SCR1(%a6),%d4
    689	rts
    690byte_d5:
    691	moveb	L_SCR1(%a6),%d5
    692	rts
    693byte_d6:
    694	moveb	L_SCR1(%a6),%d6
    695	rts
    696byte_d7:
    697	moveb	L_SCR1(%a6),%d7
    698	rts
    699word_d0:
    700	movew	L_SCR1(%a6),USER_D0+2(%a6)
    701	rts
    702word_d1:
    703	movew	L_SCR1(%a6),USER_D1+2(%a6)
    704	rts
    705word_d2:
    706	movew	L_SCR1(%a6),%d2
    707	rts
    708word_d3:
    709	movew	L_SCR1(%a6),%d3
    710	rts
    711word_d4:
    712	movew	L_SCR1(%a6),%d4
    713	rts
    714word_d5:
    715	movew	L_SCR1(%a6),%d5
    716	rts
    717word_d6:
    718	movew	L_SCR1(%a6),%d6
    719	rts
    720word_d7:
    721	movew	L_SCR1(%a6),%d7
    722	rts
    723long_d0:
    724	movel	L_SCR1(%a6),USER_D0(%a6)
    725	rts
    726long_d1:
    727	movel	L_SCR1(%a6),USER_D1(%a6)
    728	rts
    729long_d2:
    730	movel	L_SCR1(%a6),%d2
    731	rts
    732long_d3:
    733	movel	L_SCR1(%a6),%d3
    734	rts
    735long_d4:
    736	movel	L_SCR1(%a6),%d4
    737	rts
    738long_d5:
    739	movel	L_SCR1(%a6),%d5
    740	rts
    741long_d6:
    742	movel	L_SCR1(%a6),%d6
    743	rts
    744long_d7:
    745	movel	L_SCR1(%a6),%d7
    746	rts
    747	|end