source: rtems/c/src/lib/libcpu/m68k/m68040/fpsp/res_func.S @ 9b4422a2

4.115
Last change on this file since 9b4422a2 was 9b4422a2, checked in by Joel Sherrill <joel.sherrill@…>, on 05/03/12 at 15:09:24

Remove All CVS Id Strings Possible Using a Script

Script does what is expected and tries to do it as
smartly as possible.

+ remove occurrences of two blank comment lines

next to each other after Id string line removed.

+ remove entire comment blocks which only exited to

contain CVS Ids

+ If the processing left a blank line at the top of

a file, it was removed.

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