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