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

scale.S (8926B)


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