config: fix build with external compiler by passing the sysroot where needed
[AROS.git] / arch / m68k-all / m680x0 / fpsp / kernel_ex.sa
blob98807a91adb424b99b2102f8dc0d69761f8576e9
1 *       $NetBSD: kernel_ex.sa,v 1.2 1994/10/26 07:49:12 cgd Exp $
3 *       MOTOROLA MICROPROCESSOR & MEMORY TECHNOLOGY GROUP
4 *       M68000 Hi-Performance Microprocessor Division
5 *       M68040 Software Package 
7 *       M68040 Software Package Copyright (c) 1993, 1994 Motorola Inc.
8 *       All rights reserved.
10 *       THE SOFTWARE is provided on an "AS IS" basis and without warranty.
11 *       To the maximum extent permitted by applicable law,
12 *       MOTOROLA DISCLAIMS ALL WARRANTIES WHETHER EXPRESS OR IMPLIED,
13 *       INCLUDING IMPLIED WARRANTIES OF MERCHANTABILITY OR FITNESS FOR A
14 *       PARTICULAR PURPOSE and any warranty against infringement with
15 *       regard to the SOFTWARE (INCLUDING ANY MODIFIED VERSIONS THEREOF)
16 *       and any accompanying written materials. 
18 *       To the maximum extent permitted by applicable law,
19 *       IN NO EVENT SHALL MOTOROLA BE LIABLE FOR ANY DAMAGES WHATSOEVER
20 *       (INCLUDING WITHOUT LIMITATION, DAMAGES FOR LOSS OF BUSINESS
21 *       PROFITS, BUSINESS INTERRUPTION, LOSS OF BUSINESS INFORMATION, OR
22 *       OTHER PECUNIARY LOSS) ARISING OF THE USE OR INABILITY TO USE THE
23 *       SOFTWARE.  Motorola assumes no responsibility for the maintenance
24 *       and support of the SOFTWARE.  
26 *       You are hereby granted a copyright license to use, modify, and
27 *       distribute the SOFTWARE so long as this entire notice is retained
28 *       without alteration in any modified and/or redistributed versions,
29 *       and that such modified versions are clearly identified as such.
30 *       No licenses are granted by implication, estoppel or otherwise
31 *       under any patents or trademarks of Motorola, Inc.
34 *       kernel_ex.sa 3.3 12/19/90 
36 * This file contains routines to force exception status in the 
37 * fpu for exceptional cases detected or reported within the
38 * transcendental functions.  Typically, the t_xx routine will
39 * set the appropriate bits in the USER_FPSR word on the stack.
40 * The bits are tested in gen_except.sa to determine if an exceptional
41 * situation needs to be created on return from the FPSP. 
44 KERNEL_EX    IDNT    2,1 Motorola 040 Floating Point Software Package
46         section    8
48         include fpsp.h
50 mns_inf  dc.l $ffff0000,$00000000,$00000000
51 pls_inf  dc.l $7fff0000,$00000000,$00000000
52 nan      dc.l $7fff0000,$ffffffff,$ffffffff
53 huge     dc.l $7ffe0000,$ffffffff,$ffffffff
55         xref      ovf_r_k
56         xref      unf_sub
57         xref      nrm_set
59         xdef      t_dz
60         xdef      t_dz2
61         xdef      t_operr
62         xdef      t_unfl
63         xdef      t_ovfl
64         xdef      t_ovfl2
65         xdef      t_inx2
66         xdef      t_frcinx
67         xdef      t_extdnrm
68         xdef      t_resdnrm
69         xdef      dst_nan
70         xdef      src_nan
72 *       DZ exception
75 *       if dz trap disabled
76 *               store properly signed inf (use sign of etemp) into fp0
77 *               set FPSR exception status dz bit, condition code 
78 *               inf bit, and accrued dz bit
79 *               return
80 *               frestore the frame into the machine (done by unimp_hd)
82 *       else dz trap enabled
83 *               set exception status bit & accrued bits in FPSR
84 *               set flag to disable sto_res from corrupting fp register
85 *               return
86 *               frestore the frame into the machine (done by unimp_hd)
88 * t_dz2 is used by monadic functions such as flogn (from do_func).
89 * t_dz is used by monadic functions such as satanh (from the 
90 * transcendental function).
92 t_dz2:
93         bset.b  #neg_bit,FPSR_CC(a6)    ;set neg bit in FPSR
94         fmove.l #0,FPSR                 ;clr status bits (Z set)
95         btst.b  #dz_bit,FPCR_ENABLE(a6) ;test FPCR for dz exc enabled
96         bne.b   dz_ena_end
97         bra.b   m_inf                   ;flogx always returns -inf
98 t_dz:
99         fmove.l #0,FPSR                 ;clr status bits (Z set)
100         btst.b  #dz_bit,FPCR_ENABLE(a6) ;test FPCR for dz exc enabled
101         bne.b   dz_ena
103 *       dz disabled
105         btst.b  #sign_bit,ETEMP_EX(a6)  ;check sign for neg or pos
106         beq.b   p_inf                   ;branch if pos sign
108 m_inf:
109         fmovem.x mns_inf,fp0            ;load -inf
110         bset.b  #neg_bit,FPSR_CC(a6)    ;set neg bit in FPSR
111         bra.b   set_fpsr
112 p_inf:
113         fmovem.x pls_inf,fp0            ;load +inf
114 set_fpsr:
115         or.l    #dzinf_mask,USER_FPSR(a6) ;set I,DZ,ADZ
116         rts
118 *       dz enabled
120 dz_ena:
121         btst.b  #sign_bit,ETEMP_EX(a6)  ;check sign for neg or pos
122         beq.b   dz_ena_end
123         bset.b  #neg_bit,FPSR_CC(a6)    ;set neg bit in FPSR
124 dz_ena_end:
125         or.l    #dzinf_mask,USER_FPSR(a6) ;set I,DZ,ADZ
126         st.b    STORE_FLG(a6)
127         rts
129 *       OPERR exception
131 *       if (operr trap disabled)
132 *               set FPSR exception status operr bit, condition code 
133 *               nan bit; Store default NAN into fp0
134 *               frestore the frame into the machine (done by unimp_hd)
135 *       
136 *       else (operr trap enabled)
137 *               set FPSR exception status operr bit, accrued operr bit
138 *               set flag to disable sto_res from corrupting fp register
139 *               frestore the frame into the machine (done by unimp_hd)
141 t_operr:
142         or.l    #opnan_mask,USER_FPSR(a6) ;set NaN, OPERR, AIOP
144         btst.b  #operr_bit,FPCR_ENABLE(a6) ;test FPCR for operr enabled
145         bne.b   op_ena
147         fmovem.x nan,fp0                ;load default nan
148         rts
149 op_ena:
150         st.b    STORE_FLG(a6)           ;do not corrupt destination
151         rts
154 *       t_unfl --- UNFL exception
156 * This entry point is used by all routines requiring unfl, inex2,
157 * aunfl, and ainex to be set on exit.
159 * On entry, a0 points to the exceptional operand.  The final exceptional
160 * operand is built in FP_SCR1 and only the sign from the original operand
161 * is used.
163 t_unfl:
164         clr.l   FP_SCR1(a6)             ;set exceptional operand to zero
165         clr.l   FP_SCR1+4(a6)
166         clr.l   FP_SCR1+8(a6)
167         tst.b   (a0)                    ;extract sign from caller's exop
168         bpl.b   unfl_signok
169         bset    #sign_bit,FP_SCR1(a6)
170 unfl_signok:
171         lea.l   FP_SCR1(a6),a0
172         or.l    #unfinx_mask,USER_FPSR(a6)
173 *                                       ;set UNFL, INEX2, AUNFL, AINEX
174 unfl_con:
175         btst.b  #unfl_bit,FPCR_ENABLE(a6)
176         beq.b   unfl_dis
178 unfl_ena:
179         bfclr   STAG(a6){5:3}           ;clear wbtm66,wbtm1,wbtm0
180         bset.b  #wbtemp15_bit,WB_BYTE(a6) ;set wbtemp15
181         bset.b  #sticky_bit,STICKY(a6)  ;set sticky bit
183         bclr.b  #E1,E_BYTE(a6)
185 unfl_dis:
186         bfextu  FPCR_MODE(a6){0:2},d0   ;get round precision
187         
188         bclr.b  #sign_bit,LOCAL_EX(a0)
189         sne     LOCAL_SGN(a0)           ;convert to internal ext format
191         bsr     unf_sub                 ;returns IEEE result at a0
192 *                                       ;and sets FPSR_CC accordingly
193         
194         bfclr   LOCAL_SGN(a0){0:8}      ;convert back to IEEE ext format
195         beq.b   unfl_fin
197         bset.b  #sign_bit,LOCAL_EX(a0)
198         bset.b  #sign_bit,FP_SCR1(a6)   ;set sign bit of exc operand
200 unfl_fin:
201         fmovem.x (a0),fp0               ;store result in fp0
202         rts
203         
206 *       t_ovfl2 --- OVFL exception (without inex2 returned)
208 * This entry is used by scale to force catastrophic overflow.  The
209 * ovfl, aovfl, and ainex bits are set, but not the inex2 bit.
211 t_ovfl2:
212         or.l    #ovfl_inx_mask,USER_FPSR(a6)
213         move.l  ETEMP(a6),FP_SCR1(a6)
214         move.l  ETEMP_HI(a6),FP_SCR1+4(a6)
215         move.l  ETEMP_LO(a6),FP_SCR1+8(a6)
217 * Check for single or double round precision.  If single, check if
218 * the lower 40 bits of ETEMP are zero; if not, set inex2.  If double,
219 * check if the lower 21 bits are zero; if not, set inex2.
221         move.b  FPCR_MODE(a6),d0
222         andi.b  #$c0,d0
223         beq.w   t_work          ;if extended, finish ovfl processing
224         cmpi.b  #$40,d0         ;test for single
225         bne.b   t_dbl
226 t_sgl:
227         tst.b   ETEMP_LO(a6)
228         bne.b   t_setinx2
229         move.l  ETEMP_HI(a6),d0
230         andi.l  #$ff,d0         ;look at only lower 8 bits
231         bne.b   t_setinx2
232         bra.w   t_work
233 t_dbl:
234         move.l  ETEMP_LO(a6),d0
235         andi.l  #$7ff,d0        ;look at only lower 11 bits
236         beq.w   t_work
237 t_setinx2:
238         or.l    #inex2_mask,USER_FPSR(a6)
239         bra.b   t_work
241 *       t_ovfl --- OVFL exception
243 *** Note: the exc operand is returned in ETEMP.
245 t_ovfl:
246         or.l    #ovfinx_mask,USER_FPSR(a6)
247 t_work:
248         btst.b  #ovfl_bit,FPCR_ENABLE(a6) ;test FPCR for ovfl enabled
249         beq.b   ovf_dis
251 ovf_ena:
252         clr.l   FP_SCR1(a6)             ;set exceptional operand
253         clr.l   FP_SCR1+4(a6)
254         clr.l   FP_SCR1+8(a6)
256         bfclr   STAG(a6){5:3}           ;clear wbtm66,wbtm1,wbtm0
257         bclr.b  #wbtemp15_bit,WB_BYTE(a6) ;clear wbtemp15
258         bset.b  #sticky_bit,STICKY(a6)  ;set sticky bit
260         bclr.b  #E1,E_BYTE(a6)
261 *                                       ;fall through to disabled case
263 * For disabled overflow call 'ovf_r_k'.  This routine loads the
264 * correct result based on the rounding precision, destination
265 * format, rounding mode and sign.
267 ovf_dis:
268         bsr     ovf_r_k                 ;returns unsigned ETEMP_EX
269 *                                       ;and sets FPSR_CC accordingly.
270         bfclr   ETEMP_SGN(a6){0:8}      ;fix sign
271         beq.b   ovf_pos
272         bset.b  #sign_bit,ETEMP_EX(a6)
273         bset.b  #sign_bit,FP_SCR1(a6)   ;set exceptional operand sign
274 ovf_pos:
275         fmovem.x ETEMP(a6),fp0          ;move the result to fp0
276         rts
280 *       INEX2 exception
282 * The inex2 and ainex bits are set.
284 t_inx2:
285         or.l    #inx2a_mask,USER_FPSR(a6) ;set INEX2, AINEX
286         rts
289 *       Force Inex2
291 * This routine is called by the transcendental routines to force
292 * the inex2 exception bits set in the FPSR.  If the underflow bit
293 * is set, but the underflow trap was not taken, the aunfl bit in
294 * the FPSR must be set.
296 t_frcinx:
297         or.l    #inx2a_mask,USER_FPSR(a6) ;set INEX2, AINEX
298         btst.b  #unfl_bit,FPSR_EXCEPT(a6) ;test for unfl bit set
299         beq.b   no_uacc1                ;if clear, do not set aunfl
300         bset.b  #aunfl_bit,FPSR_AEXCEPT(a6)
301 no_uacc1:
302         rts
305 *       DST_NAN
307 * Determine if the destination nan is signalling or non-signalling,
308 * and set the FPSR bits accordingly.  See the MC68040 User's Manual 
309 * section 3.2.2.5 NOT-A-NUMBERS.
311 dst_nan:
312         btst.b  #sign_bit,FPTEMP_EX(a6) ;test sign of nan
313         beq.b   dst_pos                 ;if clr, it was positive
314         bset.b  #neg_bit,FPSR_CC(a6)    ;set N bit
315 dst_pos:
316         btst.b  #signan_bit,FPTEMP_HI(a6) ;check if signalling 
317         beq.b   dst_snan                ;branch if signalling
319         fmove.l d1,fpcr                 ;restore user's rmode/prec
320         fmove.x FPTEMP(a6),fp0          ;return the non-signalling nan
322 * Check the source nan.  If it is signalling, snan will be reported.
324         move.b  STAG(a6),d0
325         andi.b  #$e0,d0
326         cmpi.b  #$60,d0
327         bne.b   no_snan
328         btst.b  #signan_bit,ETEMP_HI(a6) ;check if signalling 
329         bne.b   no_snan
330         or.l    #snaniop_mask,USER_FPSR(a6) ;set NAN, SNAN, AIOP
331 no_snan:
332         rts     
334 dst_snan:
335         btst.b  #snan_bit,FPCR_ENABLE(a6) ;check if trap enabled 
336         beq.b   dst_dis                 ;branch if disabled
338         or.b    #nan_tag,DTAG(a6)       ;set up dtag for nan
339         st.b    STORE_FLG(a6)           ;do not store a result
340         or.l    #snaniop_mask,USER_FPSR(a6) ;set NAN, SNAN, AIOP
341         rts
343 dst_dis:
344         bset.b  #signan_bit,FPTEMP_HI(a6) ;set SNAN bit in sop 
345         fmove.l d1,fpcr                 ;restore user's rmode/prec
346         fmove.x FPTEMP(a6),fp0          ;load non-sign. nan 
347         or.l    #snaniop_mask,USER_FPSR(a6) ;set NAN, SNAN, AIOP
348         rts
351 *       SRC_NAN
353 * Determine if the source nan is signalling or non-signalling,
354 * and set the FPSR bits accordingly.  See the MC68040 User's Manual 
355 * section 3.2.2.5 NOT-A-NUMBERS.
357 src_nan:
358         btst.b  #sign_bit,ETEMP_EX(a6) ;test sign of nan
359         beq.b   src_pos                 ;if clr, it was positive
360         bset.b  #neg_bit,FPSR_CC(a6)    ;set N bit
361 src_pos:
362         btst.b  #signan_bit,ETEMP_HI(a6) ;check if signalling 
363         beq.b   src_snan                ;branch if signalling
364         fmove.l d1,fpcr                 ;restore user's rmode/prec
365         fmove.x ETEMP(a6),fp0           ;return the non-signalling nan
366         rts     
368 src_snan:
369         btst.b  #snan_bit,FPCR_ENABLE(a6) ;check if trap enabled 
370         beq.b   src_dis                 ;branch if disabled
371         bset.b  #signan_bit,ETEMP_HI(a6) ;set SNAN bit in sop 
372         or.b    #norm_tag,DTAG(a6)      ;set up dtag for norm
373         or.b    #nan_tag,STAG(a6)       ;set up stag for nan
374         st.b    STORE_FLG(a6)           ;do not store a result
375         or.l    #snaniop_mask,USER_FPSR(a6) ;set NAN, SNAN, AIOP
376         rts
378 src_dis:
379         bset.b  #signan_bit,ETEMP_HI(a6) ;set SNAN bit in sop 
380         fmove.l d1,fpcr                 ;restore user's rmode/prec
381         fmove.x ETEMP(a6),fp0           ;load non-sign. nan 
382         or.l    #snaniop_mask,USER_FPSR(a6) ;set NAN, SNAN, AIOP
383         rts
386 * For all functions that have a denormalized input and that f(x)=x,
387 * this is the entry point
389 t_extdnrm:
390         or.l    #unfinx_mask,USER_FPSR(a6)
391 *                                       ;set UNFL, INEX2, AUNFL, AINEX
392         bra.b   xdnrm_con
394 * Entry point for scale with extended denorm.  The function does
395 * not set inex2, aunfl, or ainex.  
397 t_resdnrm:
398         or.l    #unfl_mask,USER_FPSR(a6)
400 xdnrm_con:
401         btst.b  #unfl_bit,FPCR_ENABLE(a6)
402         beq.b   xdnrm_dis
405 * If exceptions are enabled, the additional task of setting up WBTEMP
406 * is needed so that when the underflow exception handler is entered,
407 * the user perceives no difference between what the 040 provides vs.
408 * what the FPSP provides.
410 xdnrm_ena:
411         move.l  a0,-(a7)
413         move.l  LOCAL_EX(a0),FP_SCR1(a6)
414         move.l  LOCAL_HI(a0),FP_SCR1+4(a6)
415         move.l  LOCAL_LO(a0),FP_SCR1+8(a6)
417         lea     FP_SCR1(a6),a0
419         bclr.b  #sign_bit,LOCAL_EX(a0)
420         sne     LOCAL_SGN(a0)           ;convert to internal ext format
421         tst.w   LOCAL_EX(a0)            ;check if input is denorm
422         beq.b   xdnrm_dn                ;if so, skip nrm_set
423         bsr     nrm_set                 ;normalize the result (exponent
424 *                                       ;will be negative
425 xdnrm_dn:
426         bclr.b  #sign_bit,LOCAL_EX(a0)  ;take off false sign
427         bfclr   LOCAL_SGN(a0){0:8}      ;change back to IEEE ext format
428         beq.b   xdep
429         bset.b  #sign_bit,LOCAL_EX(a0)
430 xdep:   
431         bfclr   STAG(a6){5:3}           ;clear wbtm66,wbtm1,wbtm0
432         bset.b  #wbtemp15_bit,WB_BYTE(a6) ;set wbtemp15
433         bclr.b  #sticky_bit,STICKY(a6)  ;clear sticky bit
434         bclr.b  #E1,E_BYTE(a6)
435         move.l  (a7)+,a0
436 xdnrm_dis:
437         bfextu  FPCR_MODE(a6){0:2},d0   ;get round precision
438         bne.b   not_ext                 ;if not round extended, store
439 *                                       ;IEEE defaults
440 is_ext:
441         btst.b  #sign_bit,LOCAL_EX(a0)
442         beq.b   xdnrm_store
444         bset.b  #neg_bit,FPSR_CC(a6)    ;set N bit in FPSR_CC
446         bra.b   xdnrm_store
448 not_ext:
449         bclr.b  #sign_bit,LOCAL_EX(a0)
450         sne     LOCAL_SGN(a0)           ;convert to internal ext format
451         bsr     unf_sub                 ;returns IEEE result pointed by
452 *                                       ;a0; sets FPSR_CC accordingly
453         bfclr   LOCAL_SGN(a0){0:8}      ;convert back to IEEE ext format
454         beq.b   xdnrm_store
455         bset.b  #sign_bit,LOCAL_EX(a0)
456 xdnrm_store:
457         fmovem.x (a0),fp0               ;store result in fp0
458         rts
461 * This subroutine is used for dyadic operations that use an extended
462 * denorm within the kernel. The approach used is to capture the frame,
463 * fix/restore.
465         xdef    t_avoid_unsupp
466 t_avoid_unsupp:
467         link    a2,#-LOCAL_SIZE         ;so that a2 fpsp.h negative 
468 *                                       ;offsets may be used
469         fsave   -(a7)
470         tst.b   1(a7)                   ;check if idle, exit if so
471         beq.w   idle_end
472         btst.b  #E1,E_BYTE(a2)          ;check for an E1 exception if
473 *                                       ;enabled, there is an unsupp
474         beq.w   end_avun                ;else, exit
475         btst.b  #7,DTAG(a2)             ;check for denorm destination
476         beq.b   src_den                 ;else, must be a source denorm
478 * handle destination denorm
480         lea     FPTEMP(a2),a0
481         btst.b  #sign_bit,LOCAL_EX(a0)
482         sne     LOCAL_SGN(a0)           ;convert to internal ext format
483         bclr.b  #7,DTAG(a2)             ;set DTAG to norm
484         bsr     nrm_set                 ;normalize result, exponent
485 *                                       ;will become negative
486         bclr.b  #sign_bit,LOCAL_EX(a0)  ;get rid of fake sign
487         bfclr   LOCAL_SGN(a0){0:8}      ;convert back to IEEE ext format
488         beq.b   ck_src_den              ;check if source is also denorm
489         bset.b  #sign_bit,LOCAL_EX(a0)
490 ck_src_den:
491         btst.b  #7,STAG(a2)
492         beq.b   end_avun
493 src_den:
494         lea     ETEMP(a2),a0
495         btst.b  #sign_bit,LOCAL_EX(a0)
496         sne     LOCAL_SGN(a0)           ;convert to internal ext format
497         bclr.b  #7,STAG(a2)             ;set STAG to norm
498         bsr     nrm_set                 ;normalize result, exponent
499 *                                       ;will become negative
500         bclr.b  #sign_bit,LOCAL_EX(a0)  ;get rid of fake sign
501         bfclr   LOCAL_SGN(a0){0:8}      ;convert back to IEEE ext format
502         beq.b   den_com
503         bset.b  #sign_bit,LOCAL_EX(a0)
504 den_com:
505         move.b  #$fe,CU_SAVEPC(a2)      ;set continue frame
506         clr.w   NMNEXC(a2)              ;clear NMNEXC
507         bclr.b  #E1,E_BYTE(a2)
508 *       fmove.l FPSR,FPSR_SHADOW(a2)
509 *       bset.b  #SFLAG,E_BYTE(a2)
510 *       bset.b  #XFLAG,T_BYTE(a2)
511 end_avun:
512         frestore (a7)+
513         unlk    a2
514         rts
515 idle_end:
516         add.l   #4,a7
517         unlk    a2
518         rts
519         end