Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • uspace/lib/posix/stdlib/strtold.c

    rec18957a rd43c117  
    3030 * @{
    3131 */
    32 /** @file
     32/** @file Backend for floating point conversions.
    3333 */
    3434
     
    4646#include "../strings.h"
    4747#include "../errno.h"
     48#include "../limits.h"
     49
     50// FIXME: #include <float.h>
    4851
    4952#ifndef HUGE_VALL
     
    5255
    5356#ifndef abs
    54         #define abs(x) ((x < 0) ? -x : x)
    55 #endif
    56 
    57 // TODO: clean up, documentation
    58 
    59 // FIXME: ensure it builds and works on all platforms
    60 
    61 const int max_small_pow5 = 15;
    62 
    63 /* The value at index i is approximately 5**i. */
    64 long double small_pow5[] = {
    65         0x1P0,
    66         0x5P0,
    67         0x19P0,
    68         0x7dP0,
    69         0x271P0,
    70         0xc35P0,
    71         0x3d09P0,
    72         0x1312dP0,
    73         0x5f5e1P0,
    74         0x1dcd65P0,
    75         0x9502f9P0,
    76         0x2e90eddP0,
    77         0xe8d4a51P0,
    78         0x48c27395P0,
    79         0x16bcc41e9P0,
    80         0x71afd498dP0
     57        #define abs(x) (((x) < 0) ? -(x) : (x))
     58#endif
     59
     60/* If the constants are not defined, use double precision as default. */
     61#ifndef LDBL_MANT_DIG
     62        #define LDBL_MANT_DIG 53
     63#endif
     64#ifndef LDBL_MAX_EXP
     65        #define LDBL_MAX_EXP 1024
     66#endif
     67#ifndef LDBL_MIN_EXP
     68        #define LDBL_MIN_EXP (-1021)
     69#endif
     70#ifndef LDBL_DIG
     71        #define LDBL_DIG 15
     72#endif
     73#ifndef LDBL_MIN
     74        #define LDBL_MIN 2.2250738585072014E-308
     75#endif
     76
     77/* power functions ************************************************************/
     78
     79#if LDBL_MAX_EXP >= 16384
     80const int MAX_POW5 = 12;
     81#else
     82const int MAX_POW5 = 8;
     83#endif
     84
     85/* The value at index i is approximately 5**(2**i). */
     86long double pow5[] = {
     87        0x5p0l,
     88        0x19p0l,
     89        0x271p0l,
     90        0x5F5E1p0l,
     91        0x2386F26FC1p0l,
     92        0x4EE2D6D415B85ACEF81p0l,
     93        0x184F03E93FF9F4DAA797ED6E38ED6p36l,
     94        0x127748F9301D319BF8CDE66D86D62p185l,
     95        0x154FDD7F73BF3BD1BBB77203731FDp482l,
     96#if LDBL_MAX_EXP >= 16384
     97        0x1C633415D4C1D238D98CAB8A978A0p1076l,
     98        0x192ECEB0D02EA182ECA1A7A51E316p2265l,
     99        0x13D1676BB8A7ABBC94E9A519C6535p4643l,
     100        0x188C0A40514412F3592982A7F0094p9398l,
     101#endif
    81102};
    82103
    83 /* The value at index i is approximately 5**(2**i). */
    84 long double large_pow5[] = {
    85         0x5P0l,
    86         0x19P0l,
    87         0x271P0l,
    88         0x5f5e1P0l,
    89         0x2386f26fc1P0l,
    90         0x4ee2d6d415b85acef81P0l,
    91         0x184f03e93ff9f4daa797ed6e38ed64bf6a1f01P0l,
    92         0x24ee91f2603a6337f19bccdb0dac404dc08d3cff5ecP128l,
    93         0x553f75fdcefcef46eeddcP512l,
    94         0x1c633415d4c1d238d98cab8a978a0b1f138cb07303P1024l,
    95         0x325d9d61a05d4305d9434f4a3c62d433949ae6209d492P2200l,
    96         0x9e8b3b5dc53d5de4a74d28ce329ace526a3197bbebe3034f77154ce2bcba1964P4500l,
    97         0x6230290145104bcd64a60a9fc025254932bb0fd922271133eeae7P9300l
    98 };
     104#if LDBL_MAX_EXP >= 16384
     105const int MAX_POW2 = 15;
     106#else
     107const int MAX_POW2 = 9;
     108#endif
    99109
    100110/* Powers of two. */
     
    110120        0x1P256l,
    111121        0x1P512l,
     122#if LDBL_MAX_EXP >= 16384
    112123        0x1P1024l,
    113124        0x1P2048l,
    114125        0x1P4096l,
    115         0x1P8192l
     126        0x1P8192l,
     127#endif
    116128};
    117129
    118 static inline bool out_of_range(long double num)
    119 {
    120         return num == 0.0l || num == HUGE_VALL;
    121 }
    122 
    123130/**
    124131 * Multiplies a number by a power of five.
    125  * The result is not exact and may not be the best possible approximation.
    126  *
    127  * @param base Number to be multiplied.
    128  * @param exponent Base 5 exponent.
    129  * @return base multiplied by 5**exponent
    130  */
    131 static long double mul_pow5(long double base, int exponent)
    132 {
    133         if (out_of_range(base)) {
    134                 return base;
    135         }
    136        
    137         if (abs(exponent) >> 13 != 0) {
     132 * The result may be inexact and may not be the best possible approximation.
     133 *
     134 * @param mant Number to be multiplied.
     135 * @param exp Base 5 exponent.
     136 * @return mant multiplied by 5**exp
     137 */
     138static long double mul_pow5(long double mant, int exp)
     139{
     140        if (mant == 0.0l || mant == HUGE_VALL) {
     141                return mant;
     142        }
     143       
     144        if (abs(exp) >> (MAX_POW5 + 1) != 0) {
     145                /* Too large exponent. */
    138146                errno = ERANGE;
    139                 return exponent < 0 ? 0.0l : HUGE_VALL;
    140         }
    141        
    142         if (exponent < 0) {
    143                 exponent = -exponent;
    144                 base /= small_pow5[exponent & 0xF];
    145                 for (int i = 4; i < 13; ++i) {
    146                         if (((exponent >> i) & 1) != 0) {
    147                                 base /= large_pow5[i];
    148                                 if (out_of_range(base)) {
     147                return exp < 0 ? LDBL_MIN : HUGE_VALL;
     148        }
     149       
     150        if (exp < 0) {
     151                exp = abs(exp);
     152                for (int bit = 0; bit <= MAX_POW5; ++bit) {
     153                        /* Multiply by powers of five bit-by-bit. */
     154                        if (((exp >> bit) & 1) != 0) {
     155                                mant /= pow5[bit];
     156                                if (mant == 0.0l) {
     157                                        /* Underflow. */
     158                                        mant = LDBL_MIN;
    149159                                        errno = ERANGE;
    150160                                        break;
     
    153163                }
    154164        } else {
    155                 base *= small_pow5[exponent & 0xF];
    156                 for (int i = 4; i < 13; ++i) {
    157                         if (((exponent >> i) & 1) != 0) {
    158                                 base *= large_pow5[i];
    159                                 if (out_of_range(base)) {
     165                for (int bit = 0; bit <= MAX_POW5; ++bit) {
     166                        /* Multiply by powers of five bit-by-bit. */
     167                        if (((exp >> bit) & 1) != 0) {
     168                                mant *= pow5[bit];
     169                                if (mant == HUGE_VALL) {
     170                                        /* Overflow. */
    160171                                        errno = ERANGE;
    161172                                        break;
     
    165176        }
    166177       
    167         return base;
    168 }
    169 
    170 /**
    171  * Multiplies a number by a power of two.
    172  *
    173  * @param base Number to be multiplied.
    174  * @param exponent Base 2 exponent.
    175  * @return base multiplied by 2**exponent
    176  */
    177 static long double mul_pow2(long double base, int exponent)
    178 {
    179         if (out_of_range(base)) {
    180                 return base;
    181         }
    182        
    183         if (abs(exponent) >> 14 != 0) {
     178        return mant;
     179}
     180
     181/**
     182 * Multiplies a number by a power of two. This is always exact.
     183 *
     184 * @param mant Number to be multiplied.
     185 * @param exp Base 2 exponent.
     186 * @return mant multiplied by 2**exp.
     187 */
     188static long double mul_pow2(long double mant, int exp)
     189{
     190        if (mant == 0.0l || mant == HUGE_VALL) {
     191                return mant;
     192        }
     193       
     194        if (exp > LDBL_MAX_EXP || exp < LDBL_MIN_EXP) {
    184195                errno = ERANGE;
    185                 return exponent < 0 ? 0.0l : HUGE_VALL;
    186         }
    187        
    188         if (exponent < 0) {
    189                 exponent = -exponent;
    190                 for (int i = 0; i < 14; ++i) {
    191                         if (((exponent >> i) & 1) != 0) {
    192                                 base /= pow2[i];
    193                                 if (out_of_range(base)) {
     196                return exp < 0 ? LDBL_MIN : HUGE_VALL;
     197        }
     198       
     199        if (exp < 0) {
     200                exp = abs(exp);
     201                for (int i = 0; i <= MAX_POW2; ++i) {
     202                        if (((exp >> i) & 1) != 0) {
     203                                mant /= pow2[i];
     204                                if (mant == 0.0l) {
     205                                        mant = LDBL_MIN;
    194206                                        errno = ERANGE;
    195207                                        break;
     
    198210                }
    199211        } else {
    200                 for (int i = 0; i < 14; ++i) {
    201                         if (((exponent >> i) & 1) != 0) {
    202                                 base *= pow2[i];
    203                                 if (out_of_range(base)) {
     212                for (int i = 0; i <= MAX_POW2; ++i) {
     213                        if (((exp >> i) & 1) != 0) {
     214                                mant *= pow2[i];
     215                                if (mant == HUGE_VALL) {
    204216                                        errno = ERANGE;
    205217                                        break;
     
    209221        }
    210222       
    211         return base;
    212 }
    213 
    214 
     223        return mant;
     224}
     225
     226/* end power functions ********************************************************/
     227
     228
     229
     230/**
     231 * Convert decimal string representation of the floating point number.
     232 * Function expects the string pointer to be already pointed at the first
     233 * digit (i.e. leading optional sign was already consumed by the caller).
     234 *
     235 * @param sptr Pointer to the storage of the string pointer. Upon successful
     236 *     conversion, the string pointer is updated to point to the first
     237 *     unrecognized character.
     238 * @return An approximate representation of the input floating-point number.
     239 */
    215240static long double parse_decimal(const char **sptr)
    216241{
    217         // TODO: Use strtol(), at least for exponent.
     242        assert(sptr != NULL);
     243        assert (*sptr != NULL);
    218244       
    219245        const int DEC_BASE = 10;
    220246        const char DECIMAL_POINT = '.';
    221247        const char EXPONENT_MARK = 'e';
    222         /* The highest amount of digits that can be safely parsed
    223          * before an overflow occurs.
    224          */
    225         const int PARSE_DECIMAL_DIGS = 19;
    226        
    227         /* significand */
    228         uint64_t significand = 0;
    229        
    230         /* position in the input string */
    231         int i = 0;
     248       
     249        const char *str = *sptr;
     250        long double significand = 0;
     251        long exponent = 0;
    232252       
    233253        /* number of digits parsed so far */
    234254        int parsed_digits = 0;
    235        
    236         int exponent = 0;
    237        
    238         const char *str = *sptr;
    239        
    240         /* digits before decimal point */
    241         while (isdigit(str[i])) {
    242                 if (parsed_digits == 0 && str[i] == '0') {
     255        bool after_decimal = false;
     256       
     257        while (isdigit(*str) || (!after_decimal && *str == DECIMAL_POINT)) {
     258                if (*str == DECIMAL_POINT) {
     259                        after_decimal = true;
     260                        str++;
     261                        continue;
     262                }
     263               
     264                if (parsed_digits == 0 && *str == '0') {
    243265                        /* Nothing, just skip leading zeros. */
    244                 } else if (parsed_digits < PARSE_DECIMAL_DIGS) {
    245                         significand *= DEC_BASE;
    246                         significand += str[i] - '0';
     266                } else if (parsed_digits < LDBL_DIG) {
     267                        significand = significand * DEC_BASE + (*str - '0');
    247268                        parsed_digits++;
    248269                } else {
     
    250271                }
    251272               
    252                 i++;
    253         }
    254        
    255         if (str[i] == DECIMAL_POINT) {
    256                 i++;
    257                
    258                 /* digits after decimal point */
    259                 while (isdigit(str[i])) {
    260                         if (parsed_digits == 0 && str[i] == '0') {
    261                                 /* Skip leading zeros and decrement exponent. */
    262                                 exponent--;
    263                         } else if (parsed_digits < PARSE_DECIMAL_DIGS) {
    264                                 significand *= DEC_BASE;
    265                                 significand += str[i] - '0';
    266                                 exponent--;
    267                                 parsed_digits++;
    268                         } else {
    269                                 /* ignore */
    270                         }
    271                        
    272                         i++;
    273                 }
     273                if (after_decimal) {
     274                        /* Decrement exponent if we are parsing the fractional part. */
     275                        exponent--;
     276                }
     277               
     278                str++;
    274279        }
    275280       
    276281        /* exponent */
    277         if (tolower(str[i]) == EXPONENT_MARK) {
    278                 i++;
    279                
    280                 bool negative = false;
    281                 int exp = 0;
    282                
    283                 switch (str[i]) {
    284                 case '-':
    285                         negative = true;
    286                         /* fallthrough */
    287                 case '+':
    288                         i++;
    289                 }
    290                
    291                 while (isdigit(str[i])) {
    292                         if (exp < 65536) {
    293                                 exp *= DEC_BASE;
    294                                 exp += str[i] - '0';
    295                         }
    296                        
    297                         i++;
    298                 }
    299                
    300                 if (negative) {
    301                         exp = -exp;
    302                 }
    303                
    304                 exponent += exp;
    305         }
    306        
    307         long double result = (long double) significand;
    308         result = mul_pow5(result, exponent);
    309         if (result != HUGE_VALL) {
    310                 result = mul_pow2(result, exponent);
    311         }
    312        
    313         *sptr = &str[i];
    314         return result;
    315 }
    316 
     282        if (tolower(*str) == EXPONENT_MARK) {
     283                str++;
     284               
     285                /* Returns MIN/MAX value on error, which is ok. */
     286                long exp = strtol(str, (char **) &str, DEC_BASE);
     287               
     288                if (exponent > 0 && exp > LONG_MAX - exponent) {
     289                        exponent = LONG_MAX;
     290                } else if (exponent < 0 && exp < LONG_MIN - exponent) {
     291                        exponent = LONG_MIN;
     292                } else {
     293                        exponent += exp;
     294                }
     295        }
     296       
     297        *sptr = str;
     298       
     299        /* Return multiplied by a power of ten. */
     300        return mul_pow2(mul_pow5(significand, exponent), exponent);
     301}
     302
     303/**
     304 * Derive a hexadecimal digit from its character representation.
     305 *
     306 * @param ch Character representation of the hexadecimal digit.
     307 * @return Digit value represented by an integer.
     308 */
    317309static inline int hex_value(char ch)
    318310{
     
    325317
    326318/**
    327  * @param val Integer value.
    328  * @return How many leading zero bits there are. (Maximum is 3)
    329  */
    330 static inline int leading_zeros(uint64_t val)
    331 {
    332         for (int i = 3; i > 0; --i) {
    333                 if ((val >> (64 - i)) == 0) {
    334                         return i;
    335                 }
    336         }
    337        
    338         return 0;
    339 }
    340 
     319 * Convert hexadecimal string representation of the floating point number.
     320 * Function expects the string pointer to be already pointed at the first
     321 * digit (i.e. leading optional sign and 0x prefix were already consumed
     322 * by the caller).
     323 *
     324 * @param sptr Pointer to the storage of the string pointer. Upon successful
     325 *     conversion, the string pointer is updated to point to the first
     326 *     unrecognized character.
     327 * @return Representation of the input floating-point number.
     328 */
    341329static long double parse_hexadecimal(const char **sptr)
    342330{
    343         // TODO: Use strtol(), at least for exponent.
    344        
    345         /* this function currently always rounds to zero */
    346         // TODO: honor rounding mode
     331        assert(sptr != NULL && *sptr != NULL);
    347332       
    348333        const int DEC_BASE = 10;
     
    350335        const char DECIMAL_POINT = '.';
    351336        const char EXPONENT_MARK = 'p';
    352         /* The highest amount of digits that can be safely parsed
    353          * before an overflow occurs.
    354          */
    355         const int PARSE_HEX_DIGS = 16;
    356        
    357         /* significand */
    358         uint64_t significand = 0;
    359        
    360         /* position in the input string */
    361         int i = 0;
    362        
    363         /* number of digits parsed so far */
    364         int parsed_digits = 0;
    365        
    366         int exponent = 0;
    367337       
    368338        const char *str = *sptr;
    369        
    370         /* digits before decimal point */
    371         while (posix_isxdigit(str[i])) {
    372                 if (parsed_digits == 0 && str[i] == '0') {
     339        long double significand = 0;
     340        long exponent = 0;
     341       
     342        /* number of bits parsed so far */
     343        int parsed_bits = 0;
     344        bool after_decimal = false;
     345       
     346        while (posix_isxdigit(*str) || (!after_decimal && *str == DECIMAL_POINT)) {
     347                if (*str == DECIMAL_POINT) {
     348                        after_decimal = true;
     349                        str++;
     350                        continue;
     351                }
     352               
     353                if (parsed_bits == 0 && *str == '0') {
    373354                        /* Nothing, just skip leading zeros. */
    374                 } else if (parsed_digits < PARSE_HEX_DIGS) {
    375                         significand *= HEX_BASE;
    376                         significand += hex_value(str[i]);
    377                         parsed_digits++;
    378                 } else if (parsed_digits == PARSE_HEX_DIGS) {
    379                         /* The first digit may have had leading zeros,
    380                          * so we need to parse one more digit and shift
    381                          * the value accordingly.
    382                          */
    383                        
    384                         int zeros = leading_zeros(significand);
    385                         significand = (significand << zeros) |
    386                             (hex_value(str[i]) >> (4 - zeros));
    387                        
    388                         exponent += (4 - zeros);
    389                         parsed_digits++;
     355                } else if (parsed_bits <= LDBL_MANT_DIG) {
     356                        significand = significand * HEX_BASE + hex_value(*str);
     357                        parsed_bits += 4;
    390358                } else {
    391359                        exponent += 4;
    392360                }
    393361               
    394                 i++;
    395         }
    396        
    397         if (str[i] == DECIMAL_POINT) {
    398                 i++;
    399                
    400                 /* digits after decimal point */
    401                 while (posix_isxdigit(str[i])) {
    402                         if (parsed_digits == 0 && str[i] == '0') {
    403                                 /* Skip leading zeros and decrement exponent. */
    404                                 exponent -= 4;
    405                         } else if (parsed_digits < PARSE_HEX_DIGS) {
    406                                 significand *= HEX_BASE;
    407                                 significand += hex_value(str[i]);
    408                                 exponent -= 4;
    409                                 parsed_digits++;
    410                         } else if (parsed_digits == PARSE_HEX_DIGS) {
    411                                 /* The first digit may have had leading zeros,
    412                                  * so we need to parse one more digit and shift
    413                                  * the value accordingly.
    414                                  */
    415                                
    416                                 int zeros = leading_zeros(significand);
    417                                 significand = (significand << zeros) |
    418                                     (hex_value(str[i]) >> (4 - zeros));
    419                                
    420                                 exponent -= zeros;
    421                                 parsed_digits++;
    422                         } else {
    423                                 /* ignore */
    424                         }
    425                        
    426                         i++;
    427                 }
     362                if (after_decimal) {
     363                        exponent -= 4;
     364                }
     365               
     366                str++;
    428367        }
    429368       
    430369        /* exponent */
    431         if (tolower(str[i]) == EXPONENT_MARK) {
    432                 i++;
    433                
    434                 bool negative = false;
    435                 int exp = 0;
    436                
    437                 switch (str[i]) {
    438                 case '-':
    439                         negative = true;
    440                         /* fallthrough */
    441                 case '+':
    442                         i++;
    443                 }
    444                
    445                 while (isdigit(str[i])) {
    446                         if (exp < 65536) {
    447                                 exp *= DEC_BASE;
    448                                 exp += str[i] - '0';
    449                         }
    450                        
    451                         i++;
    452                 }
    453                
    454                 if (negative) {
    455                         exp = -exp;
    456                 }
    457                
    458                 exponent += exp;
    459         }
    460        
    461         long double result = (long double) significand;
    462         result = mul_pow2(result, exponent);
    463        
    464         *sptr = &str[i];
    465         return result;
     370        if (tolower(*str) == EXPONENT_MARK) {
     371                str++;
     372               
     373                /* Returns MIN/MAX value on error, which is ok. */
     374                long exp = strtol(str, (char **) &str, DEC_BASE);
     375               
     376                if (exponent > 0 && exp > LONG_MAX - exponent) {
     377                        exponent = LONG_MAX;
     378                } else if (exponent < 0 && exp < LONG_MIN - exponent) {
     379                        exponent = LONG_MIN;
     380                } else {
     381                        exponent += exp;
     382                }
     383        }
     384       
     385        *sptr = str;
     386       
     387        /* Return multiplied by a power of two. */
     388        return mul_pow2(significand, exponent);
    466389}
    467390
     
    478401 * @param nptr Input string.
    479402 * @param endptr If non-NULL, *endptr is set to the position of the first
    480  *    unrecognized character.
     403 *     unrecognized character.
    481404 * @return An approximate representation of the input floating-point number.
    482405 */
     
    512435               
    513436                if (endptr != NULL) {
    514                         *endptr = (char *) &nptr[i + 3];
    515                 }
    516                 errno = ERANGE;
    517                 return negative ? -0.0l : +0.0l;
     437                        *endptr = (char *) nptr;
     438                }
     439                errno = EINVAL;
     440                return 0;
    518441        }
    519442       
     
    567490/** @}
    568491 */
    569 
Note: See TracChangeset for help on using the changeset viewer.