OSDN Git Service

Daily bump.
[pf3gnuchains/gcc-fork.git] / gcc / config / arm / ieee754-df.S
1 /* ieee754-df.S double-precision floating point support for ARM
2
3    Copyright (C) 2003, 2004, 2005, 2007, 2008  Free Software Foundation, Inc.
4    Contributed by Nicolas Pitre (nico@cam.org)
5
6    This file is free software; you can redistribute it and/or modify it
7    under the terms of the GNU General Public License as published by the
8    Free Software Foundation; either version 2, or (at your option) any
9    later version.
10
11    In addition to the permissions in the GNU General Public License, the
12    Free Software Foundation gives you unlimited permission to link the
13    compiled version of this file into combinations with other programs,
14    and to distribute those combinations without any restriction coming
15    from the use of this file.  (The General Public License restrictions
16    do apply in other respects; for example, they cover modification of
17    the file, and distribution when not linked into a combine
18    executable.)
19
20    This file is distributed in the hope that it will be useful, but
21    WITHOUT ANY WARRANTY; without even the implied warranty of
22    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
23    General Public License for more details.
24
25    You should have received a copy of the GNU General Public License
26    along with this program; see the file COPYING.  If not, write to
27    the Free Software Foundation, 51 Franklin Street, Fifth Floor,
28    Boston, MA 02110-1301, USA.  */
29
30 /*
31  * Notes: 
32  * 
33  * The goal of this code is to be as fast as possible.  This is
34  * not meant to be easy to understand for the casual reader.
35  * For slightly simpler code please see the single precision version
36  * of this file.
37  * 
38  * Only the default rounding mode is intended for best performances.
39  * Exceptions aren't supported yet, but that can be added quite easily
40  * if necessary without impacting performances.
41  */
42
43
44 @ For FPA, float words are always big-endian.
45 @ For VFP, floats words follow the memory system mode.
46 #if defined(__VFP_FP__) && !defined(__ARMEB__)
47 #define xl r0
48 #define xh r1
49 #define yl r2
50 #define yh r3
51 #else
52 #define xh r0
53 #define xl r1
54 #define yh r2
55 #define yl r3
56 #endif
57
58
59 #ifdef L_arm_negdf2
60
61 ARM_FUNC_START negdf2
62 ARM_FUNC_ALIAS aeabi_dneg negdf2
63
64         @ flip sign bit
65         eor     xh, xh, #0x80000000
66         RET
67
68         FUNC_END aeabi_dneg
69         FUNC_END negdf2
70
71 #endif
72
73 #ifdef L_arm_addsubdf3
74
75 ARM_FUNC_START aeabi_drsub
76
77         eor     xh, xh, #0x80000000     @ flip sign bit of first arg
78         b       1f      
79
80 ARM_FUNC_START subdf3
81 ARM_FUNC_ALIAS aeabi_dsub subdf3
82
83         eor     yh, yh, #0x80000000     @ flip sign bit of second arg
84 #if defined(__INTERWORKING_STUBS__)
85         b       1f                      @ Skip Thumb-code prologue
86 #endif
87
88 ARM_FUNC_START adddf3
89 ARM_FUNC_ALIAS aeabi_dadd adddf3
90
91 1:      do_push {r4, r5, lr}
92
93         @ Look for zeroes, equal values, INF, or NAN.
94         shift1  lsl, r4, xh, #1
95         shift1  lsl, r5, yh, #1
96         teq     r4, r5
97         do_it   eq
98         teqeq   xl, yl
99         do_it   ne, ttt
100         COND(orr,s,ne)  ip, r4, xl
101         COND(orr,s,ne)  ip, r5, yl
102         COND(mvn,s,ne)  ip, r4, asr #21
103         COND(mvn,s,ne)  ip, r5, asr #21
104         beq     LSYM(Lad_s)
105
106         @ Compute exponent difference.  Make largest exponent in r4,
107         @ corresponding arg in xh-xl, and positive exponent difference in r5.
108         shift1  lsr, r4, r4, #21
109         rsbs    r5, r4, r5, lsr #21
110         do_it   lt
111         rsblt   r5, r5, #0
112         ble     1f
113         add     r4, r4, r5
114         eor     yl, xl, yl
115         eor     yh, xh, yh
116         eor     xl, yl, xl
117         eor     xh, yh, xh
118         eor     yl, xl, yl
119         eor     yh, xh, yh
120 1:
121         @ If exponent difference is too large, return largest argument
122         @ already in xh-xl.  We need up to 54 bit to handle proper rounding
123         @ of 0x1p54 - 1.1.
124         cmp     r5, #54
125         do_it   hi
126         RETLDM  "r4, r5" hi
127
128         @ Convert mantissa to signed integer.
129         tst     xh, #0x80000000
130         mov     xh, xh, lsl #12
131         mov     ip, #0x00100000
132         orr     xh, ip, xh, lsr #12
133         beq     1f
134 #if defined(__thumb2__)
135         negs    xl, xl
136         sbc     xh, xh, xh, lsl #1
137 #else
138         rsbs    xl, xl, #0
139         rsc     xh, xh, #0
140 #endif
141 1:
142         tst     yh, #0x80000000
143         mov     yh, yh, lsl #12
144         orr     yh, ip, yh, lsr #12
145         beq     1f
146 #if defined(__thumb2__)
147         negs    yl, yl
148         sbc     yh, yh, yh, lsl #1
149 #else
150         rsbs    yl, yl, #0
151         rsc     yh, yh, #0
152 #endif
153 1:
154         @ If exponent == difference, one or both args were denormalized.
155         @ Since this is not common case, rescale them off line.
156         teq     r4, r5
157         beq     LSYM(Lad_d)
158 LSYM(Lad_x):
159
160         @ Compensate for the exponent overlapping the mantissa MSB added later
161         sub     r4, r4, #1
162
163         @ Shift yh-yl right per r5, add to xh-xl, keep leftover bits into ip.
164         rsbs    lr, r5, #32
165         blt     1f
166         shift1  lsl, ip, yl, lr
167         shiftop adds xl xl yl lsr r5 yl
168         adc     xh, xh, #0
169         shiftop adds xl xl yh lsl lr yl
170         shiftop adcs xh xh yh asr r5 yh
171         b       2f
172 1:      sub     r5, r5, #32
173         add     lr, lr, #32
174         cmp     yl, #1
175         shift1  lsl,ip, yh, lr
176         do_it   cs
177         orrcs   ip, ip, #2              @ 2 not 1, to allow lsr #1 later
178         shiftop adds xl xl yh asr r5 yh
179         adcs    xh, xh, yh, asr #31
180 2:
181         @ We now have a result in xh-xl-ip.
182         @ Keep absolute value in xh-xl-ip, sign in r5 (the n bit was set above)
183         and     r5, xh, #0x80000000
184         bpl     LSYM(Lad_p)
185 #if defined(__thumb2__)
186         mov     lr, #0
187         negs    ip, ip
188         sbcs    xl, lr, xl
189         sbc     xh, lr, xh
190 #else
191         rsbs    ip, ip, #0
192         rscs    xl, xl, #0
193         rsc     xh, xh, #0
194 #endif
195
196         @ Determine how to normalize the result.
197 LSYM(Lad_p):
198         cmp     xh, #0x00100000
199         bcc     LSYM(Lad_a)
200         cmp     xh, #0x00200000
201         bcc     LSYM(Lad_e)
202
203         @ Result needs to be shifted right.
204         movs    xh, xh, lsr #1
205         movs    xl, xl, rrx
206         mov     ip, ip, rrx
207         add     r4, r4, #1
208
209         @ Make sure we did not bust our exponent.
210         mov     r2, r4, lsl #21
211         cmn     r2, #(2 << 21)
212         bcs     LSYM(Lad_o)
213
214         @ Our result is now properly aligned into xh-xl, remaining bits in ip.
215         @ Round with MSB of ip. If halfway between two numbers, round towards
216         @ LSB of xl = 0.
217         @ Pack final result together.
218 LSYM(Lad_e):
219         cmp     ip, #0x80000000
220         do_it   eq
221         COND(mov,s,eq)  ip, xl, lsr #1
222         adcs    xl, xl, #0
223         adc     xh, xh, r4, lsl #20
224         orr     xh, xh, r5
225         RETLDM  "r4, r5"
226
227         @ Result must be shifted left and exponent adjusted.
228 LSYM(Lad_a):
229         movs    ip, ip, lsl #1
230         adcs    xl, xl, xl
231         adc     xh, xh, xh
232         tst     xh, #0x00100000
233         sub     r4, r4, #1
234         bne     LSYM(Lad_e)
235
236         @ No rounding necessary since ip will always be 0 at this point.
237 LSYM(Lad_l):
238
239 #if __ARM_ARCH__ < 5
240
241         teq     xh, #0
242         movne   r3, #20
243         moveq   r3, #52
244         moveq   xh, xl
245         moveq   xl, #0
246         mov     r2, xh
247         cmp     r2, #(1 << 16)
248         movhs   r2, r2, lsr #16
249         subhs   r3, r3, #16
250         cmp     r2, #(1 << 8)
251         movhs   r2, r2, lsr #8
252         subhs   r3, r3, #8
253         cmp     r2, #(1 << 4)
254         movhs   r2, r2, lsr #4
255         subhs   r3, r3, #4
256         cmp     r2, #(1 << 2)
257         subhs   r3, r3, #2
258         sublo   r3, r3, r2, lsr #1
259         sub     r3, r3, r2, lsr #3
260
261 #else
262
263         teq     xh, #0
264         do_it   eq, t
265         moveq   xh, xl
266         moveq   xl, #0
267         clz     r3, xh
268         do_it   eq
269         addeq   r3, r3, #32
270         sub     r3, r3, #11
271
272 #endif
273
274         @ determine how to shift the value.
275         subs    r2, r3, #32
276         bge     2f
277         adds    r2, r2, #12
278         ble     1f
279
280         @ shift value left 21 to 31 bits, or actually right 11 to 1 bits
281         @ since a register switch happened above.
282         add     ip, r2, #20
283         rsb     r2, r2, #12
284         shift1  lsl, xl, xh, ip
285         shift1  lsr, xh, xh, r2
286         b       3f
287
288         @ actually shift value left 1 to 20 bits, which might also represent
289         @ 32 to 52 bits if counting the register switch that happened earlier.
290 1:      add     r2, r2, #20
291 2:      do_it   le
292         rsble   ip, r2, #32
293         shift1  lsl, xh, xh, r2
294 #if defined(__thumb2__)
295         lsr     ip, xl, ip
296         itt     le
297         orrle   xh, xh, ip
298         lslle   xl, xl, r2
299 #else
300         orrle   xh, xh, xl, lsr ip
301         movle   xl, xl, lsl r2
302 #endif
303
304         @ adjust exponent accordingly.
305 3:      subs    r4, r4, r3
306         do_it   ge, tt
307         addge   xh, xh, r4, lsl #20
308         orrge   xh, xh, r5
309         RETLDM  "r4, r5" ge
310
311         @ Exponent too small, denormalize result.
312         @ Find out proper shift value.
313         mvn     r4, r4
314         subs    r4, r4, #31
315         bge     2f
316         adds    r4, r4, #12
317         bgt     1f
318
319         @ shift result right of 1 to 20 bits, sign is in r5.
320         add     r4, r4, #20
321         rsb     r2, r4, #32
322         shift1  lsr, xl, xl, r4
323         shiftop orr xl xl xh lsl r2 yh
324         shiftop orr xh r5 xh lsr r4 yh
325         RETLDM  "r4, r5"
326
327         @ shift result right of 21 to 31 bits, or left 11 to 1 bits after
328         @ a register switch from xh to xl.
329 1:      rsb     r4, r4, #12
330         rsb     r2, r4, #32
331         shift1  lsr, xl, xl, r2
332         shiftop orr xl xl xh lsl r4 yh
333         mov     xh, r5
334         RETLDM  "r4, r5"
335
336         @ Shift value right of 32 to 64 bits, or 0 to 32 bits after a switch
337         @ from xh to xl.
338 2:      shift1  lsr, xl, xh, r4
339         mov     xh, r5
340         RETLDM  "r4, r5"
341
342         @ Adjust exponents for denormalized arguments.
343         @ Note that r4 must not remain equal to 0.
344 LSYM(Lad_d):
345         teq     r4, #0
346         eor     yh, yh, #0x00100000
347         do_it   eq, te
348         eoreq   xh, xh, #0x00100000
349         addeq   r4, r4, #1
350         subne   r5, r5, #1
351         b       LSYM(Lad_x)
352
353
354 LSYM(Lad_s):
355         mvns    ip, r4, asr #21
356         do_it   ne
357         COND(mvn,s,ne)  ip, r5, asr #21
358         beq     LSYM(Lad_i)
359
360         teq     r4, r5
361         do_it   eq
362         teqeq   xl, yl
363         beq     1f
364
365         @ Result is x + 0.0 = x or 0.0 + y = y.
366         orrs    ip, r4, xl
367         do_it   eq, t
368         moveq   xh, yh
369         moveq   xl, yl
370         RETLDM  "r4, r5"
371
372 1:      teq     xh, yh
373
374         @ Result is x - x = 0.
375         do_it   ne, tt
376         movne   xh, #0
377         movne   xl, #0
378         RETLDM  "r4, r5" ne
379
380         @ Result is x + x = 2x.
381         movs    ip, r4, lsr #21
382         bne     2f
383         movs    xl, xl, lsl #1
384         adcs    xh, xh, xh
385         do_it   cs
386         orrcs   xh, xh, #0x80000000
387         RETLDM  "r4, r5"
388 2:      adds    r4, r4, #(2 << 21)
389         do_it   cc, t
390         addcc   xh, xh, #(1 << 20)
391         RETLDM  "r4, r5" cc
392         and     r5, xh, #0x80000000
393
394         @ Overflow: return INF.
395 LSYM(Lad_o):
396         orr     xh, r5, #0x7f000000
397         orr     xh, xh, #0x00f00000
398         mov     xl, #0
399         RETLDM  "r4, r5"
400
401         @ At least one of x or y is INF/NAN.
402         @   if xh-xl != INF/NAN: return yh-yl (which is INF/NAN)
403         @   if yh-yl != INF/NAN: return xh-xl (which is INF/NAN)
404         @   if either is NAN: return NAN
405         @   if opposite sign: return NAN
406         @   otherwise return xh-xl (which is INF or -INF)
407 LSYM(Lad_i):
408         mvns    ip, r4, asr #21
409         do_it   ne, te
410         movne   xh, yh
411         movne   xl, yl
412         COND(mvn,s,eq)  ip, r5, asr #21
413         do_it   ne, t
414         movne   yh, xh
415         movne   yl, xl
416         orrs    r4, xl, xh, lsl #12
417         do_it   eq, te
418         COND(orr,s,eq)  r5, yl, yh, lsl #12
419         teqeq   xh, yh
420         orrne   xh, xh, #0x00080000     @ quiet NAN
421         RETLDM  "r4, r5"
422
423         FUNC_END aeabi_dsub
424         FUNC_END subdf3
425         FUNC_END aeabi_dadd
426         FUNC_END adddf3
427
428 ARM_FUNC_START floatunsidf
429 ARM_FUNC_ALIAS aeabi_ui2d floatunsidf
430
431         teq     r0, #0
432         do_it   eq, t
433         moveq   r1, #0
434         RETc(eq)
435         do_push {r4, r5, lr}
436         mov     r4, #0x400              @ initial exponent
437         add     r4, r4, #(52-1 - 1)
438         mov     r5, #0                  @ sign bit is 0
439         .ifnc   xl, r0
440         mov     xl, r0
441         .endif
442         mov     xh, #0
443         b       LSYM(Lad_l)
444
445         FUNC_END aeabi_ui2d
446         FUNC_END floatunsidf
447
448 ARM_FUNC_START floatsidf
449 ARM_FUNC_ALIAS aeabi_i2d floatsidf
450
451         teq     r0, #0
452         do_it   eq, t
453         moveq   r1, #0
454         RETc(eq)
455         do_push {r4, r5, lr}
456         mov     r4, #0x400              @ initial exponent
457         add     r4, r4, #(52-1 - 1)
458         ands    r5, r0, #0x80000000     @ sign bit in r5
459         do_it   mi
460         rsbmi   r0, r0, #0              @ absolute value
461         .ifnc   xl, r0
462         mov     xl, r0
463         .endif
464         mov     xh, #0
465         b       LSYM(Lad_l)
466
467         FUNC_END aeabi_i2d
468         FUNC_END floatsidf
469
470 ARM_FUNC_START extendsfdf2
471 ARM_FUNC_ALIAS aeabi_f2d extendsfdf2
472
473         movs    r2, r0, lsl #1          @ toss sign bit
474         mov     xh, r2, asr #3          @ stretch exponent
475         mov     xh, xh, rrx             @ retrieve sign bit
476         mov     xl, r2, lsl #28         @ retrieve remaining bits
477         do_it   ne, ttt
478         COND(and,s,ne)  r3, r2, #0xff000000     @ isolate exponent
479         teqne   r3, #0xff000000         @ if not 0, check if INF or NAN
480         eorne   xh, xh, #0x38000000     @ fixup exponent otherwise.
481         RETc(ne)                        @ and return it.
482
483         teq     r2, #0                  @ if actually 0
484         do_it   ne, e
485         teqne   r3, #0xff000000         @ or INF or NAN
486         RETc(eq)                        @ we are done already.
487
488         @ value was denormalized.  We can normalize it now.
489         do_push {r4, r5, lr}
490         mov     r4, #0x380              @ setup corresponding exponent
491         and     r5, xh, #0x80000000     @ move sign bit in r5
492         bic     xh, xh, #0x80000000
493         b       LSYM(Lad_l)
494
495         FUNC_END aeabi_f2d
496         FUNC_END extendsfdf2
497
498 ARM_FUNC_START floatundidf
499 ARM_FUNC_ALIAS aeabi_ul2d floatundidf
500
501         orrs    r2, r0, r1
502 #if !defined (__VFP_FP__) && !defined(__SOFTFP__)
503         do_it   eq, t
504         mvfeqd  f0, #0.0
505 #else
506         do_it   eq
507 #endif
508         RETc(eq)
509
510 #if !defined (__VFP_FP__) && !defined(__SOFTFP__)
511         @ For hard FPA code we want to return via the tail below so that
512         @ we can return the result in f0 as well as in r0/r1 for backwards
513         @ compatibility.
514         adr     ip, LSYM(f0_ret)
515         @ Push pc as well so that RETLDM works correctly.
516         do_push {r4, r5, ip, lr, pc}
517 #else
518         do_push {r4, r5, lr}
519 #endif
520
521         mov     r5, #0
522         b       2f
523
524 ARM_FUNC_START floatdidf
525 ARM_FUNC_ALIAS aeabi_l2d floatdidf
526
527         orrs    r2, r0, r1
528 #if !defined (__VFP_FP__) && !defined(__SOFTFP__)
529         do_it   eq, t
530         mvfeqd  f0, #0.0
531 #else
532         do_it   eq
533 #endif
534         RETc(eq)
535
536 #if !defined (__VFP_FP__) && !defined(__SOFTFP__)
537         @ For hard FPA code we want to return via the tail below so that
538         @ we can return the result in f0 as well as in r0/r1 for backwards
539         @ compatibility.
540         adr     ip, LSYM(f0_ret)
541         @ Push pc as well so that RETLDM works correctly.
542         do_push {r4, r5, ip, lr, pc}
543 #else
544         do_push {r4, r5, lr}
545 #endif
546
547         ands    r5, ah, #0x80000000     @ sign bit in r5
548         bpl     2f
549 #if defined(__thumb2__)
550         negs    al, al
551         sbc     ah, ah, ah, lsl #1
552 #else
553         rsbs    al, al, #0
554         rsc     ah, ah, #0
555 #endif
556 2:
557         mov     r4, #0x400              @ initial exponent
558         add     r4, r4, #(52-1 - 1)
559
560         @ FPA little-endian: must swap the word order.
561         .ifnc   xh, ah
562         mov     ip, al
563         mov     xh, ah
564         mov     xl, ip
565         .endif
566
567         movs    ip, xh, lsr #22
568         beq     LSYM(Lad_p)
569
570         @ The value is too big.  Scale it down a bit...
571         mov     r2, #3
572         movs    ip, ip, lsr #3
573         do_it   ne
574         addne   r2, r2, #3
575         movs    ip, ip, lsr #3
576         do_it   ne
577         addne   r2, r2, #3
578         add     r2, r2, ip, lsr #3
579
580         rsb     r3, r2, #32
581         shift1  lsl, ip, xl, r3
582         shift1  lsr, xl, xl, r2
583         shiftop orr xl xl xh lsl r3 lr
584         shift1  lsr, xh, xh, r2
585         add     r4, r4, r2
586         b       LSYM(Lad_p)
587
588 #if !defined (__VFP_FP__) && !defined(__SOFTFP__)
589
590         @ Legacy code expects the result to be returned in f0.  Copy it
591         @ there as well.
592 LSYM(f0_ret):
593         do_push {r0, r1}
594         ldfd    f0, [sp], #8
595         RETLDM
596
597 #endif
598
599         FUNC_END floatdidf
600         FUNC_END aeabi_l2d
601         FUNC_END floatundidf
602         FUNC_END aeabi_ul2d
603
604 #endif /* L_addsubdf3 */
605
606 #ifdef L_arm_muldivdf3
607
608 ARM_FUNC_START muldf3
609 ARM_FUNC_ALIAS aeabi_dmul muldf3
610         do_push {r4, r5, r6, lr}
611
612         @ Mask out exponents, trap any zero/denormal/INF/NAN.
613         mov     ip, #0xff
614         orr     ip, ip, #0x700
615         ands    r4, ip, xh, lsr #20
616         do_it   ne, tte
617         COND(and,s,ne)  r5, ip, yh, lsr #20
618         teqne   r4, ip
619         teqne   r5, ip
620         bleq    LSYM(Lml_s)
621
622         @ Add exponents together
623         add     r4, r4, r5
624
625         @ Determine final sign.
626         eor     r6, xh, yh
627
628         @ Convert mantissa to unsigned integer.
629         @ If power of two, branch to a separate path.
630         bic     xh, xh, ip, lsl #21
631         bic     yh, yh, ip, lsl #21
632         orrs    r5, xl, xh, lsl #12
633         do_it   ne
634         COND(orr,s,ne)  r5, yl, yh, lsl #12
635         orr     xh, xh, #0x00100000
636         orr     yh, yh, #0x00100000
637         beq     LSYM(Lml_1)
638
639 #if __ARM_ARCH__ < 4
640
641         @ Put sign bit in r6, which will be restored in yl later.
642         and   r6, r6, #0x80000000
643
644         @ Well, no way to make it shorter without the umull instruction.
645         stmfd   sp!, {r6, r7, r8, r9, sl, fp}
646         mov     r7, xl, lsr #16
647         mov     r8, yl, lsr #16
648         mov     r9, xh, lsr #16
649         mov     sl, yh, lsr #16
650         bic     xl, xl, r7, lsl #16
651         bic     yl, yl, r8, lsl #16
652         bic     xh, xh, r9, lsl #16
653         bic     yh, yh, sl, lsl #16
654         mul     ip, xl, yl
655         mul     fp, xl, r8
656         mov     lr, #0
657         adds    ip, ip, fp, lsl #16
658         adc     lr, lr, fp, lsr #16
659         mul     fp, r7, yl
660         adds    ip, ip, fp, lsl #16
661         adc     lr, lr, fp, lsr #16
662         mul     fp, xl, sl
663         mov     r5, #0
664         adds    lr, lr, fp, lsl #16
665         adc     r5, r5, fp, lsr #16
666         mul     fp, r7, yh
667         adds    lr, lr, fp, lsl #16
668         adc     r5, r5, fp, lsr #16
669         mul     fp, xh, r8
670         adds    lr, lr, fp, lsl #16
671         adc     r5, r5, fp, lsr #16
672         mul     fp, r9, yl
673         adds    lr, lr, fp, lsl #16
674         adc     r5, r5, fp, lsr #16
675         mul     fp, xh, sl
676         mul     r6, r9, sl
677         adds    r5, r5, fp, lsl #16
678         adc     r6, r6, fp, lsr #16
679         mul     fp, r9, yh
680         adds    r5, r5, fp, lsl #16
681         adc     r6, r6, fp, lsr #16
682         mul     fp, xl, yh
683         adds    lr, lr, fp
684         mul     fp, r7, sl
685         adcs    r5, r5, fp
686         mul     fp, xh, yl
687         adc     r6, r6, #0
688         adds    lr, lr, fp
689         mul     fp, r9, r8
690         adcs    r5, r5, fp
691         mul     fp, r7, r8
692         adc     r6, r6, #0
693         adds    lr, lr, fp
694         mul     fp, xh, yh
695         adcs    r5, r5, fp
696         adc     r6, r6, #0
697         ldmfd   sp!, {yl, r7, r8, r9, sl, fp}
698
699 #else
700
701         @ Here is the actual multiplication.
702         umull   ip, lr, xl, yl
703         mov     r5, #0
704         umlal   lr, r5, xh, yl
705         and     yl, r6, #0x80000000
706         umlal   lr, r5, xl, yh
707         mov     r6, #0
708         umlal   r5, r6, xh, yh
709
710 #endif
711
712         @ The LSBs in ip are only significant for the final rounding.
713         @ Fold them into lr.
714         teq     ip, #0
715         do_it   ne
716         orrne   lr, lr, #1
717
718         @ Adjust result upon the MSB position.
719         sub     r4, r4, #0xff
720         cmp     r6, #(1 << (20-11))
721         sbc     r4, r4, #0x300
722         bcs     1f
723         movs    lr, lr, lsl #1
724         adcs    r5, r5, r5
725         adc     r6, r6, r6
726 1:
727         @ Shift to final position, add sign to result.
728         orr     xh, yl, r6, lsl #11
729         orr     xh, xh, r5, lsr #21
730         mov     xl, r5, lsl #11
731         orr     xl, xl, lr, lsr #21
732         mov     lr, lr, lsl #11
733
734         @ Check exponent range for under/overflow.
735         subs    ip, r4, #(254 - 1)
736         do_it   hi
737         cmphi   ip, #0x700
738         bhi     LSYM(Lml_u)
739
740         @ Round the result, merge final exponent.
741         cmp     lr, #0x80000000
742         do_it   eq
743         COND(mov,s,eq)  lr, xl, lsr #1
744         adcs    xl, xl, #0
745         adc     xh, xh, r4, lsl #20
746         RETLDM  "r4, r5, r6"
747
748         @ Multiplication by 0x1p*: let''s shortcut a lot of code.
749 LSYM(Lml_1):
750         and     r6, r6, #0x80000000
751         orr     xh, r6, xh
752         orr     xl, xl, yl
753         eor     xh, xh, yh
754         subs    r4, r4, ip, lsr #1
755         do_it   gt, tt
756         COND(rsb,s,gt)  r5, r4, ip
757         orrgt   xh, xh, r4, lsl #20
758         RETLDM  "r4, r5, r6" gt
759
760         @ Under/overflow: fix things up for the code below.
761         orr     xh, xh, #0x00100000
762         mov     lr, #0
763         subs    r4, r4, #1
764
765 LSYM(Lml_u):
766         @ Overflow?
767         bgt     LSYM(Lml_o)
768
769         @ Check if denormalized result is possible, otherwise return signed 0.
770         cmn     r4, #(53 + 1)
771         do_it   le, tt
772         movle   xl, #0
773         bicle   xh, xh, #0x7fffffff
774         RETLDM  "r4, r5, r6" le
775
776         @ Find out proper shift value.
777         rsb     r4, r4, #0
778         subs    r4, r4, #32
779         bge     2f
780         adds    r4, r4, #12
781         bgt     1f
782
783         @ shift result right of 1 to 20 bits, preserve sign bit, round, etc.
784         add     r4, r4, #20
785         rsb     r5, r4, #32
786         shift1  lsl, r3, xl, r5
787         shift1  lsr, xl, xl, r4
788         shiftop orr xl xl xh lsl r5 r2
789         and     r2, xh, #0x80000000
790         bic     xh, xh, #0x80000000
791         adds    xl, xl, r3, lsr #31
792         shiftop adc xh r2 xh lsr r4 r6
793         orrs    lr, lr, r3, lsl #1
794         do_it   eq
795         biceq   xl, xl, r3, lsr #31
796         RETLDM  "r4, r5, r6"
797
798         @ shift result right of 21 to 31 bits, or left 11 to 1 bits after
799         @ a register switch from xh to xl. Then round.
800 1:      rsb     r4, r4, #12
801         rsb     r5, r4, #32
802         shift1  lsl, r3, xl, r4
803         shift1  lsr, xl, xl, r5
804         shiftop orr xl xl xh lsl r4 r2
805         bic     xh, xh, #0x7fffffff
806         adds    xl, xl, r3, lsr #31
807         adc     xh, xh, #0
808         orrs    lr, lr, r3, lsl #1
809         do_it   eq
810         biceq   xl, xl, r3, lsr #31
811         RETLDM  "r4, r5, r6"
812
813         @ Shift value right of 32 to 64 bits, or 0 to 32 bits after a switch
814         @ from xh to xl.  Leftover bits are in r3-r6-lr for rounding.
815 2:      rsb     r5, r4, #32
816         shiftop orr lr lr xl lsl r5 r2
817         shift1  lsr, r3, xl, r4
818         shiftop orr r3 r3 xh lsl r5 r2
819         shift1  lsr, xl, xh, r4
820         bic     xh, xh, #0x7fffffff
821         shiftop bic xl xl xh lsr r4 r2
822         add     xl, xl, r3, lsr #31
823         orrs    lr, lr, r3, lsl #1
824         do_it   eq
825         biceq   xl, xl, r3, lsr #31
826         RETLDM  "r4, r5, r6"
827
828         @ One or both arguments are denormalized.
829         @ Scale them leftwards and preserve sign bit.
830 LSYM(Lml_d):
831         teq     r4, #0
832         bne     2f
833         and     r6, xh, #0x80000000
834 1:      movs    xl, xl, lsl #1
835         adc     xh, xh, xh
836         tst     xh, #0x00100000
837         do_it   eq
838         subeq   r4, r4, #1
839         beq     1b
840         orr     xh, xh, r6
841         teq     r5, #0
842         do_it   ne
843         RETc(ne)
844 2:      and     r6, yh, #0x80000000
845 3:      movs    yl, yl, lsl #1
846         adc     yh, yh, yh
847         tst     yh, #0x00100000
848         do_it   eq
849         subeq   r5, r5, #1
850         beq     3b
851         orr     yh, yh, r6
852         RET
853
854 LSYM(Lml_s):
855         @ Isolate the INF and NAN cases away
856         teq     r4, ip
857         and     r5, ip, yh, lsr #20
858         do_it   ne
859         teqne   r5, ip
860         beq     1f
861
862         @ Here, one or more arguments are either denormalized or zero.
863         orrs    r6, xl, xh, lsl #1
864         do_it   ne
865         COND(orr,s,ne)  r6, yl, yh, lsl #1
866         bne     LSYM(Lml_d)
867
868         @ Result is 0, but determine sign anyway.
869 LSYM(Lml_z):
870         eor     xh, xh, yh
871         and     xh, xh, #0x80000000
872         mov     xl, #0
873         RETLDM  "r4, r5, r6"
874
875 1:      @ One or both args are INF or NAN.
876         orrs    r6, xl, xh, lsl #1
877         do_it   eq, te
878         moveq   xl, yl
879         moveq   xh, yh
880         COND(orr,s,ne)  r6, yl, yh, lsl #1
881         beq     LSYM(Lml_n)             @ 0 * INF or INF * 0 -> NAN
882         teq     r4, ip
883         bne     1f
884         orrs    r6, xl, xh, lsl #12
885         bne     LSYM(Lml_n)             @ NAN * <anything> -> NAN
886 1:      teq     r5, ip
887         bne     LSYM(Lml_i)
888         orrs    r6, yl, yh, lsl #12
889         do_it   ne, t
890         movne   xl, yl
891         movne   xh, yh
892         bne     LSYM(Lml_n)             @ <anything> * NAN -> NAN
893
894         @ Result is INF, but we need to determine its sign.
895 LSYM(Lml_i):
896         eor     xh, xh, yh
897
898         @ Overflow: return INF (sign already in xh).
899 LSYM(Lml_o):
900         and     xh, xh, #0x80000000
901         orr     xh, xh, #0x7f000000
902         orr     xh, xh, #0x00f00000
903         mov     xl, #0
904         RETLDM  "r4, r5, r6"
905
906         @ Return a quiet NAN.
907 LSYM(Lml_n):
908         orr     xh, xh, #0x7f000000
909         orr     xh, xh, #0x00f80000
910         RETLDM  "r4, r5, r6"
911
912         FUNC_END aeabi_dmul
913         FUNC_END muldf3
914
915 ARM_FUNC_START divdf3
916 ARM_FUNC_ALIAS aeabi_ddiv divdf3
917         
918         do_push {r4, r5, r6, lr}
919
920         @ Mask out exponents, trap any zero/denormal/INF/NAN.
921         mov     ip, #0xff
922         orr     ip, ip, #0x700
923         ands    r4, ip, xh, lsr #20
924         do_it   ne, tte
925         COND(and,s,ne)  r5, ip, yh, lsr #20
926         teqne   r4, ip
927         teqne   r5, ip
928         bleq    LSYM(Ldv_s)
929
930         @ Substract divisor exponent from dividend''s.
931         sub     r4, r4, r5
932
933         @ Preserve final sign into lr.
934         eor     lr, xh, yh
935
936         @ Convert mantissa to unsigned integer.
937         @ Dividend -> r5-r6, divisor -> yh-yl.
938         orrs    r5, yl, yh, lsl #12
939         mov     xh, xh, lsl #12
940         beq     LSYM(Ldv_1)
941         mov     yh, yh, lsl #12
942         mov     r5, #0x10000000
943         orr     yh, r5, yh, lsr #4
944         orr     yh, yh, yl, lsr #24
945         mov     yl, yl, lsl #8
946         orr     r5, r5, xh, lsr #4
947         orr     r5, r5, xl, lsr #24
948         mov     r6, xl, lsl #8
949
950         @ Initialize xh with final sign bit.
951         and     xh, lr, #0x80000000
952
953         @ Ensure result will land to known bit position.
954         @ Apply exponent bias accordingly.
955         cmp     r5, yh
956         do_it   eq
957         cmpeq   r6, yl
958         adc     r4, r4, #(255 - 2)
959         add     r4, r4, #0x300
960         bcs     1f
961         movs    yh, yh, lsr #1
962         mov     yl, yl, rrx
963 1:
964         @ Perform first substraction to align result to a nibble.
965         subs    r6, r6, yl
966         sbc     r5, r5, yh
967         movs    yh, yh, lsr #1
968         mov     yl, yl, rrx
969         mov     xl, #0x00100000
970         mov     ip, #0x00080000
971
972         @ The actual division loop.
973 1:      subs    lr, r6, yl
974         sbcs    lr, r5, yh
975         do_it   cs, tt
976         subcs   r6, r6, yl
977         movcs   r5, lr
978         orrcs   xl, xl, ip
979         movs    yh, yh, lsr #1
980         mov     yl, yl, rrx
981         subs    lr, r6, yl
982         sbcs    lr, r5, yh
983         do_it   cs, tt
984         subcs   r6, r6, yl
985         movcs   r5, lr
986         orrcs   xl, xl, ip, lsr #1
987         movs    yh, yh, lsr #1
988         mov     yl, yl, rrx
989         subs    lr, r6, yl
990         sbcs    lr, r5, yh
991         do_it   cs, tt
992         subcs   r6, r6, yl
993         movcs   r5, lr
994         orrcs   xl, xl, ip, lsr #2
995         movs    yh, yh, lsr #1
996         mov     yl, yl, rrx
997         subs    lr, r6, yl
998         sbcs    lr, r5, yh
999         do_it   cs, tt
1000         subcs   r6, r6, yl
1001         movcs   r5, lr
1002         orrcs   xl, xl, ip, lsr #3
1003
1004         orrs    lr, r5, r6
1005         beq     2f
1006         mov     r5, r5, lsl #4
1007         orr     r5, r5, r6, lsr #28
1008         mov     r6, r6, lsl #4
1009         mov     yh, yh, lsl #3
1010         orr     yh, yh, yl, lsr #29
1011         mov     yl, yl, lsl #3
1012         movs    ip, ip, lsr #4
1013         bne     1b
1014
1015         @ We are done with a word of the result.
1016         @ Loop again for the low word if this pass was for the high word.
1017         tst     xh, #0x00100000
1018         bne     3f
1019         orr     xh, xh, xl
1020         mov     xl, #0
1021         mov     ip, #0x80000000
1022         b       1b
1023 2:
1024         @ Be sure result starts in the high word.
1025         tst     xh, #0x00100000
1026         do_it   eq, t
1027         orreq   xh, xh, xl
1028         moveq   xl, #0
1029 3:
1030         @ Check exponent range for under/overflow.
1031         subs    ip, r4, #(254 - 1)
1032         do_it   hi
1033         cmphi   ip, #0x700
1034         bhi     LSYM(Lml_u)
1035
1036         @ Round the result, merge final exponent.
1037         subs    ip, r5, yh
1038         do_it   eq, t
1039         COND(sub,s,eq)  ip, r6, yl
1040         COND(mov,s,eq)  ip, xl, lsr #1
1041         adcs    xl, xl, #0
1042         adc     xh, xh, r4, lsl #20
1043         RETLDM  "r4, r5, r6"
1044
1045         @ Division by 0x1p*: shortcut a lot of code.
1046 LSYM(Ldv_1):
1047         and     lr, lr, #0x80000000
1048         orr     xh, lr, xh, lsr #12
1049         adds    r4, r4, ip, lsr #1
1050         do_it   gt, tt
1051         COND(rsb,s,gt)  r5, r4, ip
1052         orrgt   xh, xh, r4, lsl #20
1053         RETLDM  "r4, r5, r6" gt
1054
1055         orr     xh, xh, #0x00100000
1056         mov     lr, #0
1057         subs    r4, r4, #1
1058         b       LSYM(Lml_u)
1059
1060         @ Result mightt need to be denormalized: put remainder bits
1061         @ in lr for rounding considerations.
1062 LSYM(Ldv_u):
1063         orr     lr, r5, r6
1064         b       LSYM(Lml_u)
1065
1066         @ One or both arguments is either INF, NAN or zero.
1067 LSYM(Ldv_s):
1068         and     r5, ip, yh, lsr #20
1069         teq     r4, ip
1070         do_it   eq
1071         teqeq   r5, ip
1072         beq     LSYM(Lml_n)             @ INF/NAN / INF/NAN -> NAN
1073         teq     r4, ip
1074         bne     1f
1075         orrs    r4, xl, xh, lsl #12
1076         bne     LSYM(Lml_n)             @ NAN / <anything> -> NAN
1077         teq     r5, ip
1078         bne     LSYM(Lml_i)             @ INF / <anything> -> INF
1079         mov     xl, yl
1080         mov     xh, yh
1081         b       LSYM(Lml_n)             @ INF / (INF or NAN) -> NAN
1082 1:      teq     r5, ip
1083         bne     2f
1084         orrs    r5, yl, yh, lsl #12
1085         beq     LSYM(Lml_z)             @ <anything> / INF -> 0
1086         mov     xl, yl
1087         mov     xh, yh
1088         b       LSYM(Lml_n)             @ <anything> / NAN -> NAN
1089 2:      @ If both are nonzero, we need to normalize and resume above.
1090         orrs    r6, xl, xh, lsl #1
1091         do_it   ne
1092         COND(orr,s,ne)  r6, yl, yh, lsl #1
1093         bne     LSYM(Lml_d)
1094         @ One or both arguments are 0.
1095         orrs    r4, xl, xh, lsl #1
1096         bne     LSYM(Lml_i)             @ <non_zero> / 0 -> INF
1097         orrs    r5, yl, yh, lsl #1
1098         bne     LSYM(Lml_z)             @ 0 / <non_zero> -> 0
1099         b       LSYM(Lml_n)             @ 0 / 0 -> NAN
1100
1101         FUNC_END aeabi_ddiv
1102         FUNC_END divdf3
1103
1104 #endif /* L_muldivdf3 */
1105
1106 #ifdef L_arm_cmpdf2
1107
1108 @ Note: only r0 (return value) and ip are clobbered here.
1109
1110 ARM_FUNC_START gtdf2
1111 ARM_FUNC_ALIAS gedf2 gtdf2
1112         mov     ip, #-1
1113         b       1f
1114
1115 ARM_FUNC_START ltdf2
1116 ARM_FUNC_ALIAS ledf2 ltdf2
1117         mov     ip, #1
1118         b       1f
1119
1120 ARM_FUNC_START cmpdf2
1121 ARM_FUNC_ALIAS nedf2 cmpdf2
1122 ARM_FUNC_ALIAS eqdf2 cmpdf2
1123         mov     ip, #1                  @ how should we specify unordered here?
1124
1125 1:      str     ip, [sp, #-4]
1126
1127         @ Trap any INF/NAN first.
1128         mov     ip, xh, lsl #1
1129         mvns    ip, ip, asr #21
1130         mov     ip, yh, lsl #1
1131         do_it   ne
1132         COND(mvn,s,ne)  ip, ip, asr #21
1133         beq     3f
1134
1135         @ Test for equality.
1136         @ Note that 0.0 is equal to -0.0.
1137 2:      orrs    ip, xl, xh, lsl #1      @ if x == 0.0 or -0.0
1138         do_it   eq, e
1139         COND(orr,s,eq)  ip, yl, yh, lsl #1      @ and y == 0.0 or -0.0
1140         teqne   xh, yh                  @ or xh == yh
1141         do_it   eq, tt
1142         teqeq   xl, yl                  @ and xl == yl
1143         moveq   r0, #0                  @ then equal.
1144         RETc(eq)
1145
1146         @ Clear C flag
1147         cmn     r0, #0
1148
1149         @ Compare sign, 
1150         teq     xh, yh
1151
1152         @ Compare values if same sign
1153         do_it   pl
1154         cmppl   xh, yh
1155         do_it   eq
1156         cmpeq   xl, yl
1157
1158         @ Result:
1159         do_it   cs, e
1160         movcs   r0, yh, asr #31
1161         mvncc   r0, yh, asr #31
1162         orr     r0, r0, #1
1163         RET
1164
1165         @ Look for a NAN.
1166 3:      mov     ip, xh, lsl #1
1167         mvns    ip, ip, asr #21
1168         bne     4f
1169         orrs    ip, xl, xh, lsl #12
1170         bne     5f                      @ x is NAN
1171 4:      mov     ip, yh, lsl #1
1172         mvns    ip, ip, asr #21
1173         bne     2b
1174         orrs    ip, yl, yh, lsl #12
1175         beq     2b                      @ y is not NAN
1176 5:      ldr     r0, [sp, #-4]           @ unordered return code
1177         RET
1178
1179         FUNC_END gedf2
1180         FUNC_END gtdf2
1181         FUNC_END ledf2
1182         FUNC_END ltdf2
1183         FUNC_END nedf2
1184         FUNC_END eqdf2
1185         FUNC_END cmpdf2
1186
1187 ARM_FUNC_START aeabi_cdrcmple
1188
1189         mov     ip, r0
1190         mov     r0, r2
1191         mov     r2, ip
1192         mov     ip, r1
1193         mov     r1, r3
1194         mov     r3, ip
1195         b       6f
1196         
1197 ARM_FUNC_START aeabi_cdcmpeq
1198 ARM_FUNC_ALIAS aeabi_cdcmple aeabi_cdcmpeq
1199
1200         @ The status-returning routines are required to preserve all
1201         @ registers except ip, lr, and cpsr.
1202 6:      do_push {r0, lr}
1203         ARM_CALL cmpdf2
1204         @ Set the Z flag correctly, and the C flag unconditionally.
1205         cmp     r0, #0
1206         @ Clear the C flag if the return value was -1, indicating
1207         @ that the first operand was smaller than the second.
1208         do_it   mi
1209         cmnmi   r0, #0
1210         RETLDM  "r0"
1211
1212         FUNC_END aeabi_cdcmple
1213         FUNC_END aeabi_cdcmpeq
1214         FUNC_END aeabi_cdrcmple
1215         
1216 ARM_FUNC_START  aeabi_dcmpeq
1217
1218         str     lr, [sp, #-8]!
1219         ARM_CALL aeabi_cdcmple
1220         do_it   eq, e
1221         moveq   r0, #1  @ Equal to.
1222         movne   r0, #0  @ Less than, greater than, or unordered.
1223         RETLDM
1224
1225         FUNC_END aeabi_dcmpeq
1226
1227 ARM_FUNC_START  aeabi_dcmplt
1228
1229         str     lr, [sp, #-8]!
1230         ARM_CALL aeabi_cdcmple
1231         do_it   cc, e
1232         movcc   r0, #1  @ Less than.
1233         movcs   r0, #0  @ Equal to, greater than, or unordered.
1234         RETLDM
1235
1236         FUNC_END aeabi_dcmplt
1237
1238 ARM_FUNC_START  aeabi_dcmple
1239
1240         str     lr, [sp, #-8]!
1241         ARM_CALL aeabi_cdcmple
1242         do_it   ls, e
1243         movls   r0, #1  @ Less than or equal to.
1244         movhi   r0, #0  @ Greater than or unordered.
1245         RETLDM
1246
1247         FUNC_END aeabi_dcmple
1248
1249 ARM_FUNC_START  aeabi_dcmpge
1250
1251         str     lr, [sp, #-8]!
1252         ARM_CALL aeabi_cdrcmple
1253         do_it   ls, e
1254         movls   r0, #1  @ Operand 2 is less than or equal to operand 1.
1255         movhi   r0, #0  @ Operand 2 greater than operand 1, or unordered.
1256         RETLDM
1257
1258         FUNC_END aeabi_dcmpge
1259
1260 ARM_FUNC_START  aeabi_dcmpgt
1261
1262         str     lr, [sp, #-8]!
1263         ARM_CALL aeabi_cdrcmple
1264         do_it   cc, e
1265         movcc   r0, #1  @ Operand 2 is less than operand 1.
1266         movcs   r0, #0  @ Operand 2 is greater than or equal to operand 1,
1267                         @ or they are unordered.
1268         RETLDM
1269
1270         FUNC_END aeabi_dcmpgt
1271
1272 #endif /* L_cmpdf2 */
1273
1274 #ifdef L_arm_unorddf2
1275
1276 ARM_FUNC_START unorddf2
1277 ARM_FUNC_ALIAS aeabi_dcmpun unorddf2
1278
1279         mov     ip, xh, lsl #1
1280         mvns    ip, ip, asr #21
1281         bne     1f
1282         orrs    ip, xl, xh, lsl #12
1283         bne     3f                      @ x is NAN
1284 1:      mov     ip, yh, lsl #1
1285         mvns    ip, ip, asr #21
1286         bne     2f
1287         orrs    ip, yl, yh, lsl #12
1288         bne     3f                      @ y is NAN
1289 2:      mov     r0, #0                  @ arguments are ordered.
1290         RET
1291
1292 3:      mov     r0, #1                  @ arguments are unordered.
1293         RET
1294
1295         FUNC_END aeabi_dcmpun
1296         FUNC_END unorddf2
1297
1298 #endif /* L_unorddf2 */
1299
1300 #ifdef L_arm_fixdfsi
1301
1302 ARM_FUNC_START fixdfsi
1303 ARM_FUNC_ALIAS aeabi_d2iz fixdfsi
1304
1305         @ check exponent range.
1306         mov     r2, xh, lsl #1
1307         adds    r2, r2, #(1 << 21)
1308         bcs     2f                      @ value is INF or NAN
1309         bpl     1f                      @ value is too small
1310         mov     r3, #(0xfffffc00 + 31)
1311         subs    r2, r3, r2, asr #21
1312         bls     3f                      @ value is too large
1313
1314         @ scale value
1315         mov     r3, xh, lsl #11
1316         orr     r3, r3, #0x80000000
1317         orr     r3, r3, xl, lsr #21
1318         tst     xh, #0x80000000         @ the sign bit
1319         shift1  lsr, r0, r3, r2
1320         do_it   ne
1321         rsbne   r0, r0, #0
1322         RET
1323
1324 1:      mov     r0, #0
1325         RET
1326
1327 2:      orrs    xl, xl, xh, lsl #12
1328         bne     4f                      @ x is NAN.
1329 3:      ands    r0, xh, #0x80000000     @ the sign bit
1330         do_it   eq
1331         moveq   r0, #0x7fffffff         @ maximum signed positive si
1332         RET
1333
1334 4:      mov     r0, #0                  @ How should we convert NAN?
1335         RET
1336
1337         FUNC_END aeabi_d2iz
1338         FUNC_END fixdfsi
1339
1340 #endif /* L_fixdfsi */
1341
1342 #ifdef L_arm_fixunsdfsi
1343
1344 ARM_FUNC_START fixunsdfsi
1345 ARM_FUNC_ALIAS aeabi_d2uiz fixunsdfsi
1346
1347         @ check exponent range.
1348         movs    r2, xh, lsl #1
1349         bcs     1f                      @ value is negative
1350         adds    r2, r2, #(1 << 21)
1351         bcs     2f                      @ value is INF or NAN
1352         bpl     1f                      @ value is too small
1353         mov     r3, #(0xfffffc00 + 31)
1354         subs    r2, r3, r2, asr #21
1355         bmi     3f                      @ value is too large
1356
1357         @ scale value
1358         mov     r3, xh, lsl #11
1359         orr     r3, r3, #0x80000000
1360         orr     r3, r3, xl, lsr #21
1361         shift1  lsr, r0, r3, r2
1362         RET
1363
1364 1:      mov     r0, #0
1365         RET
1366
1367 2:      orrs    xl, xl, xh, lsl #12
1368         bne     4f                      @ value is NAN.
1369 3:      mov     r0, #0xffffffff         @ maximum unsigned si
1370         RET
1371
1372 4:      mov     r0, #0                  @ How should we convert NAN?
1373         RET
1374
1375         FUNC_END aeabi_d2uiz
1376         FUNC_END fixunsdfsi
1377
1378 #endif /* L_fixunsdfsi */
1379
1380 #ifdef L_arm_truncdfsf2
1381
1382 ARM_FUNC_START truncdfsf2
1383 ARM_FUNC_ALIAS aeabi_d2f truncdfsf2
1384
1385         @ check exponent range.
1386         mov     r2, xh, lsl #1
1387         subs    r3, r2, #((1023 - 127) << 21)
1388         do_it   cs, t
1389         COND(sub,s,cs)  ip, r3, #(1 << 21)
1390         COND(rsb,s,cs)  ip, ip, #(254 << 21)
1391         bls     2f                      @ value is out of range
1392
1393 1:      @ shift and round mantissa
1394         and     ip, xh, #0x80000000
1395         mov     r2, xl, lsl #3
1396         orr     xl, ip, xl, lsr #29
1397         cmp     r2, #0x80000000
1398         adc     r0, xl, r3, lsl #2
1399         do_it   eq
1400         biceq   r0, r0, #1
1401         RET
1402
1403 2:      @ either overflow or underflow
1404         tst     xh, #0x40000000
1405         bne     3f                      @ overflow
1406
1407         @ check if denormalized value is possible
1408         adds    r2, r3, #(23 << 21)
1409         do_it   lt, t
1410         andlt   r0, xh, #0x80000000     @ too small, return signed 0.
1411         RETc(lt)
1412
1413         @ denormalize value so we can resume with the code above afterwards.
1414         orr     xh, xh, #0x00100000
1415         mov     r2, r2, lsr #21
1416         rsb     r2, r2, #24
1417         rsb     ip, r2, #32
1418 #if defined(__thumb2__)
1419         lsls    r3, xl, ip
1420 #else
1421         movs    r3, xl, lsl ip
1422 #endif
1423         shift1  lsr, xl, xl, r2
1424         do_it   ne
1425         orrne   xl, xl, #1              @ fold r3 for rounding considerations. 
1426         mov     r3, xh, lsl #11
1427         mov     r3, r3, lsr #11
1428         shiftop orr xl xl r3 lsl ip ip
1429         shift1  lsr, r3, r3, r2
1430         mov     r3, r3, lsl #1
1431         b       1b
1432
1433 3:      @ chech for NAN
1434         mvns    r3, r2, asr #21
1435         bne     5f                      @ simple overflow
1436         orrs    r3, xl, xh, lsl #12
1437         do_it   ne, tt
1438         movne   r0, #0x7f000000
1439         orrne   r0, r0, #0x00c00000
1440         RETc(ne)                        @ return NAN
1441
1442 5:      @ return INF with sign
1443         and     r0, xh, #0x80000000
1444         orr     r0, r0, #0x7f000000
1445         orr     r0, r0, #0x00800000
1446         RET
1447
1448         FUNC_END aeabi_d2f
1449         FUNC_END truncdfsf2
1450
1451 #endif /* L_truncdfsf2 */