Home | History | Annotate | Line # | Download | only in fpsp
setox.sa revision 1.4.152.1
      1  1.4.152.1  jdolecek *	$NetBSD: setox.sa,v 1.4.152.1 2017/12/03 11:36:23 jdolecek Exp $
      2        1.3       cgd 
      3        1.1   mycroft *	MOTOROLA MICROPROCESSOR & MEMORY TECHNOLOGY GROUP
      4        1.1   mycroft *	M68000 Hi-Performance Microprocessor Division
      5        1.1   mycroft *	M68040 Software Package 
      6        1.1   mycroft *
      7        1.1   mycroft *	M68040 Software Package Copyright (c) 1993, 1994 Motorola Inc.
      8        1.1   mycroft *	All rights reserved.
      9        1.1   mycroft *
     10        1.1   mycroft *	THE SOFTWARE is provided on an "AS IS" basis and without warranty.
     11        1.1   mycroft *	To the maximum extent permitted by applicable law,
     12        1.1   mycroft *	MOTOROLA DISCLAIMS ALL WARRANTIES WHETHER EXPRESS OR IMPLIED,
     13        1.1   mycroft *	INCLUDING IMPLIED WARRANTIES OF MERCHANTABILITY OR FITNESS FOR A
     14        1.1   mycroft *	PARTICULAR PURPOSE and any warranty against infringement with
     15        1.1   mycroft *	regard to the SOFTWARE (INCLUDING ANY MODIFIED VERSIONS THEREOF)
     16        1.1   mycroft *	and any accompanying written materials. 
     17        1.1   mycroft *
     18        1.1   mycroft *	To the maximum extent permitted by applicable law,
     19        1.1   mycroft *	IN NO EVENT SHALL MOTOROLA BE LIABLE FOR ANY DAMAGES WHATSOEVER
     20        1.1   mycroft *	(INCLUDING WITHOUT LIMITATION, DAMAGES FOR LOSS OF BUSINESS
     21        1.1   mycroft *	PROFITS, BUSINESS INTERRUPTION, LOSS OF BUSINESS INFORMATION, OR
     22        1.1   mycroft *	OTHER PECUNIARY LOSS) ARISING OF THE USE OR INABILITY TO USE THE
     23        1.1   mycroft *	SOFTWARE.  Motorola assumes no responsibility for the maintenance
     24        1.1   mycroft *	and support of the SOFTWARE.  
     25        1.1   mycroft *
     26        1.1   mycroft *	You are hereby granted a copyright license to use, modify, and
     27        1.1   mycroft *	distribute the SOFTWARE so long as this entire notice is retained
     28        1.1   mycroft *	without alteration in any modified and/or redistributed versions,
     29        1.1   mycroft *	and that such modified versions are clearly identified as such.
     30        1.1   mycroft *	No licenses are granted by implication, estoppel or otherwise
     31        1.1   mycroft *	under any patents or trademarks of Motorola, Inc.
     32        1.1   mycroft 
     33        1.1   mycroft *
     34        1.1   mycroft *	setox.sa 3.1 12/10/90
     35        1.1   mycroft *
     36        1.1   mycroft *	The entry point setox computes the exponential of a value.
     37        1.1   mycroft *	setoxd does the same except the input value is a denormalized
     38        1.1   mycroft *	number.	setoxm1 computes exp(X)-1, and setoxm1d computes
     39        1.1   mycroft *	exp(X)-1 for denormalized X.
     40        1.1   mycroft *
     41        1.1   mycroft *	INPUT
     42        1.1   mycroft *	-----
     43        1.1   mycroft *	Double-extended value in memory location pointed to by address
     44        1.1   mycroft *	register a0.
     45        1.1   mycroft *
     46        1.1   mycroft *	OUTPUT
     47        1.1   mycroft *	------
     48        1.1   mycroft *	exp(X) or exp(X)-1 returned in floating-point register fp0.
     49        1.1   mycroft *
     50        1.1   mycroft *	ACCURACY and MONOTONICITY
     51        1.1   mycroft *	-------------------------
     52        1.1   mycroft *	The returned result is within 0.85 ulps in 64 significant bit, i.e.
     53        1.1   mycroft *	within 0.5001 ulp to 53 bits if the result is subsequently rounded
     54        1.1   mycroft *	to double precision. The result is provably monotonic in double
     55        1.1   mycroft *	precision.
     56        1.1   mycroft *
     57        1.1   mycroft *	SPEED
     58        1.1   mycroft *	-----
     59        1.1   mycroft *	Two timings are measured, both in the copy-back mode. The
     60        1.1   mycroft *	first one is measured when the function is invoked the first time
     61        1.1   mycroft *	(so the instructions and data are not in cache), and the
     62        1.1   mycroft *	second one is measured when the function is reinvoked at the same
     63        1.1   mycroft *	input argument.
     64        1.1   mycroft *
     65        1.1   mycroft *	The program setox takes approximately 210/190 cycles for input
     66        1.1   mycroft *	argument X whose magnitude is less than 16380 log2, which
     67        1.1   mycroft *	is the usual situation.	For the less common arguments,
     68        1.1   mycroft *	depending on their values, the program may run faster or slower --
     69        1.1   mycroft *	but no worse than 10% slower even in the extreme cases.
     70        1.1   mycroft *
     71  1.4.152.1  jdolecek *	The program setoxm1 takes approximately ??? / ??? cycles for input
     72        1.1   mycroft *	argument X, 0.25 <= |X| < 70log2. For |X| < 0.25, it takes
     73  1.4.152.1  jdolecek *	approximately ??? / ??? cycles. For the less common arguments,
     74        1.1   mycroft *	depending on their values, the program may run faster or slower --
     75        1.1   mycroft *	but no worse than 10% slower even in the extreme cases.
     76        1.1   mycroft *
     77        1.1   mycroft *	ALGORITHM and IMPLEMENTATION NOTES
     78        1.1   mycroft *	----------------------------------
     79        1.1   mycroft *
     80        1.1   mycroft *	setoxd
     81        1.1   mycroft *	------
     82        1.1   mycroft *	Step 1.	Set ans := 1.0
     83        1.1   mycroft *
     84        1.1   mycroft *	Step 2.	Return	ans := ans + sign(X)*2^(-126). Exit.
     85        1.1   mycroft *	Notes:	This will always generate one exception -- inexact.
     86        1.1   mycroft *
     87        1.1   mycroft *
     88        1.1   mycroft *	setox
     89        1.1   mycroft *	-----
     90        1.1   mycroft *
     91        1.1   mycroft *	Step 1.	Filter out extreme cases of input argument.
     92        1.1   mycroft *		1.1	If |X| >= 2^(-65), go to Step 1.3.
     93        1.1   mycroft *		1.2	Go to Step 7.
     94        1.1   mycroft *		1.3	If |X| < 16380 log(2), go to Step 2.
     95        1.1   mycroft *		1.4	Go to Step 8.
     96        1.1   mycroft *	Notes:	The usual case should take the branches 1.1 -> 1.3 -> 2.
     97        1.1   mycroft *		 To avoid the use of floating-point comparisons, a
     98        1.1   mycroft *		 compact representation of |X| is used. This format is a
     99        1.1   mycroft *		 32-bit integer, the upper (more significant) 16 bits are
    100        1.1   mycroft *		 the sign and biased exponent field of |X|; the lower 16
    101        1.1   mycroft *		 bits are the 16 most significant fraction (including the
    102        1.1   mycroft *		 explicit bit) bits of |X|. Consequently, the comparisons
    103        1.1   mycroft *		 in Steps 1.1 and 1.3 can be performed by integer comparison.
    104        1.1   mycroft *		 Note also that the constant 16380 log(2) used in Step 1.3
    105        1.1   mycroft *		 is also in the compact form. Thus taking the branch
    106        1.1   mycroft *		 to Step 2 guarantees |X| < 16380 log(2). There is no harm
    107        1.1   mycroft *		 to have a small number of cases where |X| is less than,
    108        1.1   mycroft *		 but close to, 16380 log(2) and the branch to Step 9 is
    109        1.1   mycroft *		 taken.
    110        1.1   mycroft *
    111        1.1   mycroft *	Step 2.	Calculate N = round-to-nearest-int( X * 64/log2 ).
    112        1.1   mycroft *		2.1	Set AdjFlag := 0 (indicates the branch 1.3 -> 2 was taken)
    113        1.1   mycroft *		2.2	N := round-to-nearest-integer( X * 64/log2 ).
    114        1.1   mycroft *		2.3	Calculate	J = N mod 64; so J = 0,1,2,..., or 63.
    115        1.1   mycroft *		2.4	Calculate	M = (N - J)/64; so N = 64M + J.
    116        1.1   mycroft *		2.5	Calculate the address of the stored value of 2^(J/64).
    117        1.1   mycroft *		2.6	Create the value Scale = 2^M.
    118        1.1   mycroft *	Notes:	The calculation in 2.2 is really performed by
    119        1.1   mycroft *
    120        1.1   mycroft *			Z := X * constant
    121        1.1   mycroft *			N := round-to-nearest-integer(Z)
    122        1.1   mycroft *
    123        1.1   mycroft *		 where
    124        1.1   mycroft *
    125        1.1   mycroft *			constant := single-precision( 64/log 2 ).
    126        1.1   mycroft *
    127        1.1   mycroft *		 Using a single-precision constant avoids memory access.
    128        1.1   mycroft *		 Another effect of using a single-precision "constant" is
    129        1.1   mycroft *		 that the calculated value Z is
    130        1.1   mycroft *
    131        1.1   mycroft *			Z = X*(64/log2)*(1+eps), |eps| <= 2^(-24).
    132        1.1   mycroft *
    133        1.1   mycroft *		 This error has to be considered later in Steps 3 and 4.
    134        1.1   mycroft *
    135        1.1   mycroft *	Step 3.	Calculate X - N*log2/64.
    136        1.1   mycroft *		3.1	R := X + N*L1, where L1 := single-precision(-log2/64).
    137        1.1   mycroft *		3.2	R := R + N*L2, L2 := extended-precision(-log2/64 - L1).
    138        1.1   mycroft *	Notes:	a) The way L1 and L2 are chosen ensures L1+L2 approximate
    139        1.1   mycroft *		 the value	-log2/64	to 88 bits of accuracy.
    140        1.1   mycroft *		 b) N*L1 is exact because N is no longer than 22 bits and
    141        1.1   mycroft *		 L1 is no longer than 24 bits.
    142        1.1   mycroft *		 c) The calculation X+N*L1 is also exact due to cancellation.
    143        1.1   mycroft *		 Thus, R is practically X+N(L1+L2) to full 64 bits.
    144        1.1   mycroft *		 d) It is important to estimate how large can |R| be after
    145        1.1   mycroft *		 Step 3.2.
    146        1.1   mycroft *
    147        1.1   mycroft *			N = rnd-to-int( X*64/log2 (1+eps) ), |eps|<=2^(-24)
    148        1.1   mycroft *			X*64/log2 (1+eps)	=	N + f,	|f| <= 0.5
    149        1.1   mycroft *			X*64/log2 - N	=	f - eps*X 64/log2
    150        1.1   mycroft *			X - N*log2/64	=	f*log2/64 - eps*X
    151        1.1   mycroft *
    152        1.1   mycroft *
    153        1.1   mycroft *		 Now |X| <= 16446 log2, thus
    154        1.1   mycroft *
    155        1.1   mycroft *			|X - N*log2/64| <= (0.5 + 16446/2^(18))*log2/64
    156        1.1   mycroft *					<= 0.57 log2/64.
    157        1.1   mycroft *		 This bound will be used in Step 4.
    158        1.1   mycroft *
    159        1.1   mycroft *	Step 4.	Approximate exp(R)-1 by a polynomial
    160        1.1   mycroft *			p = R + R*R*(A1 + R*(A2 + R*(A3 + R*(A4 + R*A5))))
    161        1.1   mycroft *	Notes:	a) In order to reduce memory access, the coefficients are
    162        1.1   mycroft *		 made as "short" as possible: A1 (which is 1/2), A4 and A5
    163        1.1   mycroft *		 are single precision; A2 and A3 are double precision.
    164        1.1   mycroft *		 b) Even with the restrictions above,
    165        1.1   mycroft *			|p - (exp(R)-1)| < 2^(-68.8) for all |R| <= 0.0062.
    166        1.1   mycroft *		 Note that 0.0062 is slightly bigger than 0.57 log2/64.
    167        1.4     perry *		 c) To fully use the pipeline, p is separated into
    168        1.1   mycroft *		 two independent pieces of roughly equal complexities
    169        1.1   mycroft *			p = [ R + R*S*(A2 + S*A4) ]	+
    170        1.1   mycroft *				[ S*(A1 + S*(A3 + S*A5)) ]
    171        1.1   mycroft *		 where S = R*R.
    172        1.1   mycroft *
    173        1.1   mycroft *	Step 5.	Compute 2^(J/64)*exp(R) = 2^(J/64)*(1+p) by
    174        1.1   mycroft *				ans := T + ( T*p + t)
    175        1.1   mycroft *		 where T and t are the stored values for 2^(J/64).
    176        1.1   mycroft *	Notes:	2^(J/64) is stored as T and t where T+t approximates
    177        1.1   mycroft *		 2^(J/64) to roughly 85 bits; T is in extended precision
    178        1.1   mycroft *		 and t is in single precision. Note also that T is rounded
    179        1.1   mycroft *		 to 62 bits so that the last two bits of T are zero. The
    180        1.1   mycroft *		 reason for such a special form is that T-1, T-2, and T-8
    181        1.1   mycroft *		 will all be exact --- a property that will give much
    182        1.1   mycroft *		 more accurate computation of the function EXPM1.
    183        1.1   mycroft *
    184        1.1   mycroft *	Step 6.	Reconstruction of exp(X)
    185        1.1   mycroft *			exp(X) = 2^M * 2^(J/64) * exp(R).
    186        1.1   mycroft *		6.1	If AdjFlag = 0, go to 6.3
    187        1.1   mycroft *		6.2	ans := ans * AdjScale
    188        1.1   mycroft *		6.3	Restore the user FPCR
    189        1.1   mycroft *		6.4	Return ans := ans * Scale. Exit.
    190        1.1   mycroft *	Notes:	If AdjFlag = 0, we have X = Mlog2 + Jlog2/64 + R,
    191        1.1   mycroft *		 |M| <= 16380, and Scale = 2^M. Moreover, exp(X) will
    192        1.1   mycroft *		 neither overflow nor underflow. If AdjFlag = 1, that
    193        1.1   mycroft *		 means that
    194        1.1   mycroft *			X = (M1+M)log2 + Jlog2/64 + R, |M1+M| >= 16380.
    195        1.1   mycroft *		 Hence, exp(X) may overflow or underflow or neither.
    196        1.1   mycroft *		 When that is the case, AdjScale = 2^(M1) where M1 is
    197        1.1   mycroft *		 approximately M. Thus 6.2 will never cause over/underflow.
    198        1.1   mycroft *		 Possible exception in 6.4 is overflow or underflow.
    199        1.1   mycroft *		 The inexact exception is not generated in 6.4. Although
    200        1.1   mycroft *		 one can argue that the inexact flag should always be
    201        1.1   mycroft *		 raised, to simulate that exception cost to much than the
    202        1.1   mycroft *		 flag is worth in practical uses.
    203        1.1   mycroft *
    204        1.1   mycroft *	Step 7.	Return 1 + X.
    205        1.1   mycroft *		7.1	ans := X
    206        1.1   mycroft *		7.2	Restore user FPCR.
    207        1.1   mycroft *		7.3	Return ans := 1 + ans. Exit
    208        1.1   mycroft *	Notes:	For non-zero X, the inexact exception will always be
    209        1.1   mycroft *		 raised by 7.3. That is the only exception raised by 7.3.
    210        1.1   mycroft *		 Note also that we use the FMOVEM instruction to move X
    211        1.1   mycroft *		 in Step 7.1 to avoid unnecessary trapping. (Although
    212        1.1   mycroft *		 the FMOVEM may not seem relevant since X is normalized,
    213        1.1   mycroft *		 the precaution will be useful in the library version of
    214        1.1   mycroft *		 this code where the separate entry for denormalized inputs
    215        1.1   mycroft *		 will be done away with.)
    216        1.1   mycroft *
    217        1.1   mycroft *	Step 8.	Handle exp(X) where |X| >= 16380log2.
    218        1.1   mycroft *		8.1	If |X| > 16480 log2, go to Step 9.
    219        1.1   mycroft *		(mimic 2.2 - 2.6)
    220        1.1   mycroft *		8.2	N := round-to-integer( X * 64/log2 )
    221        1.1   mycroft *		8.3	Calculate J = N mod 64, J = 0,1,...,63
    222        1.1   mycroft *		8.4	K := (N-J)/64, M1 := truncate(K/2), M = K-M1, AdjFlag := 1.
    223        1.1   mycroft *		8.5	Calculate the address of the stored value 2^(J/64).
    224        1.1   mycroft *		8.6	Create the values Scale = 2^M, AdjScale = 2^M1.
    225        1.1   mycroft *		8.7	Go to Step 3.
    226        1.1   mycroft *	Notes:	Refer to notes for 2.2 - 2.6.
    227        1.1   mycroft *
    228        1.1   mycroft *	Step 9.	Handle exp(X), |X| > 16480 log2.
    229        1.1   mycroft *		9.1	If X < 0, go to 9.3
    230        1.1   mycroft *		9.2	ans := Huge, go to 9.4
    231        1.1   mycroft *		9.3	ans := Tiny.
    232        1.1   mycroft *		9.4	Restore user FPCR.
    233        1.1   mycroft *		9.5	Return ans := ans * ans. Exit.
    234        1.1   mycroft *	Notes:	Exp(X) will surely overflow or underflow, depending on
    235        1.1   mycroft *		 X's sign. "Huge" and "Tiny" are respectively large/tiny
    236        1.1   mycroft *		 extended-precision numbers whose square over/underflow
    237        1.1   mycroft *		 with an inexact result. Thus, 9.5 always raises the
    238        1.1   mycroft *		 inexact together with either overflow or underflow.
    239        1.1   mycroft *
    240        1.1   mycroft *
    241        1.1   mycroft *	setoxm1d
    242        1.1   mycroft *	--------
    243        1.1   mycroft *
    244        1.1   mycroft *	Step 1.	Set ans := 0
    245        1.1   mycroft *
    246        1.1   mycroft *	Step 2.	Return	ans := X + ans. Exit.
    247        1.1   mycroft *	Notes:	This will return X with the appropriate rounding
    248        1.1   mycroft *		 precision prescribed by the user FPCR.
    249        1.1   mycroft *
    250        1.1   mycroft *	setoxm1
    251        1.1   mycroft *	-------
    252        1.1   mycroft *
    253        1.1   mycroft *	Step 1.	Check |X|
    254        1.1   mycroft *		1.1	If |X| >= 1/4, go to Step 1.3.
    255        1.1   mycroft *		1.2	Go to Step 7.
    256        1.1   mycroft *		1.3	If |X| < 70 log(2), go to Step 2.
    257        1.1   mycroft *		1.4	Go to Step 10.
    258        1.1   mycroft *	Notes:	The usual case should take the branches 1.1 -> 1.3 -> 2.
    259        1.1   mycroft *		 However, it is conceivable |X| can be small very often
    260        1.1   mycroft *		 because EXPM1 is intended to evaluate exp(X)-1 accurately
    261        1.1   mycroft *		 when |X| is small. For further details on the comparisons,
    262        1.1   mycroft *		 see the notes on Step 1 of setox.
    263        1.1   mycroft *
    264        1.1   mycroft *	Step 2.	Calculate N = round-to-nearest-int( X * 64/log2 ).
    265        1.1   mycroft *		2.1	N := round-to-nearest-integer( X * 64/log2 ).
    266        1.1   mycroft *		2.2	Calculate	J = N mod 64; so J = 0,1,2,..., or 63.
    267        1.1   mycroft *		2.3	Calculate	M = (N - J)/64; so N = 64M + J.
    268        1.1   mycroft *		2.4	Calculate the address of the stored value of 2^(J/64).
    269        1.1   mycroft *		2.5	Create the values Sc = 2^M and OnebySc := -2^(-M).
    270        1.1   mycroft *	Notes:	See the notes on Step 2 of setox.
    271        1.1   mycroft *
    272        1.1   mycroft *	Step 3.	Calculate X - N*log2/64.
    273        1.1   mycroft *		3.1	R := X + N*L1, where L1 := single-precision(-log2/64).
    274        1.1   mycroft *		3.2	R := R + N*L2, L2 := extended-precision(-log2/64 - L1).
    275        1.1   mycroft *	Notes:	Applying the analysis of Step 3 of setox in this case
    276        1.1   mycroft *		 shows that |R| <= 0.0055 (note that |X| <= 70 log2 in
    277        1.1   mycroft *		 this case).
    278        1.1   mycroft *
    279        1.1   mycroft *	Step 4.	Approximate exp(R)-1 by a polynomial
    280        1.1   mycroft *			p = R+R*R*(A1+R*(A2+R*(A3+R*(A4+R*(A5+R*A6)))))
    281        1.1   mycroft *	Notes:	a) In order to reduce memory access, the coefficients are
    282        1.1   mycroft *		 made as "short" as possible: A1 (which is 1/2), A5 and A6
    283        1.1   mycroft *		 are single precision; A2, A3 and A4 are double precision.
    284        1.1   mycroft *		 b) Even with the restriction above,
    285        1.1   mycroft *			|p - (exp(R)-1)| <	|R| * 2^(-72.7)
    286        1.1   mycroft *		 for all |R| <= 0.0055.
    287        1.4     perry *		 c) To fully use the pipeline, p is separated into
    288        1.1   mycroft *		 two independent pieces of roughly equal complexity
    289        1.1   mycroft *			p = [ R*S*(A2 + S*(A4 + S*A6)) ]	+
    290        1.1   mycroft *				[ R + S*(A1 + S*(A3 + S*A5)) ]
    291        1.1   mycroft *		 where S = R*R.
    292        1.1   mycroft *
    293        1.1   mycroft *	Step 5.	Compute 2^(J/64)*p by
    294        1.1   mycroft *				p := T*p
    295        1.1   mycroft *		 where T and t are the stored values for 2^(J/64).
    296        1.1   mycroft *	Notes:	2^(J/64) is stored as T and t where T+t approximates
    297        1.1   mycroft *		 2^(J/64) to roughly 85 bits; T is in extended precision
    298        1.1   mycroft *		 and t is in single precision. Note also that T is rounded
    299        1.1   mycroft *		 to 62 bits so that the last two bits of T are zero. The
    300        1.1   mycroft *		 reason for such a special form is that T-1, T-2, and T-8
    301        1.1   mycroft *		 will all be exact --- a property that will be exploited
    302        1.1   mycroft *		 in Step 6 below. The total relative error in p is no
    303        1.1   mycroft *		 bigger than 2^(-67.7) compared to the final result.
    304        1.1   mycroft *
    305        1.1   mycroft *	Step 6.	Reconstruction of exp(X)-1
    306        1.1   mycroft *			exp(X)-1 = 2^M * ( 2^(J/64) + p - 2^(-M) ).
    307        1.1   mycroft *		6.1	If M <= 63, go to Step 6.3.
    308        1.1   mycroft *		6.2	ans := T + (p + (t + OnebySc)). Go to 6.6
    309        1.1   mycroft *		6.3	If M >= -3, go to 6.5.
    310        1.1   mycroft *		6.4	ans := (T + (p + t)) + OnebySc. Go to 6.6
    311        1.1   mycroft *		6.5	ans := (T + OnebySc) + (p + t).
    312        1.1   mycroft *		6.6	Restore user FPCR.
    313        1.1   mycroft *		6.7	Return ans := Sc * ans. Exit.
    314        1.1   mycroft *	Notes:	The various arrangements of the expressions give accurate
    315        1.1   mycroft *		 evaluations.
    316        1.1   mycroft *
    317        1.1   mycroft *	Step 7.	exp(X)-1 for |X| < 1/4.
    318        1.1   mycroft *		7.1	If |X| >= 2^(-65), go to Step 9.
    319        1.1   mycroft *		7.2	Go to Step 8.
    320        1.1   mycroft *
    321        1.1   mycroft *	Step 8.	Calculate exp(X)-1, |X| < 2^(-65).
    322        1.1   mycroft *		8.1	If |X| < 2^(-16312), goto 8.3
    323        1.1   mycroft *		8.2	Restore FPCR; return ans := X - 2^(-16382). Exit.
    324        1.1   mycroft *		8.3	X := X * 2^(140).
    325        1.1   mycroft *		8.4	Restore FPCR; ans := ans - 2^(-16382).
    326        1.1   mycroft *		 Return ans := ans*2^(140). Exit
    327        1.1   mycroft *	Notes:	The idea is to return "X - tiny" under the user
    328        1.1   mycroft *		 precision and rounding modes. To avoid unnecessary
    329        1.1   mycroft *		 inefficiency, we stay away from denormalized numbers the
    330        1.1   mycroft *		 best we can. For |X| >= 2^(-16312), the straightforward
    331        1.1   mycroft *		 8.2 generates the inexact exception as the case warrants.
    332        1.1   mycroft *
    333        1.1   mycroft *	Step 9.	Calculate exp(X)-1, |X| < 1/4, by a polynomial
    334        1.1   mycroft *			p = X + X*X*(B1 + X*(B2 + ... + X*B12))
    335        1.1   mycroft *	Notes:	a) In order to reduce memory access, the coefficients are
    336        1.1   mycroft *		 made as "short" as possible: B1 (which is 1/2), B9 to B12
    337        1.1   mycroft *		 are single precision; B3 to B8 are double precision; and
    338        1.1   mycroft *		 B2 is double extended.
    339        1.1   mycroft *		 b) Even with the restriction above,
    340        1.1   mycroft *			|p - (exp(X)-1)| < |X| 2^(-70.6)
    341        1.1   mycroft *		 for all |X| <= 0.251.
    342        1.1   mycroft *		 Note that 0.251 is slightly bigger than 1/4.
    343        1.1   mycroft *		 c) To fully preserve accuracy, the polynomial is computed
    344        1.1   mycroft *		 as	X + ( S*B1 +	Q ) where S = X*X and
    345        1.1   mycroft *			Q	=	X*S*(B2 + X*(B3 + ... + X*B12))
    346        1.4     perry *		 d) To fully use the pipeline, Q is separated into
    347        1.1   mycroft *		 two independent pieces of roughly equal complexity
    348        1.1   mycroft *			Q = [ X*S*(B2 + S*(B4 + ... + S*B12)) ] +
    349        1.1   mycroft *				[ S*S*(B3 + S*(B5 + ... + S*B11)) ]
    350        1.1   mycroft *
    351        1.1   mycroft *	Step 10.	Calculate exp(X)-1 for |X| >= 70 log 2.
    352        1.1   mycroft *		10.1 If X >= 70log2 , exp(X) - 1 = exp(X) for all practical
    353        1.1   mycroft *		 purposes. Therefore, go to Step 1 of setox.
    354        1.1   mycroft *		10.2 If X <= -70log2, exp(X) - 1 = -1 for all practical purposes.
    355        1.1   mycroft *		 ans := -1
    356        1.1   mycroft *		 Restore user FPCR
    357        1.1   mycroft *		 Return ans := ans + 2^(-126). Exit.
    358        1.1   mycroft *	Notes:	10.2 will always create an inexact and return -1 + tiny
    359        1.1   mycroft *		 in the user rounding precision and mode.
    360        1.1   mycroft *
    361        1.1   mycroft 
    362        1.1   mycroft setox	IDNT	2,1 Motorola 040 Floating Point Software Package
    363        1.1   mycroft 
    364        1.1   mycroft 	section	8
    365        1.1   mycroft 
    366        1.1   mycroft 	include	fpsp.h
    367        1.1   mycroft 
    368        1.1   mycroft L2	DC.L	$3FDC0000,$82E30865,$4361C4C6,$00000000
    369        1.1   mycroft 
    370        1.1   mycroft EXPA3	DC.L	$3FA55555,$55554431
    371        1.1   mycroft EXPA2	DC.L	$3FC55555,$55554018
    372        1.1   mycroft 
    373        1.1   mycroft HUGE	DC.L	$7FFE0000,$FFFFFFFF,$FFFFFFFF,$00000000
    374        1.1   mycroft TINY	DC.L	$00010000,$FFFFFFFF,$FFFFFFFF,$00000000
    375        1.1   mycroft 
    376        1.1   mycroft EM1A4	DC.L	$3F811111,$11174385
    377        1.1   mycroft EM1A3	DC.L	$3FA55555,$55554F5A
    378        1.1   mycroft 
    379        1.1   mycroft EM1A2	DC.L	$3FC55555,$55555555,$00000000,$00000000
    380        1.1   mycroft 
    381        1.1   mycroft EM1B8	DC.L	$3EC71DE3,$A5774682
    382        1.1   mycroft EM1B7	DC.L	$3EFA01A0,$19D7CB68
    383        1.1   mycroft 
    384        1.1   mycroft EM1B6	DC.L	$3F2A01A0,$1A019DF3
    385        1.1   mycroft EM1B5	DC.L	$3F56C16C,$16C170E2
    386        1.1   mycroft 
    387        1.1   mycroft EM1B4	DC.L	$3F811111,$11111111
    388        1.1   mycroft EM1B3	DC.L	$3FA55555,$55555555
    389        1.1   mycroft 
    390        1.1   mycroft EM1B2	DC.L	$3FFC0000,$AAAAAAAA,$AAAAAAAB
    391        1.1   mycroft 	DC.L	$00000000
    392        1.1   mycroft 
    393        1.1   mycroft TWO140	DC.L	$48B00000,$00000000
    394        1.1   mycroft TWON140	DC.L	$37300000,$00000000
    395        1.1   mycroft 
    396        1.1   mycroft EXPTBL
    397        1.1   mycroft 	DC.L	$3FFF0000,$80000000,$00000000,$00000000
    398        1.1   mycroft 	DC.L	$3FFF0000,$8164D1F3,$BC030774,$9F841A9B
    399        1.1   mycroft 	DC.L	$3FFF0000,$82CD8698,$AC2BA1D8,$9FC1D5B9
    400        1.1   mycroft 	DC.L	$3FFF0000,$843A28C3,$ACDE4048,$A0728369
    401        1.1   mycroft 	DC.L	$3FFF0000,$85AAC367,$CC487B14,$1FC5C95C
    402        1.1   mycroft 	DC.L	$3FFF0000,$871F6196,$9E8D1010,$1EE85C9F
    403        1.1   mycroft 	DC.L	$3FFF0000,$88980E80,$92DA8528,$9FA20729
    404        1.1   mycroft 	DC.L	$3FFF0000,$8A14D575,$496EFD9C,$A07BF9AF
    405        1.1   mycroft 	DC.L	$3FFF0000,$8B95C1E3,$EA8BD6E8,$A0020DCF
    406        1.1   mycroft 	DC.L	$3FFF0000,$8D1ADF5B,$7E5BA9E4,$205A63DA
    407        1.1   mycroft 	DC.L	$3FFF0000,$8EA4398B,$45CD53C0,$1EB70051
    408        1.1   mycroft 	DC.L	$3FFF0000,$9031DC43,$1466B1DC,$1F6EB029
    409        1.1   mycroft 	DC.L	$3FFF0000,$91C3D373,$AB11C338,$A0781494
    410        1.1   mycroft 	DC.L	$3FFF0000,$935A2B2F,$13E6E92C,$9EB319B0
    411        1.1   mycroft 	DC.L	$3FFF0000,$94F4EFA8,$FEF70960,$2017457D
    412        1.1   mycroft 	DC.L	$3FFF0000,$96942D37,$20185A00,$1F11D537
    413        1.1   mycroft 	DC.L	$3FFF0000,$9837F051,$8DB8A970,$9FB952DD
    414        1.1   mycroft 	DC.L	$3FFF0000,$99E04593,$20B7FA64,$1FE43087
    415        1.1   mycroft 	DC.L	$3FFF0000,$9B8D39B9,$D54E5538,$1FA2A818
    416        1.1   mycroft 	DC.L	$3FFF0000,$9D3ED9A7,$2CFFB750,$1FDE494D
    417        1.1   mycroft 	DC.L	$3FFF0000,$9EF53260,$91A111AC,$20504890
    418        1.1   mycroft 	DC.L	$3FFF0000,$A0B0510F,$B9714FC4,$A073691C
    419        1.1   mycroft 	DC.L	$3FFF0000,$A2704303,$0C496818,$1F9B7A05
    420        1.1   mycroft 	DC.L	$3FFF0000,$A43515AE,$09E680A0,$A0797126
    421        1.1   mycroft 	DC.L	$3FFF0000,$A5FED6A9,$B15138EC,$A071A140
    422        1.1   mycroft 	DC.L	$3FFF0000,$A7CD93B4,$E9653568,$204F62DA
    423        1.1   mycroft 	DC.L	$3FFF0000,$A9A15AB4,$EA7C0EF8,$1F283C4A
    424        1.1   mycroft 	DC.L	$3FFF0000,$AB7A39B5,$A93ED338,$9F9A7FDC
    425        1.1   mycroft 	DC.L	$3FFF0000,$AD583EEA,$42A14AC8,$A05B3FAC
    426        1.1   mycroft 	DC.L	$3FFF0000,$AF3B78AD,$690A4374,$1FDF2610
    427        1.1   mycroft 	DC.L	$3FFF0000,$B123F581,$D2AC2590,$9F705F90
    428        1.1   mycroft 	DC.L	$3FFF0000,$B311C412,$A9112488,$201F678A
    429        1.1   mycroft 	DC.L	$3FFF0000,$B504F333,$F9DE6484,$1F32FB13
    430        1.1   mycroft 	DC.L	$3FFF0000,$B6FD91E3,$28D17790,$20038B30
    431        1.1   mycroft 	DC.L	$3FFF0000,$B8FBAF47,$62FB9EE8,$200DC3CC
    432        1.1   mycroft 	DC.L	$3FFF0000,$BAFF5AB2,$133E45FC,$9F8B2AE6
    433        1.1   mycroft 	DC.L	$3FFF0000,$BD08A39F,$580C36C0,$A02BBF70
    434        1.1   mycroft 	DC.L	$3FFF0000,$BF1799B6,$7A731084,$A00BF518
    435        1.1   mycroft 	DC.L	$3FFF0000,$C12C4CCA,$66709458,$A041DD41
    436        1.1   mycroft 	DC.L	$3FFF0000,$C346CCDA,$24976408,$9FDF137B
    437        1.1   mycroft 	DC.L	$3FFF0000,$C5672A11,$5506DADC,$201F1568
    438        1.1   mycroft 	DC.L	$3FFF0000,$C78D74C8,$ABB9B15C,$1FC13A2E
    439        1.1   mycroft 	DC.L	$3FFF0000,$C9B9BD86,$6E2F27A4,$A03F8F03
    440        1.1   mycroft 	DC.L	$3FFF0000,$CBEC14FE,$F2727C5C,$1FF4907D
    441        1.1   mycroft 	DC.L	$3FFF0000,$CE248C15,$1F8480E4,$9E6E53E4
    442        1.1   mycroft 	DC.L	$3FFF0000,$D06333DA,$EF2B2594,$1FD6D45C
    443        1.1   mycroft 	DC.L	$3FFF0000,$D2A81D91,$F12AE45C,$A076EDB9
    444        1.1   mycroft 	DC.L	$3FFF0000,$D4F35AAB,$CFEDFA20,$9FA6DE21
    445        1.1   mycroft 	DC.L	$3FFF0000,$D744FCCA,$D69D6AF4,$1EE69A2F
    446        1.1   mycroft 	DC.L	$3FFF0000,$D99D15C2,$78AFD7B4,$207F439F
    447        1.1   mycroft 	DC.L	$3FFF0000,$DBFBB797,$DAF23754,$201EC207
    448        1.1   mycroft 	DC.L	$3FFF0000,$DE60F482,$5E0E9124,$9E8BE175
    449        1.1   mycroft 	DC.L	$3FFF0000,$E0CCDEEC,$2A94E110,$20032C4B
    450        1.1   mycroft 	DC.L	$3FFF0000,$E33F8972,$BE8A5A50,$2004DFF5
    451        1.1   mycroft 	DC.L	$3FFF0000,$E5B906E7,$7C8348A8,$1E72F47A
    452        1.1   mycroft 	DC.L	$3FFF0000,$E8396A50,$3C4BDC68,$1F722F22
    453        1.1   mycroft 	DC.L	$3FFF0000,$EAC0C6E7,$DD243930,$A017E945
    454        1.1   mycroft 	DC.L	$3FFF0000,$ED4F301E,$D9942B84,$1F401A5B
    455        1.1   mycroft 	DC.L	$3FFF0000,$EFE4B99B,$DCDAF5CC,$9FB9A9E3
    456        1.1   mycroft 	DC.L	$3FFF0000,$F281773C,$59FFB138,$20744C05
    457        1.1   mycroft 	DC.L	$3FFF0000,$F5257D15,$2486CC2C,$1F773A19
    458        1.1   mycroft 	DC.L	$3FFF0000,$F7D0DF73,$0AD13BB8,$1FFE90D5
    459        1.1   mycroft 	DC.L	$3FFF0000,$FA83B2DB,$722A033C,$A041ED22
    460        1.1   mycroft 	DC.L	$3FFF0000,$FD3E0C0C,$F486C174,$1F853F3A
    461        1.1   mycroft 
    462        1.1   mycroft ADJFLAG	equ L_SCR2
    463        1.1   mycroft SCALE	equ FP_SCR1
    464        1.1   mycroft ADJSCALE equ FP_SCR2
    465        1.1   mycroft SC	equ FP_SCR3
    466        1.1   mycroft ONEBYSC	equ FP_SCR4
    467        1.1   mycroft 
    468        1.1   mycroft 	xref	t_frcinx
    469        1.1   mycroft 	xref	t_extdnrm
    470        1.1   mycroft 	xref	t_unfl
    471        1.1   mycroft 	xref	t_ovfl
    472        1.1   mycroft 
    473        1.1   mycroft 	xdef	setoxd
    474        1.1   mycroft setoxd:
    475        1.1   mycroft *--entry point for EXP(X), X is denormalized
    476        1.1   mycroft 	MOVE.L		(a0),d0
    477        1.1   mycroft 	ANDI.L		#$80000000,d0
    478        1.1   mycroft 	ORI.L		#$00800000,d0		...sign(X)*2^(-126)
    479        1.1   mycroft 	MOVE.L		d0,-(sp)
    480        1.1   mycroft 	FMOVE.S		#:3F800000,fp0
    481        1.1   mycroft 	fmove.l		d1,fpcr
    482        1.1   mycroft 	FADD.S		(sp)+,fp0
    483        1.1   mycroft 	bra		t_frcinx
    484        1.1   mycroft 
    485        1.1   mycroft 	xdef	setox
    486        1.1   mycroft setox:
    487        1.1   mycroft *--entry point for EXP(X), here X is finite, non-zero, and not NaN's
    488        1.1   mycroft 
    489        1.1   mycroft *--Step 1.
    490        1.1   mycroft 	MOVE.L		(a0),d0	 ...load part of input X
    491        1.1   mycroft 	ANDI.L		#$7FFF0000,d0	...biased expo. of X
    492        1.1   mycroft 	CMPI.L		#$3FBE0000,d0	...2^(-65)
    493        1.1   mycroft 	BGE.B		EXPC1		...normal case
    494        1.1   mycroft 	BRA.W		EXPSM
    495        1.1   mycroft 
    496        1.1   mycroft EXPC1:
    497        1.1   mycroft *--The case |X| >= 2^(-65)
    498        1.1   mycroft 	MOVE.W		4(a0),d0	...expo. and partial sig. of |X|
    499        1.1   mycroft 	CMPI.L		#$400CB167,d0	...16380 log2 trunc. 16 bits
    500        1.1   mycroft 	BLT.B		EXPMAIN	 ...normal case
    501        1.1   mycroft 	BRA.W		EXPBIG
    502        1.1   mycroft 
    503        1.1   mycroft EXPMAIN:
    504        1.1   mycroft *--Step 2.
    505        1.1   mycroft *--This is the normal branch:	2^(-65) <= |X| < 16380 log2.
    506        1.1   mycroft 	FMOVE.X		(a0),fp0	...load input from (a0)
    507        1.1   mycroft 
    508        1.1   mycroft 	FMOVE.X		fp0,fp1
    509        1.1   mycroft 	FMUL.S		#:42B8AA3B,fp0	...64/log2 * X
    510        1.1   mycroft 	fmovem.x	fp2/fp3,-(a7)		...save fp2
    511        1.2   mycroft 	CLR.L		ADJFLAG(a6)
    512        1.1   mycroft 	FMOVE.L		fp0,d0		...N = int( X * 64/log2 )
    513        1.1   mycroft 	LEA		EXPTBL,a1
    514        1.1   mycroft 	FMOVE.L		d0,fp0		...convert to floating-format
    515        1.1   mycroft 
    516        1.1   mycroft 	MOVE.L		d0,L_SCR1(a6)	...save N temporarily
    517        1.1   mycroft 	ANDI.L		#$3F,d0		...D0 is J = N mod 64
    518        1.1   mycroft 	LSL.L		#4,d0
    519        1.1   mycroft 	ADDA.L		d0,a1		...address of 2^(J/64)
    520        1.1   mycroft 	MOVE.L		L_SCR1(a6),d0
    521        1.1   mycroft 	ASR.L		#6,d0		...D0 is M
    522        1.1   mycroft 	ADDI.W		#$3FFF,d0	...biased expo. of 2^(M)
    523        1.1   mycroft 	MOVE.W		L2,L_SCR1(a6)	...prefetch L2, no need in CB
    524        1.1   mycroft 
    525        1.1   mycroft EXPCONT1:
    526        1.1   mycroft *--Step 3.
    527        1.1   mycroft *--fp1,fp2 saved on the stack. fp0 is N, fp1 is X,
    528        1.1   mycroft *--a0 points to 2^(J/64), D0 is biased expo. of 2^(M)
    529        1.1   mycroft 	FMOVE.X		fp0,fp2
    530        1.1   mycroft 	FMUL.S		#:BC317218,fp0	...N * L1, L1 = lead(-log2/64)
    531        1.1   mycroft 	FMUL.X		L2,fp2		...N * L2, L1+L2 = -log2/64
    532        1.1   mycroft 	FADD.X		fp1,fp0	 	...X + N*L1
    533        1.1   mycroft 	FADD.X		fp2,fp0		...fp0 is R, reduced arg.
    534        1.1   mycroft *	MOVE.W		#$3FA5,EXPA3	...load EXPA3 in cache
    535        1.1   mycroft 
    536        1.1   mycroft *--Step 4.
    537        1.1   mycroft *--WE NOW COMPUTE EXP(R)-1 BY A POLYNOMIAL
    538        1.1   mycroft *-- R + R*R*(A1 + R*(A2 + R*(A3 + R*(A4 + R*A5))))
    539        1.4     perry *--TO FULLY USE THE PIPELINE, WE COMPUTE S = R*R
    540        1.1   mycroft *--[R+R*S*(A2+S*A4)] + [S*(A1+S*(A3+S*A5))]
    541        1.1   mycroft 
    542        1.1   mycroft 	FMOVE.X		fp0,fp1
    543        1.1   mycroft 	FMUL.X		fp1,fp1	 	...fp1 IS S = R*R
    544        1.1   mycroft 
    545        1.1   mycroft 	FMOVE.S		#:3AB60B70,fp2	...fp2 IS A5
    546        1.2   mycroft *	CLR.W		2(a1)		...load 2^(J/64) in cache
    547        1.1   mycroft 
    548        1.1   mycroft 	FMUL.X		fp1,fp2	 	...fp2 IS S*A5
    549        1.1   mycroft 	FMOVE.X		fp1,fp3
    550        1.1   mycroft 	FMUL.S		#:3C088895,fp3	...fp3 IS S*A4
    551        1.1   mycroft 
    552        1.1   mycroft 	FADD.D		EXPA3,fp2	...fp2 IS A3+S*A5
    553        1.1   mycroft 	FADD.D		EXPA2,fp3	...fp3 IS A2+S*A4
    554        1.1   mycroft 
    555        1.1   mycroft 	FMUL.X		fp1,fp2	 	...fp2 IS S*(A3+S*A5)
    556        1.1   mycroft 	MOVE.W		d0,SCALE(a6)	...SCALE is 2^(M) in extended
    557        1.1   mycroft 	clr.w		SCALE+2(a6)
    558        1.1   mycroft 	move.l		#$80000000,SCALE+4(a6)
    559        1.1   mycroft 	clr.l		SCALE+8(a6)
    560        1.1   mycroft 
    561        1.1   mycroft 	FMUL.X		fp1,fp3	 	...fp3 IS S*(A2+S*A4)
    562        1.1   mycroft 
    563        1.1   mycroft 	FADD.S		#:3F000000,fp2	...fp2 IS A1+S*(A3+S*A5)
    564        1.1   mycroft 	FMUL.X		fp0,fp3	 	...fp3 IS R*S*(A2+S*A4)
    565        1.1   mycroft 
    566        1.1   mycroft 	FMUL.X		fp1,fp2	 	...fp2 IS S*(A1+S*(A3+S*A5))
    567        1.1   mycroft 	FADD.X		fp3,fp0	 	...fp0 IS R+R*S*(A2+S*A4),
    568        1.1   mycroft *					...fp3 released
    569        1.1   mycroft 
    570        1.1   mycroft 	FMOVE.X		(a1)+,fp1	...fp1 is lead. pt. of 2^(J/64)
    571        1.1   mycroft 	FADD.X		fp2,fp0	 	...fp0 is EXP(R) - 1
    572        1.1   mycroft *					...fp2 released
    573        1.1   mycroft 
    574        1.1   mycroft *--Step 5
    575        1.1   mycroft *--final reconstruction process
    576        1.1   mycroft *--EXP(X) = 2^M * ( 2^(J/64) + 2^(J/64)*(EXP(R)-1) )
    577        1.1   mycroft 
    578        1.1   mycroft 	FMUL.X		fp1,fp0	 	...2^(J/64)*(Exp(R)-1)
    579        1.1   mycroft 	fmovem.x	(a7)+,fp2/fp3	...fp2 restored
    580        1.1   mycroft 	FADD.S		(a1),fp0	...accurate 2^(J/64)
    581        1.1   mycroft 
    582        1.1   mycroft 	FADD.X		fp1,fp0	 	...2^(J/64) + 2^(J/64)*...
    583        1.1   mycroft 	MOVE.L		ADJFLAG(a6),d0
    584        1.1   mycroft 
    585        1.1   mycroft *--Step 6
    586        1.1   mycroft 	TST.L		D0
    587        1.1   mycroft 	BEQ.B		NORMAL
    588        1.1   mycroft ADJUST:
    589        1.1   mycroft 	FMUL.X		ADJSCALE(a6),fp0
    590        1.1   mycroft NORMAL:
    591        1.1   mycroft 	FMOVE.L		d1,FPCR	 	...restore user FPCR
    592        1.1   mycroft 	FMUL.X		SCALE(a6),fp0	...multiply 2^(M)
    593        1.1   mycroft 	bra		t_frcinx
    594        1.1   mycroft 
    595        1.1   mycroft EXPSM:
    596        1.1   mycroft *--Step 7
    597        1.1   mycroft 	FMOVEM.X	(a0),fp0	...in case X is denormalized
    598        1.1   mycroft 	FMOVE.L		d1,FPCR
    599        1.1   mycroft 	FADD.S		#:3F800000,fp0	...1+X in user mode
    600        1.1   mycroft 	bra		t_frcinx
    601        1.1   mycroft 
    602        1.1   mycroft EXPBIG:
    603        1.1   mycroft *--Step 8
    604        1.1   mycroft 	CMPI.L		#$400CB27C,d0	...16480 log2
    605        1.1   mycroft 	BGT.B		EXP2BIG
    606        1.1   mycroft *--Steps 8.2 -- 8.6
    607        1.1   mycroft 	FMOVE.X		(a0),fp0	...load input from (a0)
    608        1.1   mycroft 
    609        1.1   mycroft 	FMOVE.X		fp0,fp1
    610        1.1   mycroft 	FMUL.S		#:42B8AA3B,fp0	...64/log2 * X
    611        1.1   mycroft 	fmovem.x	 fp2/fp3,-(a7)		...save fp2
    612        1.1   mycroft 	MOVE.L		#1,ADJFLAG(a6)
    613        1.1   mycroft 	FMOVE.L		fp0,d0		...N = int( X * 64/log2 )
    614        1.1   mycroft 	LEA		EXPTBL,a1
    615        1.1   mycroft 	FMOVE.L		d0,fp0		...convert to floating-format
    616        1.1   mycroft 	MOVE.L		d0,L_SCR1(a6)			...save N temporarily
    617        1.1   mycroft 	ANDI.L		#$3F,d0		 ...D0 is J = N mod 64
    618        1.1   mycroft 	LSL.L		#4,d0
    619        1.1   mycroft 	ADDA.L		d0,a1			...address of 2^(J/64)
    620        1.1   mycroft 	MOVE.L		L_SCR1(a6),d0
    621        1.1   mycroft 	ASR.L		#6,d0			...D0 is K
    622        1.1   mycroft 	MOVE.L		d0,L_SCR1(a6)			...save K temporarily
    623        1.1   mycroft 	ASR.L		#1,d0			...D0 is M1
    624        1.1   mycroft 	SUB.L		d0,L_SCR1(a6)			...a1 is M
    625        1.1   mycroft 	ADDI.W		#$3FFF,d0		...biased expo. of 2^(M1)
    626        1.1   mycroft 	MOVE.W		d0,ADJSCALE(a6)		...ADJSCALE := 2^(M1)
    627        1.1   mycroft 	clr.w		ADJSCALE+2(a6)
    628        1.1   mycroft 	move.l		#$80000000,ADJSCALE+4(a6)
    629        1.1   mycroft 	clr.l		ADJSCALE+8(a6)
    630        1.1   mycroft 	MOVE.L		L_SCR1(a6),d0			...D0 is M
    631        1.1   mycroft 	ADDI.W		#$3FFF,d0		...biased expo. of 2^(M)
    632        1.1   mycroft 	BRA.W		EXPCONT1		...go back to Step 3
    633        1.1   mycroft 
    634        1.1   mycroft EXP2BIG:
    635        1.1   mycroft *--Step 9
    636        1.1   mycroft 	FMOVE.L		d1,FPCR
    637        1.1   mycroft 	MOVE.L		(a0),d0
    638        1.1   mycroft 	bclr.b		#sign_bit,(a0)		...setox always returns positive
    639        1.2   mycroft 	TST.L		d0
    640        1.1   mycroft 	BLT		t_unfl
    641        1.1   mycroft 	BRA		t_ovfl
    642        1.1   mycroft 
    643        1.1   mycroft 	xdef	setoxm1d
    644        1.1   mycroft setoxm1d:
    645        1.1   mycroft *--entry point for EXPM1(X), here X is denormalized
    646        1.1   mycroft *--Step 0.
    647        1.1   mycroft 	bra		t_extdnrm
    648        1.1   mycroft 
    649        1.1   mycroft 
    650        1.1   mycroft 	xdef	setoxm1
    651        1.1   mycroft setoxm1:
    652        1.1   mycroft *--entry point for EXPM1(X), here X is finite, non-zero, non-NaN
    653        1.1   mycroft 
    654        1.1   mycroft *--Step 1.
    655        1.1   mycroft *--Step 1.1
    656        1.1   mycroft 	MOVE.L		(a0),d0	 ...load part of input X
    657        1.1   mycroft 	ANDI.L		#$7FFF0000,d0	...biased expo. of X
    658        1.1   mycroft 	CMPI.L		#$3FFD0000,d0	...1/4
    659        1.1   mycroft 	BGE.B		EM1CON1	 ...|X| >= 1/4
    660        1.1   mycroft 	BRA.W		EM1SM
    661        1.1   mycroft 
    662        1.1   mycroft EM1CON1:
    663        1.1   mycroft *--Step 1.3
    664        1.1   mycroft *--The case |X| >= 1/4
    665        1.1   mycroft 	MOVE.W		4(a0),d0	...expo. and partial sig. of |X|
    666        1.1   mycroft 	CMPI.L		#$4004C215,d0	...70log2 rounded up to 16 bits
    667        1.1   mycroft 	BLE.B		EM1MAIN	 ...1/4 <= |X| <= 70log2
    668        1.1   mycroft 	BRA.W		EM1BIG
    669        1.1   mycroft 
    670        1.1   mycroft EM1MAIN:
    671        1.1   mycroft *--Step 2.
    672        1.1   mycroft *--This is the case:	1/4 <= |X| <= 70 log2.
    673        1.1   mycroft 	FMOVE.X		(a0),fp0	...load input from (a0)
    674        1.1   mycroft 
    675        1.1   mycroft 	FMOVE.X		fp0,fp1
    676        1.1   mycroft 	FMUL.S		#:42B8AA3B,fp0	...64/log2 * X
    677        1.1   mycroft 	fmovem.x	fp2/fp3,-(a7)		...save fp2
    678        1.1   mycroft *	MOVE.W		#$3F81,EM1A4		...prefetch in CB mode
    679        1.1   mycroft 	FMOVE.L		fp0,d0		...N = int( X * 64/log2 )
    680        1.1   mycroft 	LEA		EXPTBL,a1
    681        1.1   mycroft 	FMOVE.L		d0,fp0		...convert to floating-format
    682        1.1   mycroft 
    683        1.1   mycroft 	MOVE.L		d0,L_SCR1(a6)			...save N temporarily
    684        1.1   mycroft 	ANDI.L		#$3F,d0		 ...D0 is J = N mod 64
    685        1.1   mycroft 	LSL.L		#4,d0
    686        1.1   mycroft 	ADDA.L		d0,a1			...address of 2^(J/64)
    687        1.1   mycroft 	MOVE.L		L_SCR1(a6),d0
    688        1.1   mycroft 	ASR.L		#6,d0			...D0 is M
    689        1.1   mycroft 	MOVE.L		d0,L_SCR1(a6)			...save a copy of M
    690        1.1   mycroft *	MOVE.W		#$3FDC,L2		...prefetch L2 in CB mode
    691        1.1   mycroft 
    692        1.1   mycroft *--Step 3.
    693        1.1   mycroft *--fp1,fp2 saved on the stack. fp0 is N, fp1 is X,
    694        1.1   mycroft *--a0 points to 2^(J/64), D0 and a1 both contain M
    695        1.1   mycroft 	FMOVE.X		fp0,fp2
    696        1.1   mycroft 	FMUL.S		#:BC317218,fp0	...N * L1, L1 = lead(-log2/64)
    697        1.1   mycroft 	FMUL.X		L2,fp2		...N * L2, L1+L2 = -log2/64
    698        1.1   mycroft 	FADD.X		fp1,fp0	 ...X + N*L1
    699        1.1   mycroft 	FADD.X		fp2,fp0	 ...fp0 is R, reduced arg.
    700        1.1   mycroft *	MOVE.W		#$3FC5,EM1A2		...load EM1A2 in cache
    701        1.1   mycroft 	ADDI.W		#$3FFF,d0		...D0 is biased expo. of 2^M
    702        1.1   mycroft 
    703        1.1   mycroft *--Step 4.
    704        1.1   mycroft *--WE NOW COMPUTE EXP(R)-1 BY A POLYNOMIAL
    705        1.1   mycroft *-- R + R*R*(A1 + R*(A2 + R*(A3 + R*(A4 + R*(A5 + R*A6)))))
    706        1.4     perry *--TO FULLY USE THE PIPELINE, WE COMPUTE S = R*R
    707        1.1   mycroft *--[R*S*(A2+S*(A4+S*A6))] + [R+S*(A1+S*(A3+S*A5))]
    708        1.1   mycroft 
    709        1.1   mycroft 	FMOVE.X		fp0,fp1
    710        1.1   mycroft 	FMUL.X		fp1,fp1		...fp1 IS S = R*R
    711        1.1   mycroft 
    712        1.1   mycroft 	FMOVE.S		#:3950097B,fp2	...fp2 IS a6
    713        1.2   mycroft *	CLR.W		2(a1)		...load 2^(J/64) in cache
    714        1.1   mycroft 
    715        1.1   mycroft 	FMUL.X		fp1,fp2		...fp2 IS S*A6
    716        1.1   mycroft 	FMOVE.X		fp1,fp3
    717        1.1   mycroft 	FMUL.S		#:3AB60B6A,fp3	...fp3 IS S*A5
    718        1.1   mycroft 
    719        1.1   mycroft 	FADD.D		EM1A4,fp2	...fp2 IS A4+S*A6
    720        1.1   mycroft 	FADD.D		EM1A3,fp3	...fp3 IS A3+S*A5
    721        1.1   mycroft 	MOVE.W		d0,SC(a6)		...SC is 2^(M) in extended
    722        1.1   mycroft 	clr.w		SC+2(a6)
    723        1.1   mycroft 	move.l		#$80000000,SC+4(a6)
    724        1.1   mycroft 	clr.l		SC+8(a6)
    725        1.1   mycroft 
    726        1.1   mycroft 	FMUL.X		fp1,fp2		...fp2 IS S*(A4+S*A6)
    727        1.1   mycroft 	MOVE.L		L_SCR1(a6),d0		...D0 is	M
    728        1.1   mycroft 	NEG.W		D0		...D0 is -M
    729        1.1   mycroft 	FMUL.X		fp1,fp3		...fp3 IS S*(A3+S*A5)
    730        1.1   mycroft 	ADDI.W		#$3FFF,d0	...biased expo. of 2^(-M)
    731        1.1   mycroft 	FADD.D		EM1A2,fp2	...fp2 IS A2+S*(A4+S*A6)
    732        1.1   mycroft 	FADD.S		#:3F000000,fp3	...fp3 IS A1+S*(A3+S*A5)
    733        1.1   mycroft 
    734        1.1   mycroft 	FMUL.X		fp1,fp2		...fp2 IS S*(A2+S*(A4+S*A6))
    735        1.1   mycroft 	ORI.W		#$8000,d0	...signed/expo. of -2^(-M)
    736        1.1   mycroft 	MOVE.W		d0,ONEBYSC(a6)	...OnebySc is -2^(-M)
    737        1.1   mycroft 	clr.w		ONEBYSC+2(a6)
    738        1.1   mycroft 	move.l		#$80000000,ONEBYSC+4(a6)
    739        1.1   mycroft 	clr.l		ONEBYSC+8(a6)
    740        1.1   mycroft 	FMUL.X		fp3,fp1		...fp1 IS S*(A1+S*(A3+S*A5))
    741        1.1   mycroft *					...fp3 released
    742        1.1   mycroft 
    743        1.1   mycroft 	FMUL.X		fp0,fp2		...fp2 IS R*S*(A2+S*(A4+S*A6))
    744        1.1   mycroft 	FADD.X		fp1,fp0		...fp0 IS R+S*(A1+S*(A3+S*A5))
    745        1.1   mycroft *					...fp1 released
    746        1.1   mycroft 
    747        1.1   mycroft 	FADD.X		fp2,fp0		...fp0 IS EXP(R)-1
    748        1.1   mycroft *					...fp2 released
    749        1.1   mycroft 	fmovem.x	(a7)+,fp2/fp3	...fp2 restored
    750        1.1   mycroft 
    751        1.1   mycroft *--Step 5
    752        1.1   mycroft *--Compute 2^(J/64)*p
    753        1.1   mycroft 
    754        1.1   mycroft 	FMUL.X		(a1),fp0	...2^(J/64)*(Exp(R)-1)
    755        1.1   mycroft 
    756        1.1   mycroft *--Step 6
    757        1.1   mycroft *--Step 6.1
    758        1.1   mycroft 	MOVE.L		L_SCR1(a6),d0		...retrieve M
    759        1.1   mycroft 	CMPI.L		#63,d0
    760        1.1   mycroft 	BLE.B		MLE63
    761        1.1   mycroft *--Step 6.2	M >= 64
    762        1.1   mycroft 	FMOVE.S		12(a1),fp1	...fp1 is t
    763        1.1   mycroft 	FADD.X		ONEBYSC(a6),fp1	...fp1 is t+OnebySc
    764        1.1   mycroft 	FADD.X		fp1,fp0		...p+(t+OnebySc), fp1 released
    765        1.1   mycroft 	FADD.X		(a1),fp0	...T+(p+(t+OnebySc))
    766        1.1   mycroft 	BRA.B		EM1SCALE
    767        1.1   mycroft MLE63:
    768        1.1   mycroft *--Step 6.3	M <= 63
    769        1.1   mycroft 	CMPI.L		#-3,d0
    770        1.1   mycroft 	BGE.B		MGEN3
    771        1.1   mycroft MLTN3:
    772        1.1   mycroft *--Step 6.4	M <= -4
    773        1.1   mycroft 	FADD.S		12(a1),fp0	...p+t
    774        1.1   mycroft 	FADD.X		(a1),fp0	...T+(p+t)
    775        1.1   mycroft 	FADD.X		ONEBYSC(a6),fp0	...OnebySc + (T+(p+t))
    776        1.1   mycroft 	BRA.B		EM1SCALE
    777        1.1   mycroft MGEN3:
    778        1.1   mycroft *--Step 6.5	-3 <= M <= 63
    779        1.1   mycroft 	FMOVE.X		(a1)+,fp1	...fp1 is T
    780        1.1   mycroft 	FADD.S		(a1),fp0	...fp0 is p+t
    781        1.1   mycroft 	FADD.X		ONEBYSC(a6),fp1	...fp1 is T+OnebySc
    782        1.1   mycroft 	FADD.X		fp1,fp0		...(T+OnebySc)+(p+t)
    783        1.1   mycroft 
    784        1.1   mycroft EM1SCALE:
    785        1.1   mycroft *--Step 6.6
    786        1.1   mycroft 	FMOVE.L		d1,FPCR
    787        1.1   mycroft 	FMUL.X		SC(a6),fp0
    788        1.1   mycroft 
    789        1.1   mycroft 	bra		t_frcinx
    790        1.1   mycroft 
    791        1.1   mycroft EM1SM:
    792        1.1   mycroft *--Step 7	|X| < 1/4.
    793        1.1   mycroft 	CMPI.L		#$3FBE0000,d0	...2^(-65)
    794        1.1   mycroft 	BGE.B		EM1POLY
    795        1.1   mycroft 
    796        1.1   mycroft EM1TINY:
    797        1.1   mycroft *--Step 8	|X| < 2^(-65)
    798        1.1   mycroft 	CMPI.L		#$00330000,d0	...2^(-16312)
    799        1.1   mycroft 	BLT.B		EM12TINY
    800        1.1   mycroft *--Step 8.2
    801        1.1   mycroft 	MOVE.L		#$80010000,SC(a6)	...SC is -2^(-16382)
    802        1.1   mycroft 	move.l		#$80000000,SC+4(a6)
    803        1.1   mycroft 	clr.l		SC+8(a6)
    804        1.1   mycroft 	FMOVE.X		(a0),fp0
    805        1.1   mycroft 	FMOVE.L		d1,FPCR
    806        1.1   mycroft 	FADD.X		SC(a6),fp0
    807        1.1   mycroft 
    808        1.1   mycroft 	bra		t_frcinx
    809        1.1   mycroft 
    810        1.1   mycroft EM12TINY:
    811        1.1   mycroft *--Step 8.3
    812        1.1   mycroft 	FMOVE.X		(a0),fp0
    813        1.1   mycroft 	FMUL.D		TWO140,fp0
    814        1.1   mycroft 	MOVE.L		#$80010000,SC(a6)
    815        1.1   mycroft 	move.l		#$80000000,SC+4(a6)
    816        1.1   mycroft 	clr.l		SC+8(a6)
    817        1.1   mycroft 	FADD.X		SC(a6),fp0
    818        1.1   mycroft 	FMOVE.L		d1,FPCR
    819        1.1   mycroft 	FMUL.D		TWON140,fp0
    820        1.1   mycroft 
    821        1.1   mycroft 	bra		t_frcinx
    822        1.1   mycroft 
    823        1.1   mycroft EM1POLY:
    824        1.1   mycroft *--Step 9	exp(X)-1 by a simple polynomial
    825        1.1   mycroft 	FMOVE.X		(a0),fp0	...fp0 is X
    826        1.1   mycroft 	FMUL.X		fp0,fp0		...fp0 is S := X*X
    827        1.1   mycroft 	fmovem.x	fp2/fp3,-(a7)	...save fp2
    828        1.1   mycroft 	FMOVE.S		#:2F30CAA8,fp1	...fp1 is B12
    829        1.1   mycroft 	FMUL.X		fp0,fp1		...fp1 is S*B12
    830        1.1   mycroft 	FMOVE.S		#:310F8290,fp2	...fp2 is B11
    831        1.1   mycroft 	FADD.S		#:32D73220,fp1	...fp1 is B10+S*B12
    832        1.1   mycroft 
    833        1.1   mycroft 	FMUL.X		fp0,fp2		...fp2 is S*B11
    834        1.1   mycroft 	FMUL.X		fp0,fp1		...fp1 is S*(B10 + ...
    835        1.1   mycroft 
    836        1.1   mycroft 	FADD.S		#:3493F281,fp2	...fp2 is B9+S*...
    837        1.1   mycroft 	FADD.D		EM1B8,fp1	...fp1 is B8+S*...
    838        1.1   mycroft 
    839        1.1   mycroft 	FMUL.X		fp0,fp2		...fp2 is S*(B9+...
    840        1.1   mycroft 	FMUL.X		fp0,fp1		...fp1 is S*(B8+...
    841        1.1   mycroft 
    842        1.1   mycroft 	FADD.D		EM1B7,fp2	...fp2 is B7+S*...
    843        1.1   mycroft 	FADD.D		EM1B6,fp1	...fp1 is B6+S*...
    844        1.1   mycroft 
    845        1.1   mycroft 	FMUL.X		fp0,fp2		...fp2 is S*(B7+...
    846        1.1   mycroft 	FMUL.X		fp0,fp1		...fp1 is S*(B6+...
    847        1.1   mycroft 
    848        1.1   mycroft 	FADD.D		EM1B5,fp2	...fp2 is B5+S*...
    849        1.1   mycroft 	FADD.D		EM1B4,fp1	...fp1 is B4+S*...
    850        1.1   mycroft 
    851        1.1   mycroft 	FMUL.X		fp0,fp2		...fp2 is S*(B5+...
    852        1.1   mycroft 	FMUL.X		fp0,fp1		...fp1 is S*(B4+...
    853        1.1   mycroft 
    854        1.1   mycroft 	FADD.D		EM1B3,fp2	...fp2 is B3+S*...
    855        1.1   mycroft 	FADD.X		EM1B2,fp1	...fp1 is B2+S*...
    856        1.1   mycroft 
    857        1.1   mycroft 	FMUL.X		fp0,fp2		...fp2 is S*(B3+...
    858        1.1   mycroft 	FMUL.X		fp0,fp1		...fp1 is S*(B2+...
    859        1.1   mycroft 
    860        1.1   mycroft 	FMUL.X		fp0,fp2		...fp2 is S*S*(B3+...)
    861        1.1   mycroft 	FMUL.X		(a0),fp1	...fp1 is X*S*(B2...
    862        1.1   mycroft 
    863        1.1   mycroft 	FMUL.S		#:3F000000,fp0	...fp0 is S*B1
    864        1.1   mycroft 	FADD.X		fp2,fp1		...fp1 is Q
    865        1.1   mycroft *					...fp2 released
    866        1.1   mycroft 
    867        1.1   mycroft 	fmovem.x	(a7)+,fp2/fp3	...fp2 restored
    868        1.1   mycroft 
    869        1.1   mycroft 	FADD.X		fp1,fp0		...fp0 is S*B1+Q
    870        1.1   mycroft *					...fp1 released
    871        1.1   mycroft 
    872        1.1   mycroft 	FMOVE.L		d1,FPCR
    873        1.1   mycroft 	FADD.X		(a0),fp0
    874        1.1   mycroft 
    875        1.1   mycroft 	bra		t_frcinx
    876        1.1   mycroft 
    877        1.1   mycroft EM1BIG:
    878        1.1   mycroft *--Step 10	|X| > 70 log2
    879        1.1   mycroft 	MOVE.L		(a0),d0
    880        1.2   mycroft 	TST.L		d0
    881        1.1   mycroft 	BGT.W		EXPC1
    882        1.1   mycroft *--Step 10.2
    883        1.1   mycroft 	FMOVE.S		#:BF800000,fp0	...fp0 is -1
    884        1.1   mycroft 	FMOVE.L		d1,FPCR
    885        1.1   mycroft 	FADD.S		#:00800000,fp0	...-1 + 2^(-126)
    886        1.1   mycroft 
    887        1.1   mycroft 	bra		t_frcinx
    888        1.1   mycroft 
    889        1.1   mycroft 	end
    890