Home | History | Annotate | Line # | Download | only in softfloat
softfloat-specialize revision 1.13
      1     /*	$NetBSD: softfloat-specialize,v 1.13 2025/09/17 11:37:38 nat Exp $	*/
      2     
      3     /* This is a derivative work. */
      4     
      5     /*
      6     ===============================================================================
      7     
      8     This C source fragment is part of the SoftFloat IEC/IEEE Floating-point
      9     Arithmetic Package, Release 2a.
     10     
     11     Written by John R. Hauser.  This work was made possible in part by the
     12     International Computer Science Institute, located at Suite 600, 1947 Center
     13     Street, Berkeley, California 94704.  Funding was partially provided by the
     14     National Science Foundation under grant MIP-9311980.  The original version
     15     of this code was written as part of a project to build a fixed-point vector
     16     processor in collaboration with the University of California at Berkeley,
     17     overseen by Profs. Nelson Morgan and John Wawrzynek.  More information
     18     is available through the Web page `http://HTTP.CS.Berkeley.EDU/~jhauser/
     19     arithmetic/SoftFloat.html'.
     20     
     21     THIS SOFTWARE IS DISTRIBUTED AS IS, FOR FREE.  Although reasonable effort
     22     has been made to avoid it, THIS SOFTWARE MAY CONTAIN FAULTS THAT WILL AT
     23     TIMES RESULT IN INCORRECT BEHAVIOR.  USE OF THIS SOFTWARE IS RESTRICTED TO
     24     PERSONS AND ORGANIZATIONS WHO CAN AND WILL TAKE FULL RESPONSIBILITY FOR ANY
     25     AND ALL LOSSES, COSTS, OR OTHER PROBLEMS ARISING FROM ITS USE.
     26     
     27     Derivative works are acceptable, even for commercial purposes, so long as
     28     (1) they include prominent notice that the work is derivative, and (2) they
     29     include prominent notice akin to these four paragraphs for those parts of
     30     this code that are retained.
     31     
     32     ===============================================================================
     33     */
     34     
     35     #include <signal.h>
     36     #include <string.h>
     37     #include <unistd.h>
     38     
     39     #include "reentrant.h"
     40     
     41     /*
     42     -------------------------------------------------------------------------------
     43     Underflow tininess-detection mode, statically initialized to default value.
     44     (The declaration in `softfloat.h' must match the `int8' type here.)
     45     -------------------------------------------------------------------------------
     46     */
     47     #ifdef SOFTFLOAT_FOR_GCC
     48     static
     49     #endif
     50     int8 float_detect_tininess = float_tininess_after_rounding;
     51     
     52     /*
     53     -------------------------------------------------------------------------------
     54     Raises the exceptions specified by `flags'.  Floating-point traps can be
     55     defined here if desired.  It is currently not possible for such a trap to
     56     substitute a result value.  If traps are not implemented, this routine
     57     should be simply `float_exception_flags |= flags;'.
     58     -------------------------------------------------------------------------------
     59     */
     60     #ifdef SOFTFLOAT_FOR_GCC
     61     #ifndef set_float_exception_mask
     62     #define float_exception_mask	_softfloat_float_exception_mask
     63     #endif
     64     #endif
     65     #ifndef set_float_exception_mask
     66     fp_except float_exception_mask = 0;
     67     #endif
     68     void
     69     float_raise( fp_except newflags )
     70     {
     71         siginfo_t info;
     72         struct sigaction sa;
     73         sigset_t sigmask, osigmask;
     74         fp_except flags;
     75     
     76         for (;;) {
     77     #ifdef set_float_exception_mask
     78     	flags = newflags | set_float_exception_flags(newflags, 0);
     79     #else
     80     	float_exception_flags |= newflags;
     81     	flags = float_exception_flags;
     82     #endif
     83     
     84     	/*
     85     	 * If none of the sticky flags are trapped (i.e., enabled in
     86     	 * float_exception_mask), we're done.  Trapping is unusual and
     87     	 * costly anyway, so take the non-trapping path as the fast
     88     	 * path.
     89     	 */
     90     	flags &= float_exception_mask;
     91     	if (__predict_true(flags == 0))
     92     	    break;
     93     
     94     	/*
     95     	 * Block all signals while we figure out how to deliver a
     96     	 * non-maskable (as a signal), non-ignorable SIGFPE, and obtain
     97     	 * the current signal mask.
     98     	 */
     99     	sigfillset(&sigmask);
    100     #ifdef _REENTRANT	/* XXX PR lib/59401 */
    101     	thr_sigsetmask(SIG_BLOCK, &sigmask, &osigmask);
    102     #else
    103     	sigprocmask(SIG_BLOCK, &sigmask, &osigmask);
    104     #endif
    105     
    106     	/*
    107     	 * Find the current signal disposition of SIGFPE.
    108     	 */
    109     	sigaction(SIGFPE, NULL, &sa);
    110     
    111     	/*
    112     	 * If SIGFPE is masked or ignored, unmask it and reset it to
    113     	 * the default disposition to deliver the signal.
    114     	 */
    115     	if (sigismember(&osigmask, SIGFPE) ||
    116     	    ((sa.sa_flags & SA_SIGINFO) == 0 &&
    117     		sa.sa_handler == SIG_IGN)) {
    118     		/*
    119     		 * Prepare to unmask SIGFPE.  This will take effect
    120     		 * when we use thr_sigsetmask(SIG_SETMASK, ...) below,
    121     		 * once the signal has been queued, so that it happens
    122     		 * atomically with respect to other signal delivery.
    123     		 */
    124     		sigdelset(&osigmask, SIGFPE);
    125     
    126     		/*
    127     		 * Reset SIGFPE to the default disposition, which is to
    128     		 * terminate the process.
    129     		 */
    130     		memset(&sa, 0, sizeof(sa));
    131     		sa.sa_handler = SIG_DFL;
    132     		sigemptyset(&sa.sa_mask);
    133     		sa.sa_flags = 0;
    134     		sigaction(SIGFPE, &sa, NULL);
    135     	}
    136     
    137     	/*
    138     	 * Queue the signal for delivery.  It won't trigger the signal
    139     	 * handler yet, because it's still masked, but as soon as we
    140     	 * unmask it either the process will terminate or the signal
    141     	 * handler will be called.
    142     	 */
    143     	memset(&info, 0, sizeof info);
    144     	info.si_signo = SIGFPE;
    145     	info.si_pid = getpid();
    146     	info.si_uid = geteuid();
    147     	if (flags & float_flag_underflow)
    148     	    info.si_code = FPE_FLTUND;
    149     	else if (flags & float_flag_overflow)
    150     	    info.si_code = FPE_FLTOVF;
    151     	else if (flags & float_flag_divbyzero)
    152     	    info.si_code = FPE_FLTDIV;
    153     	else if (flags & float_flag_invalid)
    154     	    info.si_code = FPE_FLTINV;
    155     	else if (flags & float_flag_inexact)
    156     	    info.si_code = FPE_FLTRES;
    157     	sigqueueinfo(getpid(), &info);
    158     
    159     	/*
    160     	 * Restore the old signal mask, except with SIGFPE unmasked
    161     	 * even if it was masked before.
    162     	 *
    163     	 * At this point, either the process will terminate (if SIGFPE
    164     	 * had or now has the default disposition) or the signal
    165     	 * handler will be called (if SIGFPE had a non-default,
    166     	 * non-ignored disposition).
    167     	 *
    168     	 * If the signal handler returns, it can't change the set of
    169     	 * exceptions raised by this floating-point operation -- but it
    170     	 * can change the sticky set from previous operations, and it
    171     	 * can change the set of exceptions that are trapped, so loop
    172     	 * around; next time we might make progress instead of calling
    173     	 * the signal handler again.
    174     	 */
    175     #ifdef _REENTRANT	/* XXX PR lib/59401 */
    176     	thr_sigsetmask(SIG_SETMASK, &osigmask, NULL);
    177     #else
    178     	sigprocmask(SIG_SETMASK, &osigmask, NULL);
    179     #endif
    180         }
    181     }
    182     #undef float_exception_mask
    183     
    184     /*
    185     -------------------------------------------------------------------------------
    186     Internal canonical NaN format.
    187     -------------------------------------------------------------------------------
    188     */
    189     typedef struct {
    190         flag sign;
    191         bits64 high, low;
    192     } commonNaNT;
    193     
    194     /*
    195     -------------------------------------------------------------------------------
    196     The pattern for a default generated single-precision NaN.
    197     -------------------------------------------------------------------------------
    198     */
    199     #define float32_default_nan 0xFFFFFFFF
    200     
    201     /*
    202     -------------------------------------------------------------------------------
    203     Returns 1 if the single-precision floating-point value `a' is a NaN;
    204     otherwise returns 0.
    205     -------------------------------------------------------------------------------
    206     */
    207     #ifdef SOFTFLOAT_FOR_GCC
    208     static
    209     #endif
    210     flag float32_is_nan( float32 a )
    211     {
    212     
    213         return ( (bits32)0xFF000000 < (bits32) ( a<<1 ) );
    214     
    215     }
    216     
    217     /*
    218     -------------------------------------------------------------------------------
    219     Returns 1 if the single-precision floating-point value `a' is a signaling
    220     NaN; otherwise returns 0.
    221     -------------------------------------------------------------------------------
    222     */
    223     #if defined(SOFTFLOAT_FOR_GCC) \
    224         && !defined(SOFTFLOATAARCH64_FOR_GCC) \
    225         && !defined(SOFTFLOATSPARC64_FOR_GCC) \
    226         && !defined(SOFTFLOATM68K_FOR_GCC)
    227     static
    228     #endif
    229     flag float32_is_signaling_nan( float32 a )
    230     {
    231     
    232         return ( ( ( a>>22 ) & 0x1FF ) == 0x1FE ) && ( a & 0x003FFFFF );
    233     
    234     }
    235     
    236     /*
    237     -------------------------------------------------------------------------------
    238     Returns the result of converting the single-precision floating-point NaN
    239     `a' to the canonical NaN format.  If `a' is a signaling NaN, the invalid
    240     exception is raised.
    241     -------------------------------------------------------------------------------
    242     */
    243     static commonNaNT float32ToCommonNaN( float32 a )
    244     {
    245         commonNaNT z;
    246     
    247         if ( float32_is_signaling_nan( a ) ) float_raise( float_flag_invalid );
    248         z.sign = a>>31;
    249         z.low = 0;
    250         z.high = ( (bits64) a )<<41;
    251         return z;
    252     
    253     }
    254     
    255     /*
    256     -------------------------------------------------------------------------------
    257     Returns the result of converting the canonical NaN `a' to the single-
    258     precision floating-point format.
    259     -------------------------------------------------------------------------------
    260     */
    261     static float32 commonNaNToFloat32( commonNaNT a )
    262     {
    263     
    264         return ( ( (bits32) a.sign )<<31 ) | 0x7FC00000 | (bits32)( a.high>>41 );
    265     
    266     }
    267     
    268     /*
    269     -------------------------------------------------------------------------------
    270     Takes two single-precision floating-point values `a' and `b', one of which
    271     is a NaN, and returns the appropriate NaN result.  If either `a' or `b' is a
    272     signaling NaN, the invalid exception is raised.
    273     -------------------------------------------------------------------------------
    274     */
    275     static float32 propagateFloat32NaN( float32 a, float32 b )
    276     {
    277         flag aIsNaN, aIsSignalingNaN, bIsNaN, bIsSignalingNaN;
    278     
    279         aIsNaN = float32_is_nan( a );
    280         aIsSignalingNaN = float32_is_signaling_nan( a );
    281         bIsNaN = float32_is_nan( b );
    282         bIsSignalingNaN = float32_is_signaling_nan( b );
    283         a |= 0x00400000;
    284         b |= 0x00400000;
    285         if ( aIsSignalingNaN | bIsSignalingNaN ) float_raise( float_flag_invalid );
    286         if ( aIsNaN ) {
    287             return ( aIsSignalingNaN & bIsNaN ) ? b : a;
    288         }
    289         else {
    290             return b;
    291         }
    292     
    293     }
    294     
    295     /*
    296     -------------------------------------------------------------------------------
    297     The pattern for a default generated double-precision NaN.
    298     -------------------------------------------------------------------------------
    299     */
    300     #define float64_default_nan LIT64( 0xFFFFFFFFFFFFFFFF )
    301     
    302     /*
    303     -------------------------------------------------------------------------------
    304     Returns 1 if the double-precision floating-point value `a' is a NaN;
    305     otherwise returns 0.
    306     -------------------------------------------------------------------------------
    307     */
    308     #ifdef SOFTFLOAT_FOR_GCC
    309     static
    310     #endif
    311     flag float64_is_nan( float64 a )
    312     {
    313     
    314         return ( (bits64)LIT64( 0xFFE0000000000000 ) <
    315     	     (bits64) ( FLOAT64_DEMANGLE(a)<<1 ) );
    316     
    317     }
    318     
    319     /*
    320     -------------------------------------------------------------------------------
    321     Returns 1 if the double-precision floating-point value `a' is a signaling
    322     NaN; otherwise returns 0.
    323     -------------------------------------------------------------------------------
    324     */
    325     #if defined(SOFTFLOAT_FOR_GCC) \
    326         && !defined(SOFTFLOATAARCH64_FOR_GCC) \
    327         && !defined(SOFTFLOATSPARC64_FOR_GCC) \
    328         && !defined(SOFTFLOATM68K_FOR_GCC)
    329     static
    330     #endif
    331     flag float64_is_signaling_nan( float64 a )
    332     {
    333     
    334         return
    335                ( ( ( FLOAT64_DEMANGLE(a)>>51 ) & 0xFFF ) == 0xFFE )
    336             && ( FLOAT64_DEMANGLE(a) & LIT64( 0x0007FFFFFFFFFFFF ) );
    337     
    338     }
    339     
    340     /*
    341     -------------------------------------------------------------------------------
    342     Returns the result of converting the double-precision floating-point NaN
    343     `a' to the canonical NaN format.  If `a' is a signaling NaN, the invalid
    344     exception is raised.
    345     -------------------------------------------------------------------------------
    346     */
    347     static commonNaNT float64ToCommonNaN( float64 a )
    348     {
    349         commonNaNT z;
    350     
    351         if ( float64_is_signaling_nan( a ) ) float_raise( float_flag_invalid );
    352         z.sign = (flag)(FLOAT64_DEMANGLE(a)>>63);
    353         z.low = 0;
    354         z.high = FLOAT64_DEMANGLE(a)<<12;
    355         return z;
    356     
    357     }
    358     
    359     /*
    360     -------------------------------------------------------------------------------
    361     Returns the result of converting the canonical NaN `a' to the double-
    362     precision floating-point format.
    363     -------------------------------------------------------------------------------
    364     */
    365     static float64 commonNaNToFloat64( commonNaNT a )
    366     {
    367     
    368         return FLOAT64_MANGLE(
    369     	( ( (bits64) a.sign )<<63 )
    370             | LIT64( 0x7FF8000000000000 )
    371             | ( a.high>>12 ) );
    372     
    373     }
    374     
    375     /*
    376     -------------------------------------------------------------------------------
    377     Takes two double-precision floating-point values `a' and `b', one of which
    378     is a NaN, and returns the appropriate NaN result.  If either `a' or `b' is a
    379     signaling NaN, the invalid exception is raised.
    380     -------------------------------------------------------------------------------
    381     */
    382     static float64 propagateFloat64NaN( float64 a, float64 b )
    383     {
    384         flag aIsNaN, aIsSignalingNaN, bIsNaN, bIsSignalingNaN;
    385     
    386         aIsNaN = float64_is_nan( a );
    387         aIsSignalingNaN = float64_is_signaling_nan( a );
    388         bIsNaN = float64_is_nan( b );
    389         bIsSignalingNaN = float64_is_signaling_nan( b );
    390         a |= FLOAT64_MANGLE(LIT64( 0x0008000000000000 ));
    391         b |= FLOAT64_MANGLE(LIT64( 0x0008000000000000 ));
    392         if ( aIsSignalingNaN | bIsSignalingNaN ) float_raise( float_flag_invalid );
    393         if ( aIsNaN ) {
    394             return ( aIsSignalingNaN & bIsNaN ) ? b : a;
    395         }
    396         else {
    397             return b;
    398         }
    399     
    400     }
    401     
    402     #ifdef FLOATX80
    403     
    404     /*
    405     -------------------------------------------------------------------------------
    406     The pattern for a default generated extended double-precision NaN.  The
    407     `high' and `low' values hold the most- and least-significant bits,
    408     respectively.
    409     -------------------------------------------------------------------------------
    410     */
    411     #define floatx80_default_nan_high 0xFFFF
    412     #define floatx80_default_nan_low  LIT64( 0xFFFFFFFFFFFFFFFF )
    413     
    414     /*
    415     -------------------------------------------------------------------------------
    416     Returns 1 if the extended double-precision floating-point value `a' is a
    417     NaN; otherwise returns 0.
    418     -------------------------------------------------------------------------------
    419     */
    420     flag floatx80_is_nan( floatx80 a )
    421     {
    422     
    423         return (((a.high >> X80SHIFT) & 0x7FFF) == 0x7FFF) && (bits64)(a.low<<1);
    424     
    425     }
    426     
    427     /*
    428     -------------------------------------------------------------------------------
    429     Returns 1 if the extended double-precision floating-point value `a' is a
    430     signaling NaN; otherwise returns 0.
    431     -------------------------------------------------------------------------------
    432     */
    433     flag floatx80_is_signaling_nan( floatx80 a )
    434     {
    435         bits64 aLow;
    436     
    437         aLow = a.low & ~ LIT64( 0x4000000000000000 );
    438         return
    439                ( ( (a.high >> X80SHIFT) & 0x7FFF ) == 0x7FFF )
    440             && (bits64) ( aLow<<1 )
    441             && ( a.low == aLow );
    442     
    443     }
    444     
    445     #ifndef SOFTFLOAT_BITS32
    446     /*
    447     -------------------------------------------------------------------------------
    448     Returns the result of converting the extended double-precision floating-
    449     point NaN `a' to the canonical NaN format.  If `a' is a signaling NaN, the
    450     invalid exception is raised.
    451     -------------------------------------------------------------------------------
    452     */
    453     static commonNaNT floatx80ToCommonNaN( floatx80 a )
    454     {
    455         commonNaNT z;
    456     
    457         if ( floatx80_is_signaling_nan( a ) ) float_raise( float_flag_invalid );
    458         z.sign = a.high>>15;
    459         z.low = 0;
    460         z.high = a.low<<1;
    461         return z;
    462     
    463     }
    464     
    465     /*
    466     -------------------------------------------------------------------------------
    467     Returns the result of converting the canonical NaN `a' to the extended
    468     double-precision floating-point format.
    469     -------------------------------------------------------------------------------
    470     */
    471     static floatx80 commonNaNToFloatx80( commonNaNT a )
    472     {
    473         floatx80 z;
    474     
    475         z.low = LIT64( 0xC000000000000000 ) | ( a.high>>1 );
    476         z.high = ( ( (bits16) a.sign )<<15 ) | 0x7FFF;
    477         return z;
    478     
    479     }
    480     
    481     /*
    482     -------------------------------------------------------------------------------
    483     Takes two extended double-precision floating-point values `a' and `b', one
    484     of which is a NaN, and returns the appropriate NaN result.  If either `a' or
    485     `b' is a signaling NaN, the invalid exception is raised.
    486     -------------------------------------------------------------------------------
    487     */
    488     static floatx80 propagateFloatx80NaN( floatx80 a, floatx80 b )
    489     {
    490         flag aIsNaN, aIsSignalingNaN, bIsNaN, bIsSignalingNaN;
    491     
    492         aIsNaN = floatx80_is_nan( a );
    493         aIsSignalingNaN = floatx80_is_signaling_nan( a );
    494         bIsNaN = floatx80_is_nan( b );
    495         bIsSignalingNaN = floatx80_is_signaling_nan( b );
    496         a.low |= LIT64( 0xC000000000000000 );
    497         b.low |= LIT64( 0xC000000000000000 );
    498         if ( aIsSignalingNaN | bIsSignalingNaN ) float_raise( float_flag_invalid );
    499         if ( aIsNaN ) {
    500             return ( aIsSignalingNaN & bIsNaN ) ? b : a;
    501         }
    502         else {
    503             return b;
    504         }
    505     
    506     }
    507     
    508     #endif
    509     #endif
    510     
    511     #ifdef FLOAT128
    512     
    513     /*
    514     -------------------------------------------------------------------------------
    515     The pattern for a default generated quadruple-precision NaN.  The `high' and
    516     `low' values hold the most- and least-significant bits, respectively.
    517     -------------------------------------------------------------------------------
    518     */
    519     #define float128_default_nan_high LIT64( 0xFFFFFFFFFFFFFFFF )
    520     #define float128_default_nan_low  LIT64( 0xFFFFFFFFFFFFFFFF )
    521     
    522     /*
    523     -------------------------------------------------------------------------------
    524     Returns 1 if the quadruple-precision floating-point value `a' is a NaN;
    525     otherwise returns 0.
    526     -------------------------------------------------------------------------------
    527     */
    528     flag float128_is_nan( float128 a )
    529     {
    530     
    531         return
    532                ( (bits64)LIT64( 0xFFFE000000000000 ) <= (bits64) ( a.high<<1 ) )
    533             && ( a.low || ( a.high & LIT64( 0x0000FFFFFFFFFFFF ) ) );
    534     
    535     }
    536     
    537     /*
    538     -------------------------------------------------------------------------------
    539     Returns 1 if the quadruple-precision floating-point value `a' is a
    540     signaling NaN; otherwise returns 0.
    541     -------------------------------------------------------------------------------
    542     */
    543     flag float128_is_signaling_nan( float128 a )
    544     {
    545     
    546         return
    547                ( ( ( a.high>>47 ) & 0xFFFF ) == 0xFFFE )
    548             && ( a.low || ( a.high & LIT64( 0x00007FFFFFFFFFFF ) ) );
    549     
    550     }
    551     
    552     /*
    553     -------------------------------------------------------------------------------
    554     Returns the result of converting the quadruple-precision floating-point NaN
    555     `a' to the canonical NaN format.  If `a' is a signaling NaN, the invalid
    556     exception is raised.
    557     -------------------------------------------------------------------------------
    558     */
    559     static commonNaNT float128ToCommonNaN( float128 a )
    560     {
    561         commonNaNT z;
    562     
    563         if ( float128_is_signaling_nan( a ) ) float_raise( float_flag_invalid );
    564         z.sign = (flag)(a.high>>63);
    565         shortShift128Left( a.high, a.low, 16, &z.high, &z.low );
    566         return z;
    567     
    568     }
    569     
    570     /*
    571     -------------------------------------------------------------------------------
    572     Returns the result of converting the canonical NaN `a' to the quadruple-
    573     precision floating-point format.
    574     -------------------------------------------------------------------------------
    575     */
    576     static float128 commonNaNToFloat128( commonNaNT a )
    577     {
    578         float128 z;
    579     
    580         shift128Right( a.high, a.low, 16, &z.high, &z.low );
    581         z.high |= ( ( (bits64) a.sign )<<63 ) | LIT64( 0x7FFF800000000000 );
    582         return z;
    583     
    584     }
    585     
    586     /*
    587     -------------------------------------------------------------------------------
    588     Takes two quadruple-precision floating-point values `a' and `b', one of
    589     which is a NaN, and returns the appropriate NaN result.  If either `a' or
    590     `b' is a signaling NaN, the invalid exception is raised.
    591     -------------------------------------------------------------------------------
    592     */
    593     static float128 propagateFloat128NaN( float128 a, float128 b )
    594     {
    595         flag aIsNaN, aIsSignalingNaN, bIsNaN, bIsSignalingNaN;
    596     
    597         aIsNaN = float128_is_nan( a );
    598         aIsSignalingNaN = float128_is_signaling_nan( a );
    599         bIsNaN = float128_is_nan( b );
    600         bIsSignalingNaN = float128_is_signaling_nan( b );
    601         a.high |= LIT64( 0x0000800000000000 );
    602         b.high |= LIT64( 0x0000800000000000 );
    603         if ( aIsSignalingNaN | bIsSignalingNaN ) float_raise( float_flag_invalid );
    604         if ( aIsNaN ) {
    605             return ( aIsSignalingNaN & bIsNaN ) ? b : a;
    606         }
    607         else {
    608             return b;
    609         }
    610     
    611     }
    612     
    613     #endif
    614     
    615