config: fix build with external compiler by passing the sysroot where needed
[AROS.git] / arch / m68k-all / m680x0 / fpsp / res_func.sa
blob5441ec8a7aca9f45ccb6a58ea555a3371e05487a
1 *       $NetBSD: res_func.sa,v 1.5 2001/09/16 16:34:32 wiz 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 *       res_func.sa 3.9 7/29/91
36 * Normalizes denormalized numbers if necessary and updates the
37 * stack frame.  The function is then restored back into the
38 * machine and the 040 completes the operation.  This routine
39 * is only used by the unsupported data type/format handler.
40 * (Exception vector 55).
42 * For packed move out (fmove.p fpm,<ea>) the operation is
43 * completed here; data is packed and moved to user memory. 
44 * The stack is restored to the 040 only in the case of a
45 * reportable exception in the conversion.
48 RES_FUNC    IDNT    2,1 Motorola 040 Floating Point Software Package
50         section 8
52         include fpsp.h
54 sp_bnds:        dc.w    $3f81,$407e
55                 dc.w    $3f6a,$0000
56 dp_bnds:        dc.w    $3c01,$43fe
57                 dc.w    $3bcd,$0000
59         xref    mem_write
60         xref    bindec
61         xref    get_fline
62         xref    round
63         xref    denorm
64         xref    dest_ext
65         xref    dest_dbl
66         xref    dest_sgl
67         xref    unf_sub
68         xref    nrm_set
69         xref    dnrm_lp
70         xref    ovf_res
71         xref    reg_dest
72         xref    t_ovfl
73         xref    t_unfl
75         xdef    res_func
76         xdef    p_move
78 res_func:
79         clr.b   DNRM_FLG(a6)
80         clr.b   RES_FLG(a6)
81         clr.b   CU_ONLY(a6)
82         tst.b   DY_MO_FLG(a6)
83         beq.b   monadic
84 dyadic:
85         btst.b  #7,DTAG(a6)     ;if dop = norm=000, zero=001,
86 *                               ;inf=010 or nan=011
87         beq.b   monadic         ;then branch
88 *                               ;else denorm
89 * HANDLE DESTINATION DENORM HERE
90 *                               ;set dtag to norm
91 *                               ;write the tag & fpte15 to the fstack
92         lea.l   FPTEMP(a6),a0
94         bclr.b  #sign_bit,LOCAL_EX(a0)
95         sne     LOCAL_SGN(a0)
97         bsr     nrm_set         ;normalize number (exp will go negative)
98         bclr.b  #sign_bit,LOCAL_EX(a0) ;get rid of false sign
99         bfclr   LOCAL_SGN(a0){0:8}      ;change back to IEEE ext format
100         beq.b   dpos
101         bset.b  #sign_bit,LOCAL_EX(a0)
102 dpos:
103         bfclr   DTAG(a6){0:4}   ;set tag to normalized, FPTE15 = 0
104         bset.b  #4,DTAG(a6)     ;set FPTE15
105         or.b    #$0f,DNRM_FLG(a6)
106 monadic:
107         lea.l   ETEMP(a6),a0
108         btst.b  #direction_bit,CMDREG1B(a6)     ;check direction
109         bne.w   opclass3                        ;it is a mv out
111 * At this point, only oplcass 0 and 2 possible
113         btst.b  #7,STAG(a6)     ;if sop = norm=000, zero=001,
114 *                               ;inf=010 or nan=011
115         bne.w   mon_dnrm        ;else denorm
116         tst.b   DY_MO_FLG(a6)   ;all cases of dyadic instructions would
117         bne.w   normal          ;require normalization of denorm
119 * At this point:
120 *       monadic instructions:   fabs  = $18  fneg   = $1a  ftst   = $3a
121 *                               fmove = $00  fsmove = $40  fdmove = $44
122 *                               fsqrt = $05* fssqrt = $41  fdsqrt = $45
123 *                               (*fsqrt reencoded to $05)
125         move.w  CMDREG1B(a6),d0 ;get command register
126         andi.l  #$7f,d0                 ;strip to only command word
128 * At this point, fabs, fneg, fsmove, fdmove, ftst, fsqrt, fssqrt, and 
129 * fdsqrt are possible.
130 * For cases fabs, fneg, fsmove, and fdmove goto spos (do not normalize)
131 * For cases fsqrt, fssqrt, and fdsqrt goto nrm_src (do normalize)
133         btst.l  #0,d0
134         bne.w   normal                  ;weed out fsqrt instructions
136 * cu_norm handles fmove in instructions with normalized inputs.
137 * The routine round is used to correctly round the input for the
138 * destination precision and mode.
140 cu_norm:
141         st      CU_ONLY(a6)             ;set cu-only inst flag
142         move.w  CMDREG1B(a6),d0
143         andi.b  #$3b,d0         ;isolate bits to select inst
144         tst.b   d0
145         beq.l   cu_nmove        ;if zero, it is an fmove
146         cmpi.b  #$18,d0
147         beq.l   cu_nabs         ;if $18, it is fabs
148         cmpi.b  #$1a,d0
149         beq.l   cu_nneg         ;if $1a, it is fneg
151 * Inst is ftst.  Check the source operand and set the cc's accordingly.
152 * No write is done, so simply rts.
154 cu_ntst:
155         move.w  LOCAL_EX(a0),d0
156         bclr.l  #15,d0
157         sne     LOCAL_SGN(a0)
158         beq.b   cu_ntpo
159         or.l    #neg_mask,USER_FPSR(a6) ;set N
160 cu_ntpo:
161         cmpi.w  #$7fff,d0       ;test for inf/nan
162         bne.b   cu_ntcz
163         tst.l   LOCAL_HI(a0)
164         bne.b   cu_ntn
165         tst.l   LOCAL_LO(a0)
166         bne.b   cu_ntn
167         or.l    #inf_mask,USER_FPSR(a6)
168         rts
169 cu_ntn:
170         or.l    #nan_mask,USER_FPSR(a6)
171         move.l  ETEMP_EX(a6),FPTEMP_EX(a6)      ;set up fptemp sign for 
172 *                                               ;snan handler
174         rts
175 cu_ntcz:
176         tst.l   LOCAL_HI(a0)
177         bne.l   cu_ntsx
178         tst.l   LOCAL_LO(a0)
179         bne.l   cu_ntsx
180         or.l    #z_mask,USER_FPSR(a6)
181 cu_ntsx:
182         rts
184 * Inst is fabs.  Execute the absolute value function on the input.
185 * Branch to the fmove code.  If the operand is NaN, do nothing.
187 cu_nabs:
188         move.b  STAG(a6),d0
189         btst.l  #5,d0                   ;test for NaN or zero
190         bne     wr_etemp                ;if either, simply write it
191         bclr.b  #7,LOCAL_EX(a0)         ;do abs
192         bra.b   cu_nmove                ;fmove code will finish
194 * Inst is fneg.  Execute the negate value function on the input.
195 * Fall though to the fmove code.  If the operand is NaN, do nothing.
197 cu_nneg:
198         move.b  STAG(a6),d0
199         btst.l  #5,d0                   ;test for NaN or zero
200         bne     wr_etemp                ;if either, simply write it
201         bchg.b  #7,LOCAL_EX(a0)         ;do neg
203 * Inst is fmove.  This code also handles all result writes.
204 * If bit 2 is set, round is forced to double.  If it is clear,
205 * and bit 6 is set, round is forced to single.  If both are clear,
206 * the round precision is found in the fpcr.  If the rounding precision
207 * is double or single, round the result before the write.
209 cu_nmove:
210         move.b  STAG(a6),d0
211         andi.b  #$e0,d0                 ;isolate stag bits
212         bne     wr_etemp                ;if not norm, simply write it
213         btst.b  #2,CMDREG1B+1(a6)       ;check for rd
214         bne     cu_nmrd
215         btst.b  #6,CMDREG1B+1(a6)       ;check for rs
216         bne     cu_nmrs
218 * The move or operation is not with forced precision.  Test for
219 * nan or inf as the input; if so, simply write it to FPn.  Use the
220 * FPCR_MODE byte to get rounding on norms and zeros.
222 cu_nmnr:
223         bfextu  FPCR_MODE(a6){0:2},d0
224         tst.b   d0                      ;check for extended
225         beq     cu_wrexn                ;if so, just write result
226         cmpi.b  #1,d0                   ;check for single
227         beq     cu_nmrs                 ;fall through to double
229 * The move is fdmove or round precision is double.
231 cu_nmrd:
232         move.l  #2,d0                   ;set up the size for denorm
233         move.w  LOCAL_EX(a0),d1         ;compare exponent to double threshold
234         and.w   #$7fff,d1       
235         cmp.w   #$3c01,d1
236         bls     cu_nunfl
237         bfextu  FPCR_MODE(a6){2:2},d1   ;get rmode
238         or.l    #$00020000,d1           ;or in rprec (double)
239         clr.l   d0                      ;clear g,r,s for round
240         bclr.b  #sign_bit,LOCAL_EX(a0)  ;convert to internal format
241         sne     LOCAL_SGN(a0)
242         bsr.l   round
243         bfclr   LOCAL_SGN(a0){0:8}
244         beq.b   cu_nmrdc
245         bset.b  #sign_bit,LOCAL_EX(a0)
246 cu_nmrdc:
247         move.w  LOCAL_EX(a0),d1         ;check for overflow
248         and.w   #$7fff,d1
249         cmp.w   #$43ff,d1
250         bge     cu_novfl                ;take care of overflow case
251         bra.w   cu_wrexn
253 * The move is fsmove or round precision is single.
255 cu_nmrs:
256         move.l  #1,d0
257         move.w  LOCAL_EX(a0),d1
258         and.w   #$7fff,d1
259         cmp.w   #$3f81,d1
260         bls     cu_nunfl
261         bfextu  FPCR_MODE(a6){2:2},d1
262         or.l    #$00010000,d1
263         clr.l   d0
264         bclr.b  #sign_bit,LOCAL_EX(a0)
265         sne     LOCAL_SGN(a0)
266         bsr.l   round
267         bfclr   LOCAL_SGN(a0){0:8}
268         beq.b   cu_nmrsc
269         bset.b  #sign_bit,LOCAL_EX(a0)
270 cu_nmrsc:
271         move.w  LOCAL_EX(a0),d1
272         and.w   #$7FFF,d1
273         cmp.w   #$407f,d1
274         blt     cu_wrexn
276 * The operand is above precision boundaries.  Use t_ovfl to
277 * generate the correct value.
279 cu_novfl:
280         bsr     t_ovfl
281         bra     cu_wrexn
283 * The operand is below precision boundaries.  Use denorm to
284 * generate the correct value.
286 cu_nunfl:
287         bclr.b  #sign_bit,LOCAL_EX(a0)
288         sne     LOCAL_SGN(a0)
289         bsr     denorm
290         bfclr   LOCAL_SGN(a0){0:8}      ;change back to IEEE ext format
291         beq.b   cu_nucont
292         bset.b  #sign_bit,LOCAL_EX(a0)
293 cu_nucont:
294         bfextu  FPCR_MODE(a6){2:2},d1
295         btst.b  #2,CMDREG1B+1(a6)       ;check for rd
296         bne     inst_d
297         btst.b  #6,CMDREG1B+1(a6)       ;check for rs
298         bne     inst_s
299         swap    d1
300         move.b  FPCR_MODE(a6),d1
301         lsr.b   #6,d1
302         swap    d1
303         bra     inst_sd
304 inst_d:
305         or.l    #$00020000,d1
306         bra     inst_sd
307 inst_s:
308         or.l    #$00010000,d1
309 inst_sd:
310         bclr.b  #sign_bit,LOCAL_EX(a0)
311         sne     LOCAL_SGN(a0)
312         bsr.l   round
313         bfclr   LOCAL_SGN(a0){0:8}
314         beq.b   cu_nuflp
315         bset.b  #sign_bit,LOCAL_EX(a0)
316 cu_nuflp:
317         btst.b  #inex2_bit,FPSR_EXCEPT(a6)
318         beq.b   cu_nuninx
319         or.l    #aunfl_mask,USER_FPSR(a6) ;if the round was inex, set AUNFL
320 cu_nuninx:
321         tst.l   LOCAL_HI(a0)            ;test for zero
322         bne.b   cu_nunzro
323         tst.l   LOCAL_LO(a0)
324         bne.b   cu_nunzro
326 * The mantissa is zero from the denorm loop.  Check sign and rmode
327 * to see if rounding should have occurred which would leave the lsb.
329         move.l  USER_FPCR(a6),d0
330         andi.l  #$30,d0         ;isolate rmode
331         cmpi.l  #$20,d0
332         blt.b   cu_nzro
333         bne.b   cu_nrp
334 cu_nrm:
335         tst.w   LOCAL_EX(a0)    ;if positive, set lsb
336         bge.b   cu_nzro
337         btst.b  #7,FPCR_MODE(a6) ;check for double
338         beq.b   cu_nincs
339         bra.b   cu_nincd
340 cu_nrp:
341         tst.w   LOCAL_EX(a0)    ;if positive, set lsb
342         blt.b   cu_nzro
343         btst.b  #7,FPCR_MODE(a6) ;check for double
344         beq.b   cu_nincs
345 cu_nincd:
346         or.l    #$800,LOCAL_LO(a0) ;inc for double
347         bra     cu_nunzro
348 cu_nincs:
349         or.l    #$100,LOCAL_HI(a0) ;inc for single
350         bra     cu_nunzro
351 cu_nzro:
352         or.l    #z_mask,USER_FPSR(a6)
353         move.b  STAG(a6),d0
354         andi.b  #$e0,d0
355         cmpi.b  #$40,d0         ;check if input was tagged zero
356         beq.b   cu_numv
357 cu_nunzro:
358         or.l    #unfl_mask,USER_FPSR(a6) ;set unfl
359 cu_numv:
360         move.l  (a0),ETEMP(a6)
361         move.l  4(a0),ETEMP_HI(a6)
362         move.l  8(a0),ETEMP_LO(a6)
364 * Write the result to memory, setting the fpsr cc bits.  NaN and Inf
365 * bypass cu_wrexn.
367 cu_wrexn:
368         tst.w   LOCAL_EX(a0)            ;test for zero
369         beq.b   cu_wrzero
370         cmp.w   #$8000,LOCAL_EX(a0)     ;test for zero
371         bne.b   cu_wreon
372 cu_wrzero:
373         or.l    #z_mask,USER_FPSR(a6)   ;set Z bit
374 cu_wreon:
375         tst.w   LOCAL_EX(a0)
376         bpl     wr_etemp
377         or.l    #neg_mask,USER_FPSR(a6)
378         bra     wr_etemp
381 * HANDLE SOURCE DENORM HERE
383 *                               ;clear denorm stag to norm
384 *                               ;write the new tag & ete15 to the fstack
385 mon_dnrm:
387 * At this point, check for the cases in which normalizing the 
388 * denorm produces incorrect results.
390         tst.b   DY_MO_FLG(a6)   ;all cases of dyadic instructions would
391         bne.b   nrm_src         ;require normalization of denorm
393 * At this point:
394 *       monadic instructions:   fabs  = $18  fneg   = $1a  ftst   = $3a
395 *                               fmove = $00  fsmove = $40  fdmove = $44
396 *                               fsqrt = $05* fssqrt = $41  fdsqrt = $45
397 *                               (*fsqrt reencoded to $05)
399         move.w  CMDREG1B(a6),d0 ;get command register
400         andi.l  #$7f,d0                 ;strip to only command word
402 * At this point, fabs, fneg, fsmove, fdmove, ftst, fsqrt, fssqrt, and 
403 * fdsqrt are possible.
404 * For cases fabs, fneg, fsmove, and fdmove goto spos (do not normalize)
405 * For cases fsqrt, fssqrt, and fdsqrt goto nrm_src (do normalize)
407         btst.l  #0,d0
408         bne.b   nrm_src         ;weed out fsqrt instructions
409         st      CU_ONLY(a6)     ;set cu-only inst flag
410         bra     cu_dnrm         ;fmove, fabs, fneg, ftst 
411 *                               ;cases go to cu_dnrm
412 nrm_src:
413         bclr.b  #sign_bit,LOCAL_EX(a0)
414         sne     LOCAL_SGN(a0)
415         bsr     nrm_set         ;normalize number (exponent will go 
416 *                               ; negative)
417         bclr.b  #sign_bit,LOCAL_EX(a0) ;get rid of false sign
419         bfclr   LOCAL_SGN(a0){0:8}      ;change back to IEEE ext format
420         beq.b   spos
421         bset.b  #sign_bit,LOCAL_EX(a0)
422 spos:
423         bfclr   STAG(a6){0:4}   ;set tag to normalized, FPTE15 = 0
424         bset.b  #4,STAG(a6)     ;set ETE15
425         or.b    #$f0,DNRM_FLG(a6)
426 normal:
427         tst.b   DNRM_FLG(a6)    ;check if any of the ops were denorms
428         bne     ck_wrap         ;if so, check if it is a potential
429 *                               ;wrap-around case
430 fix_stk:
431         move.b  #$fe,CU_SAVEPC(a6)
432         bclr.b  #E1,E_BYTE(a6)
434         clr.w   NMNEXC(a6)
436         st.b    RES_FLG(a6)     ;indicate that a restore is needed
437         rts
440 * cu_dnrm handles all cu-only instructions (fmove, fabs, fneg, and
441 * ftst) completly in software without an frestore to the 040. 
443 cu_dnrm:
444         st.b    CU_ONLY(a6)
445         move.w  CMDREG1B(a6),d0
446         andi.b  #$3b,d0         ;isolate bits to select inst
447         tst.b   d0
448         beq.l   cu_dmove        ;if zero, it is an fmove
449         cmpi.b  #$18,d0
450         beq.l   cu_dabs         ;if $18, it is fabs
451         cmpi.b  #$1a,d0
452         beq.l   cu_dneg         ;if $1a, it is fneg
454 * Inst is ftst.  Check the source operand and set the cc's accordingly.
455 * No write is done, so simply rts.
457 cu_dtst:
458         move.w  LOCAL_EX(a0),d0
459         bclr.l  #15,d0
460         sne     LOCAL_SGN(a0)
461         beq.b   cu_dtpo
462         or.l    #neg_mask,USER_FPSR(a6) ;set N
463 cu_dtpo:
464         cmpi.w  #$7fff,d0       ;test for inf/nan
465         bne.b   cu_dtcz
466         tst.l   LOCAL_HI(a0)
467         bne.b   cu_dtn
468         tst.l   LOCAL_LO(a0)
469         bne.b   cu_dtn
470         or.l    #inf_mask,USER_FPSR(a6)
471         rts
472 cu_dtn:
473         or.l    #nan_mask,USER_FPSR(a6)
474         move.l  ETEMP_EX(a6),FPTEMP_EX(a6)      ;set up fptemp sign for 
475 *                                               ;snan handler
476         rts
477 cu_dtcz:
478         tst.l   LOCAL_HI(a0)
479         bne.l   cu_dtsx
480         tst.l   LOCAL_LO(a0)
481         bne.l   cu_dtsx
482         or.l    #z_mask,USER_FPSR(a6)
483 cu_dtsx:
484         rts
486 * Inst is fabs.  Execute the absolute value function on the input.
487 * Branch to the fmove code.
489 cu_dabs:
490         bclr.b  #7,LOCAL_EX(a0)         ;do abs
491         bra.b   cu_dmove                ;fmove code will finish
493 * Inst is fneg.  Execute the negate value function on the input.
494 * Fall though to the fmove code.
496 cu_dneg:
497         bchg.b  #7,LOCAL_EX(a0)         ;do neg
499 * Inst is fmove.  This code also handles all result writes.
500 * If bit 2 is set, round is forced to double.  If it is clear,
501 * and bit 6 is set, round is forced to single.  If both are clear,
502 * the round precision is found in the fpcr.  If the rounding precision
503 * is double or single, the result is zero, and the mode is checked
504 * to determine if the lsb of the result should be set.
506 cu_dmove:
507         btst.b  #2,CMDREG1B+1(a6)       ;check for rd
508         bne     cu_dmrd
509         btst.b  #6,CMDREG1B+1(a6)       ;check for rs
510         bne     cu_dmrs
512 * The move or operation is not with forced precision.  Use the
513 * FPCR_MODE byte to get rounding.
515 cu_dmnr:
516         bfextu  FPCR_MODE(a6){0:2},d0
517         tst.b   d0                      ;check for extended
518         beq     cu_wrexd                ;if so, just write result
519         cmpi.b  #1,d0                   ;check for single
520         beq     cu_dmrs                 ;fall through to double
522 * The move is fdmove or round precision is double.  Result is zero.
523 * Check rmode for rp or rm and set lsb accordingly.
525 cu_dmrd:
526         bfextu  FPCR_MODE(a6){2:2},d1   ;get rmode
527         tst.w   LOCAL_EX(a0)            ;check sign
528         blt.b   cu_dmdn
529         cmpi.b  #3,d1                   ;check for rp
530         bne     cu_dpd                  ;load double pos zero
531         bra     cu_dpdr                 ;load double pos zero w/lsb
532 cu_dmdn:
533         cmpi.b  #2,d1                   ;check for rm
534         bne     cu_dnd                  ;load double neg zero
535         bra     cu_dndr                 ;load double neg zero w/lsb
537 * The move is fsmove or round precision is single.  Result is zero.
538 * Check for rp or rm and set lsb accordingly.
540 cu_dmrs:
541         bfextu  FPCR_MODE(a6){2:2},d1   ;get rmode
542         tst.w   LOCAL_EX(a0)            ;check sign
543         blt.b   cu_dmsn
544         cmpi.b  #3,d1                   ;check for rp
545         bne     cu_spd                  ;load single pos zero
546         bra     cu_spdr                 ;load single pos zero w/lsb
547 cu_dmsn:
548         cmpi.b  #2,d1                   ;check for rm
549         bne     cu_snd                  ;load single neg zero
550         bra     cu_sndr                 ;load single neg zero w/lsb
552 * The precision is extended, so the result in etemp is correct.
553 * Simply set unfl (not inex2 or aunfl) and write the result to 
554 * the correct fp register.
555 cu_wrexd:
556         or.l    #unfl_mask,USER_FPSR(a6)
557         tst.w   LOCAL_EX(a0)
558         beq     wr_etemp
559         or.l    #neg_mask,USER_FPSR(a6)
560         bra     wr_etemp
562 * These routines write +/- zero in double format.  The routines
563 * cu_dpdr and cu_dndr set the double lsb.
565 cu_dpd:
566         move.l  #$3c010000,LOCAL_EX(a0) ;force pos double zero
567         clr.l   LOCAL_HI(a0)
568         clr.l   LOCAL_LO(a0)
569         or.l    #z_mask,USER_FPSR(a6)
570         or.l    #unfinx_mask,USER_FPSR(a6)
571         bra     wr_etemp
572 cu_dpdr:
573         move.l  #$3c010000,LOCAL_EX(a0) ;force pos double zero
574         clr.l   LOCAL_HI(a0)
575         move.l  #$800,LOCAL_LO(a0)      ;with lsb set
576         or.l    #unfinx_mask,USER_FPSR(a6)
577         bra     wr_etemp
578 cu_dnd:
579         move.l  #$bc010000,LOCAL_EX(a0) ;force pos double zero
580         clr.l   LOCAL_HI(a0)
581         clr.l   LOCAL_LO(a0)
582         or.l    #z_mask,USER_FPSR(a6)
583         or.l    #neg_mask,USER_FPSR(a6)
584         or.l    #unfinx_mask,USER_FPSR(a6)
585         bra     wr_etemp
586 cu_dndr:
587         move.l  #$bc010000,LOCAL_EX(a0) ;force pos double zero
588         clr.l   LOCAL_HI(a0)
589         move.l  #$800,LOCAL_LO(a0)      ;with lsb set
590         or.l    #neg_mask,USER_FPSR(a6)
591         or.l    #unfinx_mask,USER_FPSR(a6)
592         bra     wr_etemp
594 * These routines write +/- zero in single format.  The routines
595 * cu_dpdr and cu_dndr set the single lsb.
597 cu_spd:
598         move.l  #$3f810000,LOCAL_EX(a0) ;force pos single zero
599         clr.l   LOCAL_HI(a0)
600         clr.l   LOCAL_LO(a0)
601         or.l    #z_mask,USER_FPSR(a6)
602         or.l    #unfinx_mask,USER_FPSR(a6)
603         bra     wr_etemp
604 cu_spdr:
605         move.l  #$3f810000,LOCAL_EX(a0) ;force pos single zero
606         move.l  #$100,LOCAL_HI(a0)      ;with lsb set
607         clr.l   LOCAL_LO(a0)
608         or.l    #unfinx_mask,USER_FPSR(a6)
609         bra     wr_etemp
610 cu_snd:
611         move.l  #$bf810000,LOCAL_EX(a0) ;force pos single zero
612         clr.l   LOCAL_HI(a0)
613         clr.l   LOCAL_LO(a0)
614         or.l    #z_mask,USER_FPSR(a6)
615         or.l    #neg_mask,USER_FPSR(a6)
616         or.l    #unfinx_mask,USER_FPSR(a6)
617         bra     wr_etemp
618 cu_sndr:
619         move.l  #$bf810000,LOCAL_EX(a0) ;force pos single zero
620         move.l  #$100,LOCAL_HI(a0)      ;with lsb set
621         clr.l   LOCAL_LO(a0)
622         or.l    #neg_mask,USER_FPSR(a6)
623         or.l    #unfinx_mask,USER_FPSR(a6)
624         bra     wr_etemp
625         
627 * This code checks for 16-bit overflow conditions on dyadic
628 * operations which are not restorable into the floating-point
629 * unit and must be completed in software.  Basically, this
630 * condition exists with a very large norm and a denorm.  One
631 * of the operands must be denormalized to enter this code.
633 * Flags used:
634 *       DY_MO_FLG contains 0 for monadic op, $ff for dyadic
635 *       DNRM_FLG contains $00 for neither op denormalized
636 *                         $0f for the destination op denormalized
637 *                         $f0 for the source op denormalized
638 *                         $ff for both ops denormalzed
640 * The wrap-around condition occurs for add, sub, div, and cmp
641 * when 
643 *       abs(dest_exp - src_exp) >= $8000
645 * and for mul when
647 *       (dest_exp + src_exp) < $0
649 * we must process the operation here if this case is true.
651 * The rts following the frcfpn routine is the exit from res_func
652 * for this condition.  The restore flag (RES_FLG) is left clear.
653 * No frestore is done unless an exception is to be reported.
655 * For fadd: 
656 *       if(sign_of(dest) != sign_of(src))
657 *               replace exponent of src with $3fff (keep sign)
658 *               use fpu to perform dest+new_src (user's rmode and X)
659 *               clr sticky
660 *       else
661 *               set sticky
662 *       call round with user's precision and mode
663 *       move result to fpn and wbtemp
665 * For fsub:
666 *       if(sign_of(dest) == sign_of(src))
667 *               replace exponent of src with $3fff (keep sign)
668 *               use fpu to perform dest+new_src (user's rmode and X)
669 *               clr sticky
670 *       else
671 *               set sticky
672 *       call round with user's precision and mode
673 *       move result to fpn and wbtemp
675 * For fdiv/fsgldiv:
676 *       if(both operands are denorm)
677 *               restore_to_fpu;
678 *       if(dest is norm)
679 *               force_ovf;
680 *       else(dest is denorm)
681 *               force_unf:
683 * For fcmp:
684 *       if(dest is norm)
685 *               N = sign_of(dest);
686 *       else(dest is denorm)
687 *               N = sign_of(src);
689 * For fmul:
690 *       if(both operands are denorm)
691 *               force_unf;
692 *       if((dest_exp + src_exp) < 0)
693 *               force_unf:
694 *       else
695 *               restore_to_fpu;
697 * local equates:
698 addcode equ     $22
699 subcode equ     $28
700 mulcode equ     $23
701 divcode equ     $20
702 cmpcode equ     $38
703 ck_wrap:
704         tst.b   DY_MO_FLG(a6)   ;check for fsqrt
705         beq     fix_stk         ;if zero, it is fsqrt
706         move.w  CMDREG1B(a6),d0
707         andi.w  #$3b,d0         ;strip to command bits
708         cmpi.w  #addcode,d0
709         beq     wrap_add
710         cmpi.w  #subcode,d0
711         beq     wrap_sub
712         cmpi.w  #mulcode,d0
713         beq     wrap_mul
714         cmpi.w  #cmpcode,d0
715         beq     wrap_cmp
717 * Inst is fdiv.  
719 wrap_div:
720         cmp.b   #$ff,DNRM_FLG(a6) ;if both ops denorm, 
721         beq     fix_stk          ;restore to fpu
723 * One of the ops is denormalized.  Test for wrap condition
724 * and force the result.
726         cmp.b   #$0f,DNRM_FLG(a6) ;check for dest denorm
727         bne.b   div_srcd
728 div_destd:
729         bsr.l   ckinf_ns
730         bne     fix_stk
731         bfextu  ETEMP_EX(a6){1:15},d0   ;get src exp (always pos)
732         bfexts  FPTEMP_EX(a6){1:15},d1  ;get dest exp (always neg)
733         sub.l   d1,d0                   ;subtract dest from src
734         cmp.l   #$7fff,d0
735         blt     fix_stk                 ;if less, not wrap case
736         clr.b   WBTEMP_SGN(a6)
737         move.w  ETEMP_EX(a6),d0         ;find the sign of the result
738         move.w  FPTEMP_EX(a6),d1
739         eor.w   d1,d0
740         andi.w  #$8000,d0
741         beq     force_unf
742         st.b    WBTEMP_SGN(a6)
743         bra     force_unf
745 ckinf_ns:
746         move.b  STAG(a6),d0             ;check source tag for inf or nan
747         bra     ck_in_com
748 ckinf_nd:
749         move.b  DTAG(a6),d0             ;check destination tag for inf or nan
750 ck_in_com:      
751         andi.b  #$60,d0                 ;isolate tag bits
752         cmp.b   #$40,d0                 ;is it inf?
753         beq     nan_or_inf              ;not wrap case
754         cmp.b   #$60,d0                 ;is it nan?
755         beq     nan_or_inf              ;yes, not wrap case?
756         cmp.b   #$20,d0                 ;is it a zero?
757         beq     nan_or_inf              ;yes
758         clr.l   d0
759         rts                             ;then it is either a zero of norm,
760 *                                       ;check wrap case
761 nan_or_inf:
762         moveq.l #-1,d0
763         rts
767 div_srcd:
768         bsr.l   ckinf_nd
769         bne     fix_stk
770         bfextu  FPTEMP_EX(a6){1:15},d0  ;get dest exp (always pos)
771         bfexts  ETEMP_EX(a6){1:15},d1   ;get src exp (always neg)
772         sub.l   d1,d0                   ;subtract src from dest
773         cmp.l   #$8000,d0
774         blt     fix_stk                 ;if less, not wrap case
775         clr.b   WBTEMP_SGN(a6)
776         move.w  ETEMP_EX(a6),d0         ;find the sign of the result
777         move.w  FPTEMP_EX(a6),d1
778         eor.w   d1,d0
779         andi.w  #$8000,d0
780         beq.b   force_ovf
781         st.b    WBTEMP_SGN(a6)
783 * This code handles the case of the instruction resulting in 
784 * an overflow condition.
786 force_ovf:
787         bclr.b  #E1,E_BYTE(a6)
788         or.l    #ovfl_inx_mask,USER_FPSR(a6)
789         clr.w   NMNEXC(a6)
790         lea.l   WBTEMP(a6),a0           ;point a0 to memory location
791         move.w  CMDREG1B(a6),d0
792         btst.l  #6,d0                   ;test for forced precision
793         beq.b   frcovf_fpcr
794         btst.l  #2,d0                   ;check for double
795         bne.b   frcovf_dbl
796         move.l  #$1,d0                  ;inst is forced single
797         bra.b   frcovf_rnd
798 frcovf_dbl:
799         move.l  #$2,d0                  ;inst is forced double
800         bra.b   frcovf_rnd
801 frcovf_fpcr:
802         bfextu  FPCR_MODE(a6){0:2},d0   ;inst not forced - use fpcr prec
803 frcovf_rnd:
805 * The 881/882 does not set inex2 for the following case, so the 
806 * line is commented out to be compatible with 881/882
807 *       tst.b   d0
808 *       beq.b   frcovf_x
809 *       or.l    #inex2_mask,USER_FPSR(a6) ;if prec is s or d, set inex2
811 *frcovf_x:
812         bsr.l   ovf_res                 ;get correct result based on
813 *                                       ;round precision/mode.  This 
814 *                                       ;sets FPSR_CC correctly
815 *                                       ;returns in external format
816         bfclr   WBTEMP_SGN(a6){0:8}
817         beq     frcfpn
818         bset.b  #sign_bit,WBTEMP_EX(a6)
819         bra     frcfpn
821 * Inst is fadd.
823 wrap_add:
824         cmp.b   #$ff,DNRM_FLG(a6) ;if both ops denorm, 
825         beq     fix_stk          ;restore to fpu
827 * One of the ops is denormalized.  Test for wrap condition
828 * and complete the instruction.
830         cmp.b   #$0f,DNRM_FLG(a6) ;check for dest denorm
831         bne.b   add_srcd
832 add_destd:
833         bsr.l   ckinf_ns
834         bne     fix_stk
835         bfextu  ETEMP_EX(a6){1:15},d0   ;get src exp (always pos)
836         bfexts  FPTEMP_EX(a6){1:15},d1  ;get dest exp (always neg)
837         sub.l   d1,d0                   ;subtract dest from src
838         cmp.l   #$8000,d0
839         blt     fix_stk                 ;if less, not wrap case
840         bra     add_wrap
841 add_srcd:
842         bsr.l   ckinf_nd
843         bne     fix_stk
844         bfextu  FPTEMP_EX(a6){1:15},d0  ;get dest exp (always pos)
845         bfexts  ETEMP_EX(a6){1:15},d1   ;get src exp (always neg)
846         sub.l   d1,d0                   ;subtract src from dest
847         cmp.l   #$8000,d0
848         blt     fix_stk                 ;if less, not wrap case
850 * Check the signs of the operands.  If they are unlike, the fpu
851 * can be used to add the norm and 1.0 with the sign of the
852 * denorm and it will correctly generate the result in extended
853 * precision.  We can then call round with no sticky and the result
854 * will be correct for the user's rounding mode and precision.  If
855 * the signs are the same, we call round with the sticky bit set
856 * and the result will be correctfor the user's rounding mode and
857 * precision.
859 add_wrap:
860         move.w  ETEMP_EX(a6),d0
861         move.w  FPTEMP_EX(a6),d1
862         eor.w   d1,d0
863         andi.w  #$8000,d0
864         beq     add_same
866 * The signs are unlike.
868         cmp.b   #$0f,DNRM_FLG(a6) ;is dest the denorm?
869         bne.b   add_u_srcd
870         move.w  FPTEMP_EX(a6),d0
871         andi.w  #$8000,d0
872         or.w    #$3fff,d0       ;force the exponent to +/- 1
873         move.w  d0,FPTEMP_EX(a6) ;in the denorm
874         move.l  USER_FPCR(a6),d0
875         andi.l  #$30,d0
876         fmove.l d0,fpcr         ;set up users rmode and X
877         fmove.x ETEMP(a6),fp0
878         fadd.x  FPTEMP(a6),fp0
879         lea.l   WBTEMP(a6),a0   ;point a0 to wbtemp in frame
880         fmove.l fpsr,d1
881         or.l    d1,USER_FPSR(a6) ;capture cc's and inex from fadd
882         fmove.x fp0,WBTEMP(a6)  ;write result to memory
883         lsr.l   #4,d0           ;put rmode in lower 2 bits
884         move.l  USER_FPCR(a6),d1
885         andi.l  #$c0,d1
886         lsr.l   #6,d1           ;put precision in upper word
887         swap    d1
888         or.l    d0,d1           ;set up for round call
889         clr.l   d0              ;force sticky to zero
890         bclr.b  #sign_bit,WBTEMP_EX(a6)
891         sne     WBTEMP_SGN(a6)
892         bsr.l   round           ;round result to users rmode & prec
893         bfclr   WBTEMP_SGN(a6){0:8}     ;convert back to IEEE ext format
894         beq     frcfpnr
895         bset.b  #sign_bit,WBTEMP_EX(a6)
896         bra     frcfpnr
897 add_u_srcd:
898         move.w  ETEMP_EX(a6),d0
899         andi.w  #$8000,d0
900         or.w    #$3fff,d0       ;force the exponent to +/- 1
901         move.w  d0,ETEMP_EX(a6) ;in the denorm
902         move.l  USER_FPCR(a6),d0
903         andi.l  #$30,d0
904         fmove.l d0,fpcr         ;set up users rmode and X
905         fmove.x ETEMP(a6),fp0
906         fadd.x  FPTEMP(a6),fp0
907         fmove.l fpsr,d1
908         or.l    d1,USER_FPSR(a6) ;capture cc's and inex from fadd
909         lea.l   WBTEMP(a6),a0   ;point a0 to wbtemp in frame
910         fmove.x fp0,WBTEMP(a6)  ;write result to memory
911         lsr.l   #4,d0           ;put rmode in lower 2 bits
912         move.l  USER_FPCR(a6),d1
913         andi.l  #$c0,d1
914         lsr.l   #6,d1           ;put precision in upper word
915         swap    d1
916         or.l    d0,d1           ;set up for round call
917         clr.l   d0              ;force sticky to zero
918         bclr.b  #sign_bit,WBTEMP_EX(a6)
919         sne     WBTEMP_SGN(a6)  ;use internal format for round
920         bsr.l   round           ;round result to users rmode & prec
921         bfclr   WBTEMP_SGN(a6){0:8}     ;convert back to IEEE ext format
922         beq     frcfpnr
923         bset.b  #sign_bit,WBTEMP_EX(a6)
924         bra     frcfpnr
926 * Signs are alike:
928 add_same:
929         cmp.b   #$0f,DNRM_FLG(a6) ;is dest the denorm?
930         bne.b   add_s_srcd
931 add_s_destd:
932         lea.l   ETEMP(a6),a0
933         move.l  USER_FPCR(a6),d0
934         andi.l  #$30,d0
935         lsr.l   #4,d0           ;put rmode in lower 2 bits
936         move.l  USER_FPCR(a6),d1
937         andi.l  #$c0,d1
938         lsr.l   #6,d1           ;put precision in upper word
939         swap    d1
940         or.l    d0,d1           ;set up for round call
941         move.l  #$20000000,d0   ;set sticky for round
942         bclr.b  #sign_bit,ETEMP_EX(a6)
943         sne     ETEMP_SGN(a6)
944         bsr.l   round           ;round result to users rmode & prec
945         bfclr   ETEMP_SGN(a6){0:8}      ;convert back to IEEE ext format
946         beq.b   add_s_dclr
947         bset.b  #sign_bit,ETEMP_EX(a6)
948 add_s_dclr:
949         lea.l   WBTEMP(a6),a0
950         move.l  ETEMP(a6),(a0)  ;write result to wbtemp
951         move.l  ETEMP_HI(a6),4(a0)
952         move.l  ETEMP_LO(a6),8(a0)
953         tst.w   ETEMP_EX(a6)
954         bgt     add_ckovf
955         or.l    #neg_mask,USER_FPSR(a6)
956         bra     add_ckovf
957 add_s_srcd:
958         lea.l   FPTEMP(a6),a0
959         move.l  USER_FPCR(a6),d0
960         andi.l  #$30,d0
961         lsr.l   #4,d0           ;put rmode in lower 2 bits
962         move.l  USER_FPCR(a6),d1
963         andi.l  #$c0,d1
964         lsr.l   #6,d1           ;put precision in upper word
965         swap    d1
966         or.l    d0,d1           ;set up for round call
967         move.l  #$20000000,d0   ;set sticky for round
968         bclr.b  #sign_bit,FPTEMP_EX(a6)
969         sne     FPTEMP_SGN(a6)
970         bsr.l   round           ;round result to users rmode & prec
971         bfclr   FPTEMP_SGN(a6){0:8}     ;convert back to IEEE ext format
972         beq.b   add_s_sclr
973         bset.b  #sign_bit,FPTEMP_EX(a6)
974 add_s_sclr:
975         lea.l   WBTEMP(a6),a0
976         move.l  FPTEMP(a6),(a0) ;write result to wbtemp
977         move.l  FPTEMP_HI(a6),4(a0)
978         move.l  FPTEMP_LO(a6),8(a0)
979         tst.w   FPTEMP_EX(a6)
980         bgt     add_ckovf
981         or.l    #neg_mask,USER_FPSR(a6)
982 add_ckovf:
983         move.w  WBTEMP_EX(a6),d0
984         andi.w  #$7fff,d0
985         cmpi.w  #$7fff,d0
986         bne     frcfpnr
988 * The result has overflowed to $7fff exponent.  Set I, ovfl,
989 * and aovfl, and clr the mantissa (incorrectly set by the
990 * round routine.)
992         or.l    #inf_mask+ovfl_inx_mask,USER_FPSR(a6)   
993         clr.l   4(a0)
994         bra     frcfpnr
996 * Inst is fsub.
998 wrap_sub:
999         cmp.b   #$ff,DNRM_FLG(a6) ;if both ops denorm, 
1000         beq     fix_stk          ;restore to fpu
1002 * One of the ops is denormalized.  Test for wrap condition
1003 * and complete the instruction.
1005         cmp.b   #$0f,DNRM_FLG(a6) ;check for dest denorm
1006         bne.b   sub_srcd
1007 sub_destd:
1008         bsr.l   ckinf_ns
1009         bne     fix_stk
1010         bfextu  ETEMP_EX(a6){1:15},d0   ;get src exp (always pos)
1011         bfexts  FPTEMP_EX(a6){1:15},d1  ;get dest exp (always neg)
1012         sub.l   d1,d0                   ;subtract src from dest
1013         cmp.l   #$8000,d0
1014         blt     fix_stk                 ;if less, not wrap case
1015         bra     sub_wrap
1016 sub_srcd:
1017         bsr.l   ckinf_nd
1018         bne     fix_stk
1019         bfextu  FPTEMP_EX(a6){1:15},d0  ;get dest exp (always pos)
1020         bfexts  ETEMP_EX(a6){1:15},d1   ;get src exp (always neg)
1021         sub.l   d1,d0                   ;subtract dest from src
1022         cmp.l   #$8000,d0
1023         blt     fix_stk                 ;if less, not wrap case
1025 * Check the signs of the operands.  If they are alike, the fpu
1026 * can be used to subtract from the norm 1.0 with the sign of the
1027 * denorm and it will correctly generate the result in extended
1028 * precision.  We can then call round with no sticky and the result
1029 * will be correct for the user's rounding mode and precision.  If
1030 * the signs are unlike, we call round with the sticky bit set
1031 * and the result will be correctfor the user's rounding mode and
1032 * precision.
1034 sub_wrap:
1035         move.w  ETEMP_EX(a6),d0
1036         move.w  FPTEMP_EX(a6),d1
1037         eor.w   d1,d0
1038         andi.w  #$8000,d0
1039         bne     sub_diff
1041 * The signs are alike.
1043         cmp.b   #$0f,DNRM_FLG(a6) ;is dest the denorm?
1044         bne.b   sub_u_srcd
1045         move.w  FPTEMP_EX(a6),d0
1046         andi.w  #$8000,d0
1047         or.w    #$3fff,d0       ;force the exponent to +/- 1
1048         move.w  d0,FPTEMP_EX(a6) ;in the denorm
1049         move.l  USER_FPCR(a6),d0
1050         andi.l  #$30,d0
1051         fmove.l d0,fpcr         ;set up users rmode and X
1052         fmove.x FPTEMP(a6),fp0
1053         fsub.x  ETEMP(a6),fp0
1054         fmove.l fpsr,d1
1055         or.l    d1,USER_FPSR(a6) ;capture cc's and inex from fadd
1056         lea.l   WBTEMP(a6),a0   ;point a0 to wbtemp in frame
1057         fmove.x fp0,WBTEMP(a6)  ;write result to memory
1058         lsr.l   #4,d0           ;put rmode in lower 2 bits
1059         move.l  USER_FPCR(a6),d1
1060         andi.l  #$c0,d1
1061         lsr.l   #6,d1           ;put precision in upper word
1062         swap    d1
1063         or.l    d0,d1           ;set up for round call
1064         clr.l   d0              ;force sticky to zero
1065         bclr.b  #sign_bit,WBTEMP_EX(a6)
1066         sne     WBTEMP_SGN(a6)
1067         bsr.l   round           ;round result to users rmode & prec
1068         bfclr   WBTEMP_SGN(a6){0:8}     ;convert back to IEEE ext format
1069         beq     frcfpnr
1070         bset.b  #sign_bit,WBTEMP_EX(a6)
1071         bra     frcfpnr
1072 sub_u_srcd:
1073         move.w  ETEMP_EX(a6),d0
1074         andi.w  #$8000,d0
1075         or.w    #$3fff,d0       ;force the exponent to +/- 1
1076         move.w  d0,ETEMP_EX(a6) ;in the denorm
1077         move.l  USER_FPCR(a6),d0
1078         andi.l  #$30,d0
1079         fmove.l d0,fpcr         ;set up users rmode and X
1080         fmove.x FPTEMP(a6),fp0
1081         fsub.x  ETEMP(a6),fp0
1082         fmove.l fpsr,d1
1083         or.l    d1,USER_FPSR(a6) ;capture cc's and inex from fadd
1084         lea.l   WBTEMP(a6),a0   ;point a0 to wbtemp in frame
1085         fmove.x fp0,WBTEMP(a6)  ;write result to memory
1086         lsr.l   #4,d0           ;put rmode in lower 2 bits
1087         move.l  USER_FPCR(a6),d1
1088         andi.l  #$c0,d1
1089         lsr.l   #6,d1           ;put precision in upper word
1090         swap    d1
1091         or.l    d0,d1           ;set up for round call
1092         clr.l   d0              ;force sticky to zero
1093         bclr.b  #sign_bit,WBTEMP_EX(a6)
1094         sne     WBTEMP_SGN(a6)
1095         bsr.l   round           ;round result to users rmode & prec
1096         bfclr   WBTEMP_SGN(a6){0:8}     ;convert back to IEEE ext format
1097         beq     frcfpnr
1098         bset.b  #sign_bit,WBTEMP_EX(a6)
1099         bra     frcfpnr
1101 * Signs are unlike:
1103 sub_diff:
1104         cmp.b   #$0f,DNRM_FLG(a6) ;is dest the denorm?
1105         bne.b   sub_s_srcd
1106 sub_s_destd:
1107         lea.l   ETEMP(a6),a0
1108         move.l  USER_FPCR(a6),d0
1109         andi.l  #$30,d0
1110         lsr.l   #4,d0           ;put rmode in lower 2 bits
1111         move.l  USER_FPCR(a6),d1
1112         andi.l  #$c0,d1
1113         lsr.l   #6,d1           ;put precision in upper word
1114         swap    d1
1115         or.l    d0,d1           ;set up for round call
1116         move.l  #$20000000,d0   ;set sticky for round
1118 * Since the dest is the denorm, the sign is the opposite of the
1119 * norm sign.
1121         eori.w  #$8000,ETEMP_EX(a6)     ;flip sign on result
1122         tst.w   ETEMP_EX(a6)
1123         bgt.b   sub_s_dwr
1124         or.l    #neg_mask,USER_FPSR(a6)
1125 sub_s_dwr:
1126         bclr.b  #sign_bit,ETEMP_EX(a6)
1127         sne     ETEMP_SGN(a6)
1128         bsr.l   round           ;round result to users rmode & prec
1129         bfclr   ETEMP_SGN(a6){0:8}      ;convert back to IEEE ext format
1130         beq.b   sub_s_dclr
1131         bset.b  #sign_bit,ETEMP_EX(a6)
1132 sub_s_dclr:
1133         lea.l   WBTEMP(a6),a0
1134         move.l  ETEMP(a6),(a0)  ;write result to wbtemp
1135         move.l  ETEMP_HI(a6),4(a0)
1136         move.l  ETEMP_LO(a6),8(a0)
1137         bra     sub_ckovf
1138 sub_s_srcd:
1139         lea.l   FPTEMP(a6),a0
1140         move.l  USER_FPCR(a6),d0
1141         andi.l  #$30,d0
1142         lsr.l   #4,d0           ;put rmode in lower 2 bits
1143         move.l  USER_FPCR(a6),d1
1144         andi.l  #$c0,d1
1145         lsr.l   #6,d1           ;put precision in upper word
1146         swap    d1
1147         or.l    d0,d1           ;set up for round call
1148         move.l  #$20000000,d0   ;set sticky for round
1149         bclr.b  #sign_bit,FPTEMP_EX(a6)
1150         sne     FPTEMP_SGN(a6)
1151         bsr.l   round           ;round result to users rmode & prec
1152         bfclr   FPTEMP_SGN(a6){0:8}     ;convert back to IEEE ext format
1153         beq.b   sub_s_sclr
1154         bset.b  #sign_bit,FPTEMP_EX(a6)
1155 sub_s_sclr:
1156         lea.l   WBTEMP(a6),a0
1157         move.l  FPTEMP(a6),(a0) ;write result to wbtemp
1158         move.l  FPTEMP_HI(a6),4(a0)
1159         move.l  FPTEMP_LO(a6),8(a0)
1160         tst.w   FPTEMP_EX(a6)
1161         bgt     sub_ckovf
1162         or.l    #neg_mask,USER_FPSR(a6)
1163 sub_ckovf:
1164         move.w  WBTEMP_EX(a6),d0
1165         andi.w  #$7fff,d0
1166         cmpi.w  #$7fff,d0
1167         bne     frcfpnr
1169 * The result has overflowed to $7fff exponent.  Set I, ovfl,
1170 * and aovfl, and clr the mantissa (incorrectly set by the
1171 * round routine.)
1173         or.l    #inf_mask+ovfl_inx_mask,USER_FPSR(a6)   
1174         clr.l   4(a0)
1175         bra     frcfpnr
1177 * Inst is fcmp.
1179 wrap_cmp:
1180         cmp.b   #$ff,DNRM_FLG(a6) ;if both ops denorm, 
1181         beq     fix_stk          ;restore to fpu
1183 * One of the ops is denormalized.  Test for wrap condition
1184 * and complete the instruction.
1186         cmp.b   #$0f,DNRM_FLG(a6) ;check for dest denorm
1187         bne.b   cmp_srcd
1188 cmp_destd:
1189         bsr.l   ckinf_ns
1190         bne     fix_stk
1191         bfextu  ETEMP_EX(a6){1:15},d0   ;get src exp (always pos)
1192         bfexts  FPTEMP_EX(a6){1:15},d1  ;get dest exp (always neg)
1193         sub.l   d1,d0                   ;subtract dest from src
1194         cmp.l   #$8000,d0
1195         blt     fix_stk                 ;if less, not wrap case
1196         tst.w   ETEMP_EX(a6)            ;set N to ~sign_of(src)
1197         bge     cmp_setn
1198         rts
1199 cmp_srcd:
1200         bsr.l   ckinf_nd
1201         bne     fix_stk
1202         bfextu  FPTEMP_EX(a6){1:15},d0  ;get dest exp (always pos)
1203         bfexts  ETEMP_EX(a6){1:15},d1   ;get src exp (always neg)
1204         sub.l   d1,d0                   ;subtract src from dest
1205         cmp.l   #$8000,d0
1206         blt     fix_stk                 ;if less, not wrap case
1207         tst.w   FPTEMP_EX(a6)           ;set N to sign_of(dest)
1208         blt     cmp_setn
1209         rts
1210 cmp_setn:
1211         or.l    #neg_mask,USER_FPSR(a6)
1212         rts
1215 * Inst is fmul.
1217 wrap_mul:
1218         cmp.b   #$ff,DNRM_FLG(a6) ;if both ops denorm, 
1219         beq     force_unf       ;force an underflow (really!)
1221 * One of the ops is denormalized.  Test for wrap condition
1222 * and complete the instruction.
1224         cmp.b   #$0f,DNRM_FLG(a6) ;check for dest denorm
1225         bne.b   mul_srcd
1226 mul_destd:
1227         bsr.l   ckinf_ns
1228         bne     fix_stk
1229         bfextu  ETEMP_EX(a6){1:15},d0   ;get src exp (always pos)
1230         bfexts  FPTEMP_EX(a6){1:15},d1  ;get dest exp (always neg)
1231         add.l   d1,d0                   ;subtract dest from src
1232         bgt     fix_stk
1233         bra     force_unf
1234 mul_srcd:
1235         bsr.l   ckinf_nd
1236         bne     fix_stk
1237         bfextu  FPTEMP_EX(a6){1:15},d0  ;get dest exp (always pos)
1238         bfexts  ETEMP_EX(a6){1:15},d1   ;get src exp (always neg)
1239         add.l   d1,d0                   ;subtract src from dest
1240         bgt     fix_stk
1241         
1243 * This code handles the case of the instruction resulting in 
1244 * an underflow condition.
1246 force_unf:
1247         bclr.b  #E1,E_BYTE(a6)
1248         or.l    #unfinx_mask,USER_FPSR(a6)
1249         clr.w   NMNEXC(a6)
1250         clr.b   WBTEMP_SGN(a6)
1251         move.w  ETEMP_EX(a6),d0         ;find the sign of the result
1252         move.w  FPTEMP_EX(a6),d1
1253         eor.w   d1,d0
1254         andi.w  #$8000,d0
1255         beq.b   frcunfcont
1256         st.b    WBTEMP_SGN(a6)
1257 frcunfcont:
1258         lea     WBTEMP(a6),a0           ;point a0 to memory location
1259         move.w  CMDREG1B(a6),d0
1260         btst.l  #6,d0                   ;test for forced precision
1261         beq.b   frcunf_fpcr
1262         btst.l  #2,d0                   ;check for double
1263         bne.b   frcunf_dbl
1264         move.l  #$1,d0                  ;inst is forced single
1265         bra.b   frcunf_rnd
1266 frcunf_dbl:
1267         move.l  #$2,d0                  ;inst is forced double
1268         bra.b   frcunf_rnd
1269 frcunf_fpcr:
1270         bfextu  FPCR_MODE(a6){0:2},d0   ;inst not forced - use fpcr prec
1271 frcunf_rnd:
1272         bsr.l   unf_sub                 ;get correct result based on
1273 *                                       ;round precision/mode.  This 
1274 *                                       ;sets FPSR_CC correctly
1275         bfclr   WBTEMP_SGN(a6){0:8}     ;convert back to IEEE ext format
1276         beq.b   frcfpn
1277         bset.b  #sign_bit,WBTEMP_EX(a6)
1278         bra     frcfpn
1281 * Write the result to the user's fpn.  All results must be HUGE to be
1282 * written; otherwise the results would have overflowed or underflowed.
1283 * If the rounding precision is single or double, the ovf_res routine
1284 * is needed to correctly supply the max value.
1286 frcfpnr:
1287         move.w  CMDREG1B(a6),d0
1288         btst.l  #6,d0                   ;test for forced precision
1289         beq.b   frcfpn_fpcr
1290         btst.l  #2,d0                   ;check for double
1291         bne.b   frcfpn_dbl
1292         move.l  #$1,d0                  ;inst is forced single
1293         bra.b   frcfpn_rnd
1294 frcfpn_dbl:
1295         move.l  #$2,d0                  ;inst is forced double
1296         bra.b   frcfpn_rnd
1297 frcfpn_fpcr:
1298         bfextu  FPCR_MODE(a6){0:2},d0   ;inst not forced - use fpcr prec
1299         tst.b   d0
1300         beq.b   frcfpn                  ;if extended, write what you got
1301 frcfpn_rnd:
1302         bclr.b  #sign_bit,WBTEMP_EX(a6)
1303         sne     WBTEMP_SGN(a6)
1304         bsr.l   ovf_res                 ;get correct result based on
1305 *                                       ;round precision/mode.  This 
1306 *                                       ;sets FPSR_CC correctly
1307         bfclr   WBTEMP_SGN(a6){0:8}     ;convert back to IEEE ext format
1308         beq.b   frcfpn_clr
1309         bset.b  #sign_bit,WBTEMP_EX(a6)
1310 frcfpn_clr:
1311         or.l    #ovfinx_mask,USER_FPSR(a6)
1313 * Perform the write.
1315 frcfpn:
1316         bfextu  CMDREG1B(a6){6:3},d0    ;extract fp destination register
1317         cmpi.b  #3,d0
1318         ble.b   frc0123                 ;check if dest is fp0-fp3
1319         move.l  #7,d1
1320         sub.l   d0,d1
1321         clr.l   d0
1322         bset.l  d1,d0
1323         fmovem.x WBTEMP(a6),d0
1324         rts
1325 frc0123:
1326         tst.b   d0
1327         beq.b   frc0_dst
1328         cmpi.b  #1,d0
1329         beq.b   frc1_dst 
1330         cmpi.b  #2,d0
1331         beq.b   frc2_dst 
1332 frc3_dst:
1333         move.l  WBTEMP_EX(a6),USER_FP3(a6)
1334         move.l  WBTEMP_HI(a6),USER_FP3+4(a6)
1335         move.l  WBTEMP_LO(a6),USER_FP3+8(a6)
1336         rts
1337 frc2_dst:
1338         move.l  WBTEMP_EX(a6),USER_FP2(a6)
1339         move.l  WBTEMP_HI(a6),USER_FP2+4(a6)
1340         move.l  WBTEMP_LO(a6),USER_FP2+8(a6)
1341         rts
1342 frc1_dst:
1343         move.l  WBTEMP_EX(a6),USER_FP1(a6)
1344         move.l  WBTEMP_HI(a6),USER_FP1+4(a6)
1345         move.l  WBTEMP_LO(a6),USER_FP1+8(a6)
1346         rts
1347 frc0_dst:
1348         move.l  WBTEMP_EX(a6),USER_FP0(a6)
1349         move.l  WBTEMP_HI(a6),USER_FP0+4(a6)
1350         move.l  WBTEMP_LO(a6),USER_FP0+8(a6)
1351         rts
1354 * Write etemp to fpn.
1355 * A check is made on enabled and signalled snan exceptions,
1356 * and the destination is not overwritten if this condition exists.
1357 * This code is designed to make fmoveins of unsupported data types
1358 * faster.
1360 wr_etemp:
1361         btst.b  #snan_bit,FPSR_EXCEPT(a6)       ;if snan is set, and
1362         beq.b   fmoveinc                ;enabled, force restore
1363         btst.b  #snan_bit,FPCR_ENABLE(a6) ;and don't overwrite
1364         beq.b   fmoveinc                ;the dest
1365         move.l  ETEMP_EX(a6),FPTEMP_EX(a6)      ;set up fptemp sign for 
1366 *                                               ;snan handler
1367         tst.b   ETEMP(a6)               ;check for negative
1368         blt.b   snan_neg
1369         rts
1370 snan_neg:
1371         or.l    #neg_bit,USER_FPSR(a6)  ;snan is negative; set N
1372         rts
1373 fmoveinc:
1374         clr.w   NMNEXC(a6)
1375         bclr.b  #E1,E_BYTE(a6)
1376         move.b  STAG(a6),d0             ;check if stag is inf
1377         andi.b  #$e0,d0
1378         cmpi.b  #$40,d0
1379         bne.b   fminc_cnan
1380         or.l    #inf_mask,USER_FPSR(a6) ;if inf, nothing yet has set I
1381         tst.w   LOCAL_EX(a0)            ;check sign
1382         bge.b   fminc_con
1383         or.l    #neg_mask,USER_FPSR(a6)
1384         bra     fminc_con
1385 fminc_cnan:
1386         cmpi.b  #$60,d0                 ;check if stag is NaN
1387         bne.b   fminc_czero
1388         or.l    #nan_mask,USER_FPSR(a6) ;if nan, nothing yet has set NaN
1389         move.l  ETEMP_EX(a6),FPTEMP_EX(a6)      ;set up fptemp sign for 
1390 *                                               ;snan handler
1391         tst.w   LOCAL_EX(a0)            ;check sign
1392         bge.b   fminc_con
1393         or.l    #neg_mask,USER_FPSR(a6)
1394         bra     fminc_con
1395 fminc_czero:
1396         cmpi.b  #$20,d0                 ;check if zero
1397         bne.b   fminc_con
1398         or.l    #z_mask,USER_FPSR(a6)   ;if zero, set Z
1399         tst.w   LOCAL_EX(a0)            ;check sign
1400         bge.b   fminc_con
1401         or.l    #neg_mask,USER_FPSR(a6)
1402 fminc_con:
1403         bfextu  CMDREG1B(a6){6:3},d0    ;extract fp destination register
1404         cmpi.b  #3,d0
1405         ble.b   fp0123                  ;check if dest is fp0-fp3
1406         move.l  #7,d1
1407         sub.l   d0,d1
1408         clr.l   d0
1409         bset.l  d1,d0
1410         fmovem.x ETEMP(a6),d0
1411         rts
1413 fp0123:
1414         tst.b   d0
1415         beq.b   fp0_dst
1416         cmpi.b  #1,d0
1417         beq.b   fp1_dst 
1418         cmpi.b  #2,d0
1419         beq.b   fp2_dst 
1420 fp3_dst:
1421         move.l  ETEMP_EX(a6),USER_FP3(a6)
1422         move.l  ETEMP_HI(a6),USER_FP3+4(a6)
1423         move.l  ETEMP_LO(a6),USER_FP3+8(a6)
1424         rts
1425 fp2_dst:
1426         move.l  ETEMP_EX(a6),USER_FP2(a6)
1427         move.l  ETEMP_HI(a6),USER_FP2+4(a6)
1428         move.l  ETEMP_LO(a6),USER_FP2+8(a6)
1429         rts
1430 fp1_dst:
1431         move.l  ETEMP_EX(a6),USER_FP1(a6)
1432         move.l  ETEMP_HI(a6),USER_FP1+4(a6)
1433         move.l  ETEMP_LO(a6),USER_FP1+8(a6)
1434         rts
1435 fp0_dst:
1436         move.l  ETEMP_EX(a6),USER_FP0(a6)
1437         move.l  ETEMP_HI(a6),USER_FP0+4(a6)
1438         move.l  ETEMP_LO(a6),USER_FP0+8(a6)
1439         rts
1441 opclass3:
1442         st.b    CU_ONLY(a6)
1443         move.w  CMDREG1B(a6),d0 ;check if packed moveout
1444         andi.w  #$0c00,d0       ;isolate last 2 bits of size field
1445         cmpi.w  #$0c00,d0       ;if size is 011 or 111, it is packed
1446         beq.w   pack_out        ;else it is norm or denorm
1447         bra.w   mv_out
1449         
1451 *       MOVE OUT
1454 mv_tbl:
1455         dc.l    li
1456         dc.l    sgp
1457         dc.l    xp
1458         dc.l    mvout_end       ;should never be taken
1459         dc.l    wi
1460         dc.l    dp
1461         dc.l    bi
1462         dc.l    mvout_end       ;should never be taken
1463 mv_out:
1464         bfextu  CMDREG1B(a6){3:3},d1    ;put source specifier in d1
1465         lea.l   mv_tbl,a0
1466         move.l  (a0,d1*4),a0
1467         jmp     (a0)
1470 * This exit is for move-out to memory.  The aunfl bit is 
1471 * set if the result is inex and unfl is signalled.
1473 mvout_end:
1474         btst.b  #inex2_bit,FPSR_EXCEPT(a6)
1475         beq.b   no_aufl
1476         btst.b  #unfl_bit,FPSR_EXCEPT(a6)
1477         beq.b   no_aufl
1478         bset.b  #aunfl_bit,FPSR_AEXCEPT(a6)
1479 no_aufl:
1480         clr.w   NMNEXC(a6)
1481         bclr.b  #E1,E_BYTE(a6)
1482         fmove.l #0,FPSR                 ;clear any cc bits from res_func
1484 * Return ETEMP to extended format from internal extended format so
1485 * that gen_except will have a correctly signed value for ovfl/unfl
1486 * handlers.
1488         bfclr   ETEMP_SGN(a6){0:8}
1489         beq.b   mvout_con
1490         bset.b  #sign_bit,ETEMP_EX(a6)
1491 mvout_con:
1492         rts
1494 * This exit is for move-out to int register.  The aunfl bit is 
1495 * not set in any case for this move.
1497 mvouti_end:
1498         clr.w   NMNEXC(a6)
1499         bclr.b  #E1,E_BYTE(a6)
1500         fmove.l #0,FPSR                 ;clear any cc bits from res_func
1502 * Return ETEMP to extended format from internal extended format so
1503 * that gen_except will have a correctly signed value for ovfl/unfl
1504 * handlers.
1506         bfclr   ETEMP_SGN(a6){0:8}
1507         beq.b   mvouti_con
1508         bset.b  #sign_bit,ETEMP_EX(a6)
1509 mvouti_con:
1510         rts
1512 * li is used to handle a long integer source specifier
1516         moveq.l #4,d0           ;set byte count
1518         btst.b  #7,STAG(a6)     ;check for extended denorm
1519         bne.w   int_dnrm        ;if so, branch
1521         fmovem.x ETEMP(a6),fp0
1522         fcmp.d  #:41dfffffffc00000,fp0
1523 * 41dfffffffc00000 in dbl prec = 401d0000fffffffe00000000 in ext prec
1524         fbge.w  lo_plrg 
1525         fcmp.d  #:c1e0000000000000,fp0
1526 * c1e0000000000000 in dbl prec = c01e00008000000000000000 in ext prec
1527         fble.w  lo_nlrg
1529 * at this point, the answer is between the largest pos and neg values
1531         move.l  USER_FPCR(a6),d1        ;use user's rounding mode
1532         andi.l  #$30,d1
1533         fmove.l d1,fpcr
1534         fmove.l fp0,L_SCR1(a6)  ;let the 040 perform conversion
1535         fmove.l fpsr,d1
1536         or.l    d1,USER_FPSR(a6)        ;capture inex2/ainex if set
1537         bra.w   int_wrt
1540 lo_plrg:
1541         move.l  #$7fffffff,L_SCR1(a6)   ;answer is largest positive int
1542         fbeq.w  int_wrt                 ;exact answer
1543         fcmp.d  #:41dfffffffe00000,fp0
1544 * 41dfffffffe00000 in dbl prec = 401d0000ffffffff00000000 in ext prec
1545         fbge.w  int_operr               ;set operr
1546         bra.w   int_inx                 ;set inexact
1548 lo_nlrg:
1549         move.l  #$80000000,L_SCR1(a6)
1550         fbeq.w  int_wrt                 ;exact answer
1551         fcmp.d  #:c1e0000000100000,fp0
1552 * c1e0000000100000 in dbl prec = c01e00008000000080000000 in ext prec
1553         fblt.w  int_operr               ;set operr
1554         bra.w   int_inx                 ;set inexact
1557 * wi is used to handle a word integer source specifier
1561         moveq.l #2,d0           ;set byte count
1563         btst.b  #7,STAG(a6)     ;check for extended denorm
1564         bne.w   int_dnrm        ;branch if so
1566         fmovem.x ETEMP(a6),fp0
1567         fcmp.s  #:46fffe00,fp0
1568 * 46fffe00 in sgl prec = 400d0000fffe000000000000 in ext prec
1569         fbge.w  wo_plrg 
1570         fcmp.s  #:c7000000,fp0
1571 * c7000000 in sgl prec = c00e00008000000000000000 in ext prec
1572         fble.w  wo_nlrg
1575 * at this point, the answer is between the largest pos and neg values
1577         move.l  USER_FPCR(a6),d1        ;use user's rounding mode
1578         andi.l  #$30,d1
1579         fmove.l d1,fpcr
1580         fmove.w fp0,L_SCR1(a6)  ;let the 040 perform conversion
1581         fmove.l fpsr,d1
1582         or.l    d1,USER_FPSR(a6)        ;capture inex2/ainex if set
1583         bra.w   int_wrt
1585 wo_plrg:
1586         move.w  #$7fff,L_SCR1(a6)       ;answer is largest positive int
1587         fbeq.w  int_wrt                 ;exact answer
1588         fcmp.s  #:46ffff00,fp0
1589 * 46ffff00 in sgl prec = 400d0000ffff000000000000 in ext prec
1590         fbge.w  int_operr               ;set operr
1591         bra.w   int_inx                 ;set inexact
1593 wo_nlrg:
1594         move.w  #$8000,L_SCR1(a6)
1595         fbeq.w  int_wrt                 ;exact answer
1596         fcmp.s  #:c7000080,fp0
1597 * c7000080 in sgl prec = c00e00008000800000000000 in ext prec
1598         fblt.w  int_operr               ;set operr
1599         bra.w   int_inx                 ;set inexact
1602 * bi is used to handle a byte integer source specifier
1606         moveq.l #1,d0           ;set byte count
1608         btst.b  #7,STAG(a6)     ;check for extended denorm
1609         bne.w   int_dnrm        ;branch if so
1611         fmovem.x ETEMP(a6),fp0
1612         fcmp.s  #:42fe0000,fp0
1613 * 42fe0000 in sgl prec = 40050000fe00000000000000 in ext prec
1614         fbge.w  by_plrg 
1615         fcmp.s  #:c3000000,fp0
1616 * c3000000 in sgl prec = c00600008000000000000000 in ext prec
1617         fble.w  by_nlrg
1620 * at this point, the answer is between the largest pos and neg values
1622         move.l  USER_FPCR(a6),d1        ;use user's rounding mode
1623         andi.l  #$30,d1
1624         fmove.l d1,fpcr
1625         fmove.b fp0,L_SCR1(a6)  ;let the 040 perform conversion
1626         fmove.l fpsr,d1
1627         or.l    d1,USER_FPSR(a6)        ;capture inex2/ainex if set
1628         bra.w   int_wrt
1630 by_plrg:
1631         move.b  #$7f,L_SCR1(a6)         ;answer is largest positive int
1632         fbeq.w  int_wrt                 ;exact answer
1633         fcmp.s  #:42ff0000,fp0
1634 * 42ff0000 in sgl prec = 40050000ff00000000000000 in ext prec
1635         fbge.w  int_operr               ;set operr
1636         bra.w   int_inx                 ;set inexact
1638 by_nlrg:
1639         move.b  #$80,L_SCR1(a6)
1640         fbeq.w  int_wrt                 ;exact answer
1641         fcmp.s  #:c3008000,fp0
1642 * c3008000 in sgl prec = c00600008080000000000000 in ext prec
1643         fblt.w  int_operr               ;set operr
1644         bra.w   int_inx                 ;set inexact
1647 * Common integer routines
1649 * int_drnrm---account for possible nonzero result for round up with positive
1650 * operand and round down for negative answer.  In the first case (result = 1)
1651 * byte-width (store in d0) of result must be honored.  In the second case,
1652 * -1 in L_SCR1(a6) will cover all contingencies (FMOVE.B/W/L out).
1654 int_dnrm:
1655         clr.l   L_SCR1(a6)      ; initialize result to 0
1656         bfextu  FPCR_MODE(a6){2:2},d1   ; d1 is the rounding mode
1657         cmp.b   #2,d1           
1658         bmi.b   int_inx         ; if RN or RZ, done
1659         bne.b   int_rp          ; if RP, continue below
1660         tst.w   ETEMP(a6)       ; RM: store -1 in L_SCR1 if src is negative
1661         bpl.b   int_inx         ; otherwise result is 0
1662         move.l  #-1,L_SCR1(a6)
1663         bra.b   int_inx
1664 int_rp:
1665         tst.w   ETEMP(a6)       ; RP: store +1 of proper width in L_SCR1 if
1666 *                               ; source is greater than 0
1667         bmi.b   int_inx         ; otherwise, result is 0
1668         lea     L_SCR1(a6),a1   ; a1 is address of L_SCR1
1669         adda.l  d0,a1           ; offset by destination width -1
1670         suba.l  #1,a1           
1671         bset.b  #0,(a1)         ; set low bit at a1 address
1672 int_inx:
1673         ori.l   #inx2a_mask,USER_FPSR(a6)
1674         bra.b   int_wrt
1675 int_operr:
1676         fmovem.x fp0,FPTEMP(a6) ;FPTEMP must contain the extended
1677 *                               ;precision source that needs to be
1678 *                               ;converted to integer this is required
1679 *                               ;if the operr exception is enabled.
1680 *                               ;set operr/aiop (no inex2 on int ovfl)
1682         ori.l   #opaop_mask,USER_FPSR(a6)
1683 *                               ;fall through to perform int_wrt
1684 int_wrt: 
1685         move.l  EXC_EA(a6),a1   ;load destination address
1686         tst.l   a1              ;check to see if it is a dest register
1687         beq.b   wrt_dn          ;write data register 
1688         lea     L_SCR1(a6),a0   ;point to supervisor source address
1689         bsr.l   mem_write
1690         bra.w   mvouti_end
1692 wrt_dn:
1693         move.l  d0,-(sp)        ;d0 currently contains the size to write
1694         bsr.l   get_fline       ;get_fline returns Dn in d0
1695         andi.w  #$7,d0          ;isolate register
1696         move.l  (sp)+,d1        ;get size
1697         cmpi.l  #4,d1           ;most frequent case
1698         beq.b   sz_long
1699         cmpi.l  #2,d1
1700         bne.b   sz_con
1701         or.l    #8,d0           ;add 'word' size to register#
1702         bra.b   sz_con
1703 sz_long:
1704         or.l    #$10,d0         ;add 'long' size to register#
1705 sz_con:
1706         move.l  d0,d1           ;reg_dest expects size:reg in d1
1707         bsr.l   reg_dest        ;load proper data register
1708         bra.w   mvouti_end 
1710         lea     ETEMP(a6),a0
1711         bclr.b  #sign_bit,LOCAL_EX(a0)
1712         sne     LOCAL_SGN(a0)
1713         btst.b  #7,STAG(a6)     ;check for extended denorm
1714         bne.w   xdnrm
1715         clr.l   d0
1716         bra.b   do_fp           ;do normal case
1717 sgp:
1718         lea     ETEMP(a6),a0
1719         bclr.b  #sign_bit,LOCAL_EX(a0)
1720         sne     LOCAL_SGN(a0)
1721         btst.b  #7,STAG(a6)     ;check for extended denorm
1722         bne.w   sp_catas        ;branch if so
1723         move.w  LOCAL_EX(a0),d0
1724         lea     sp_bnds,a1
1725         cmp.w   (a1),d0
1726         blt.w   sp_under
1727         cmp.w   2(a1),d0
1728         bgt.w   sp_over
1729         move.l  #1,d0           ;set destination format to single
1730         bra.b   do_fp           ;do normal case
1732         lea     ETEMP(a6),a0
1733         bclr.b  #sign_bit,LOCAL_EX(a0)
1734         sne     LOCAL_SGN(a0)
1736         btst.b  #7,STAG(a6)     ;check for extended denorm
1737         bne.w   dp_catas        ;branch if so
1739         move.w  LOCAL_EX(a0),d0
1740         lea     dp_bnds,a1
1742         cmp.w   (a1),d0
1743         blt.w   dp_under
1744         cmp.w   2(a1),d0
1745         bgt.w   dp_over
1746         
1747         move.l  #2,d0           ;set destination format to double
1748 *                               ;fall through to do_fp
1750 do_fp:
1751         bfextu  FPCR_MODE(a6){2:2},d1   ;rnd mode in d1
1752         swap    d0                      ;rnd prec in upper word
1753         add.l   d0,d1                   ;d1 has PREC/MODE info
1754         
1755         clr.l   d0                      ;clear g,r,s 
1757         bsr.l   round                   ;round 
1759         move.l  a0,a1
1760         move.l  EXC_EA(a6),a0
1762         bfextu  CMDREG1B(a6){3:3},d1    ;extract destination format
1763 *                                       ;at this point only the dest
1764 *                                       ;formats sgl, dbl, ext are
1765 *                                       ;possible
1766         cmp.b   #2,d1
1767         bgt.b   ddbl                    ;double=5, extended=2, single=1
1768         bne.b   dsgl
1769 *                                       ;fall through to dext
1770 dext:
1771         bsr.l   dest_ext
1772         bra.w   mvout_end
1773 dsgl:
1774         bsr.l   dest_sgl
1775         bra.w   mvout_end
1776 ddbl:
1777         bsr.l   dest_dbl
1778         bra.w   mvout_end
1781 * Handle possible denorm or catastrophic underflow cases here
1783 xdnrm:
1784         bsr.w   set_xop         ;initialize WBTEMP
1785         bset.b  #wbtemp15_bit,WB_BYTE(a6) ;set wbtemp15
1787         move.l  a0,a1
1788         move.l  EXC_EA(a6),a0   ;a0 has the destination pointer
1789         bsr.l   dest_ext        ;store to memory
1790         bset.b  #unfl_bit,FPSR_EXCEPT(a6)
1791         bra.w   mvout_end
1792         
1793 sp_under:
1794         bset.b  #etemp15_bit,STAG(a6)
1796         cmp.w   4(a1),d0
1797         blt.b   sp_catas        ;catastrophic underflow case    
1799         move.l  #1,d0           ;load in round precision
1800         move.l  #sgl_thresh,d1  ;load in single denorm threshold
1801         bsr.l   dpspdnrm        ;expects d1 to have the proper
1802 *                               ;denorm threshold
1803         bsr.l   dest_sgl        ;stores value to destination
1804         bset.b  #unfl_bit,FPSR_EXCEPT(a6)
1805         bra.w   mvout_end       ;exit
1807 dp_under:
1808         bset.b  #etemp15_bit,STAG(a6)
1810         cmp.w   4(a1),d0
1811         blt.b   dp_catas        ;catastrophic underflow case
1812                 
1813         move.l  #dbl_thresh,d1  ;load in double precision threshold
1814         move.l  #2,d0           
1815         bsr.l   dpspdnrm        ;expects d1 to have proper
1816 *                               ;denorm threshold
1817 *                               ;expects d0 to have round precision
1818         bsr.l   dest_dbl        ;store value to destination
1819         bset.b  #unfl_bit,FPSR_EXCEPT(a6)
1820         bra.w   mvout_end       ;exit
1823 * Handle catastrophic underflow cases here
1825 sp_catas:
1826 * Temp fix for z bit set in unf_sub
1827         move.l  USER_FPSR(a6),-(a7)
1829         move.l  #1,d0           ;set round precision to sgl
1831         bsr.l   unf_sub         ;a0 points to result
1833         move.l  (a7)+,USER_FPSR(a6)
1835         move.l  #1,d0
1836         sub.w   d0,LOCAL_EX(a0) ;account for difference between
1837 *                               ;denorm/norm bias
1839         move.l  a0,a1           ;a1 has the operand input
1840         move.l  EXC_EA(a6),a0   ;a0 has the destination pointer
1841         
1842         bsr.l   dest_sgl        ;store the result
1843         ori.l   #unfinx_mask,USER_FPSR(a6)
1844         bra.w   mvout_end
1845         
1846 dp_catas:
1847 * Temp fix for z bit set in unf_sub
1848         move.l  USER_FPSR(a6),-(a7)
1850         move.l  #2,d0           ;set round precision to dbl
1851         bsr.l   unf_sub         ;a0 points to result
1853         move.l  (a7)+,USER_FPSR(a6)
1855         move.l  #1,d0
1856         sub.w   d0,LOCAL_EX(a0) ;account for difference between 
1857 *                               ;denorm/norm bias
1859         move.l  a0,a1           ;a1 has the operand input
1860         move.l  EXC_EA(a6),a0   ;a0 has the destination pointer
1861         
1862         bsr.l   dest_dbl        ;store the result
1863         ori.l   #unfinx_mask,USER_FPSR(a6)
1864         bra.w   mvout_end
1867 * Handle catastrophic overflow cases here
1869 sp_over:
1870 * Temp fix for z bit set in unf_sub
1871         move.l  USER_FPSR(a6),-(a7)
1873         move.l  #1,d0
1874         lea.l   FP_SCR1(a6),a0  ;use FP_SCR1 for creating result
1875         move.l  ETEMP_EX(a6),(a0)
1876         move.l  ETEMP_HI(a6),4(a0)
1877         move.l  ETEMP_LO(a6),8(a0)
1878         bsr.l   ovf_res
1880         move.l  (a7)+,USER_FPSR(a6)
1882         move.l  a0,a1
1883         move.l  EXC_EA(a6),a0
1884         bsr.l   dest_sgl
1885         or.l    #ovfinx_mask,USER_FPSR(a6)
1886         bra.w   mvout_end
1888 dp_over:
1889 * Temp fix for z bit set in ovf_res
1890         move.l  USER_FPSR(a6),-(a7)
1892         move.l  #2,d0
1893         lea.l   FP_SCR1(a6),a0  ;use FP_SCR1 for creating result
1894         move.l  ETEMP_EX(a6),(a0)
1895         move.l  ETEMP_HI(a6),4(a0)
1896         move.l  ETEMP_LO(a6),8(a0)
1897         bsr.l   ovf_res
1899         move.l  (a7)+,USER_FPSR(a6)
1901         move.l  a0,a1
1902         move.l  EXC_EA(a6),a0
1903         bsr.l   dest_dbl
1904         or.l    #ovfinx_mask,USER_FPSR(a6)
1905         bra.w   mvout_end
1908 *       DPSPDNRM
1910 * This subroutine takes an extended normalized number and denormalizes
1911 * it to the given round precision. This subroutine also decrements
1912 * the input operand's exponent by 1 to account for the fact that
1913 * dest_sgl or dest_dbl expects a normalized number's bias.
1915 * Input: a0  points to a normalized number in internal extended format
1916 *        d0  is the round precision (=1 for sgl; =2 for dbl)
1917 *        d1  is the single precision or double precision
1918 *            denorm threshold
1920 * Output: (In the format for dest_sgl or dest_dbl)
1921 *        a0   points to the destination
1922 *        a1   points to the operand
1924 * Exceptions: Reports inexact 2 exception by setting USER_FPSR bits
1926 dpspdnrm:
1927         move.l  d0,-(a7)        ;save round precision
1928         clr.l   d0              ;clear initial g,r,s
1929         bsr.l   dnrm_lp         ;careful with d0, it's needed by round
1931         bfextu  FPCR_MODE(a6){2:2},d1 ;get rounding mode
1932         swap    d1
1933         move.w  2(a7),d1        ;set rounding precision 
1934         swap    d1              ;at this point d1 has PREC/MODE info
1935         bsr.l   round           ;round result, sets the inex bit in
1936 *                               ;USER_FPSR if needed
1938         move.w  #1,d0
1939         sub.w   d0,LOCAL_EX(a0) ;account for difference in denorm
1940 *                               ;vs norm bias
1942         move.l  a0,a1           ;a1 has the operand input
1943         move.l  EXC_EA(a6),a0   ;a0 has the destination pointer
1944         addq.l  #4,a7           ;pop stack
1945         rts
1947 * SET_XOP initialized WBTEMP with the value pointed to by a0
1948 * input: a0 points to input operand in the internal extended format
1950 set_xop:
1951         move.l  LOCAL_EX(a0),WBTEMP_EX(a6)
1952         move.l  LOCAL_HI(a0),WBTEMP_HI(a6)
1953         move.l  LOCAL_LO(a0),WBTEMP_LO(a6)
1954         bfclr   WBTEMP_SGN(a6){0:8}
1955         beq.b   sxop
1956         bset.b  #sign_bit,WBTEMP_EX(a6)
1957 sxop:
1958         bfclr   STAG(a6){5:4}   ;clear wbtm66,wbtm1,wbtm0,sbit
1959         rts
1961 *       P_MOVE
1963 p_movet:
1964         dc.l    p_move
1965         dc.l    p_movez
1966         dc.l    p_movei
1967         dc.l    p_moven
1968         dc.l    p_move
1969 p_regd:
1970         dc.l    p_dyd0
1971         dc.l    p_dyd1
1972         dc.l    p_dyd2
1973         dc.l    p_dyd3
1974         dc.l    p_dyd4
1975         dc.l    p_dyd5
1976         dc.l    p_dyd6
1977         dc.l    p_dyd7
1979 pack_out:
1980         lea.l   p_movet,a0      ;load jmp table address
1981         move.w  STAG(a6),d0     ;get source tag
1982         bfextu  d0{16:3},d0     ;isolate source bits
1983         move.l  (a0,d0.w*4),a0  ;load a0 with routine label for tag
1984         jmp     (a0)            ;go to the routine
1986 p_write:
1987         move.l  #$0c,d0         ;get byte count
1988         move.l  EXC_EA(a6),a1   ;get the destination address
1989         bsr     mem_write       ;write the user's destination
1990         clr.b   CU_SAVEPC(a6) ;set the cu save pc to all 0's
1993 * Also note that the dtag must be set to norm here - this is because 
1994 * the 040 uses the dtag to execute the correct microcode.
1996         bfclr    DTAG(a6){0:3}  ;set dtag to norm
1998         rts
2000 * Notes on handling of special case (zero, inf, and nan) inputs:
2001 *       1. Operr is not signalled if the k-factor is greater than 18.
2002 *       2. Per the manual, status bits are not set.
2005 p_move:
2006         move.w  CMDREG1B(a6),d0
2007         btst.l  #kfact_bit,d0   ;test for dynamic k-factor
2008         beq.b   statick         ;if clear, k-factor is static
2009 dynamick:
2010         bfextu  d0{25:3},d0     ;isolate register for dynamic k-factor
2011         lea     p_regd,a0
2012         move.l  (a0,d0*4),a0
2013         jmp     (a0)
2014 statick:
2015         andi.w  #$007f,d0       ;get k-factor
2016         bfexts  d0{25:7},d0     ;sign extend d0 for bindec
2017         lea.l   ETEMP(a6),a0    ;a0 will point to the packed decimal
2018         bsr.l   bindec          ;perform the convert; data at a6
2019         lea.l   FP_SCR1(a6),a0  ;load a0 with result address
2020         bra.l   p_write
2021 p_movez:
2022         lea.l   ETEMP(a6),a0    ;a0 will point to the packed decimal
2023         clr.w   2(a0)           ;clear lower word of exp
2024         clr.l   4(a0)           ;load second lword of ZERO
2025         clr.l   8(a0)           ;load third lword of ZERO
2026         bra.w   p_write         ;go write results
2027 p_movei:
2028         fmove.l #0,FPSR         ;clear aiop
2029         lea.l   ETEMP(a6),a0    ;a0 will point to the packed decimal
2030         clr.w   2(a0)           ;clear lower word of exp
2031         bra.w   p_write         ;go write the result
2032 p_moven:
2033         lea.l   ETEMP(a6),a0    ;a0 will point to the packed decimal
2034         clr.w   2(a0)           ;clear lower word of exp
2035         bra.w   p_write         ;go write the result
2038 * Routines to read the dynamic k-factor from Dn.
2040 p_dyd0:
2041         move.l  USER_D0(a6),d0
2042         bra.b   statick
2043 p_dyd1:
2044         move.l  USER_D1(a6),d0
2045         bra.b   statick
2046 p_dyd2:
2047         move.l  d2,d0
2048         bra.b   statick
2049 p_dyd3:
2050         move.l  d3,d0
2051         bra.b   statick
2052 p_dyd4:
2053         move.l  d4,d0
2054         bra.b   statick
2055 p_dyd5:
2056         move.l  d5,d0
2057         bra.b   statick
2058 p_dyd6:
2059         move.l  d6,d0
2060         bra.w   statick
2061 p_dyd7:
2062         move.l  d7,d0
2063         bra.w   statick
2065         end