1*34472Sbostic/* 2*34472Sbostic * Copyright (c) 1988 Regents of the University of California. 3*34472Sbostic * All rights reserved. The Berkeley software License Agreement 4*34472Sbostic * specifies the terms and conditions for redistribution. 5*34472Sbostic */ 6*34472Sbostic 7*34472Sbostic#if defined(LIBC_SCCS) && !defined(lint) 8*34472Sbostic_sccsid:.asciz "@(#)atof.s 5.1 (Berkeley) 05/24/88" 9*34472Sbostic#endif /* LIBC_SCCS and not lint */ 10*34472Sbostic 11*34472Sbostic#include "DEFS.h" 12*34472Sbostic 13*34472Sbostic/* 14*34472Sbostic * atof: convert ascii to floating 15*34472Sbostic * 16*34472Sbostic * C usage: 17*34472Sbostic * 18*34472Sbostic * double atof (s) 19*34472Sbostic * char *s; 20*34472Sbostic * 21*34472Sbostic * Register usage: 22*34472Sbostic * 23*34472Sbostic * r0-1: value being developed 24*34472Sbostic * r2: first section: pointer to the next character 25*34472Sbostic * second section: binary exponent 26*34472Sbostic * r3: flags 27*34472Sbostic * r4: first section: the current character 28*34472Sbostic * second section: scratch 29*34472Sbostic * r5: the decimal exponent 30*34472Sbostic * r6-7: scratch 31*34472Sbostic */ 32*34472Sbostic .set msign,0 # mantissa has negative sign 33*34472Sbostic .set esign,1 # exponent has negative sign 34*34472Sbostic .set decpt,2 # decimal point encountered 35*34472Sbostic 36*34472SbosticENTRY(atof, R6|R7) 37*34472Sbostic/* 38*34472Sbostic * Initialization 39*34472Sbostic */ 40*34472Sbostic clrl r3 # All flags start out false 41*34472Sbostic movl 4(fp),r2 # Address the first character 42*34472Sbostic clrl r5 # Clear starting exponent 43*34472Sbostic/* 44*34472Sbostic * Skip leading white space 45*34472Sbostic */ 46*34472Sbosticsk0: movzbl (r2),r4 # Fetch the next (first) character 47*34472Sbostic incl r2 48*34472Sbostic cmpb $' ,r4 # Is it blank? 49*34472Sbostic beql sk0 # ...yes 50*34472Sbostic cmpb r4,$8 # 8 is lowest of white-space group 51*34472Sbostic blss sk1 # Jump if char too low to be white space 52*34472Sbostic cmpb r4,$13 # 13 is highest of white-space group 53*34472Sbostic bleq sk0 # Jump if character is white space 54*34472Sbosticsk1: 55*34472Sbostic/* 56*34472Sbostic * Check for a sign 57*34472Sbostic */ 58*34472Sbostic cmpb $'+,r4 # Positive sign? 59*34472Sbostic beql cs1 # ... yes 60*34472Sbostic cmpb $'-,r4 # Negative sign? 61*34472Sbostic bneq cs2 # ... no 62*34472Sbostic orb2 $1<msign,r3 # Indicate a negative mantissa 63*34472Sbosticcs1: movzbl (r2),r4 # Skip the character 64*34472Sbostic incl r2 65*34472Sbosticcs2: 66*34472Sbostic/* 67*34472Sbostic * Accumulate digits, keeping track of the exponent 68*34472Sbostic */ 69*34472Sbostic clrl r1 70*34472Sbostic clrl r0 # Clear the accumulator 71*34472Sbosticad0: cmpb r4,$'0 # Do we have a digit? 72*34472Sbostic blss ad4 # ... no, too small 73*34472Sbostic cmpb r4,$'9 74*34472Sbostic bgtr ad4 # ... no, too large 75*34472Sbostic/* 76*34472Sbostic * We got a digit. Accumulate it 77*34472Sbostic */ 78*34472Sbostic cmpl r0,$214748364 # Would this digit cause overflow? 79*34472Sbostic bgeq ad1 # ... yes 80*34472Sbostic/* 81*34472Sbostic * Multiply (r0,r1) by 10. This is done by developing 82*34472Sbostic * (r0,r1)*2 in (r6,r7), shifting (r0,r1) left three bits, 83*34472Sbostic * and adding the two quadwords. 84*34472Sbostic */ 85*34472Sbostic shlq $1,r0,r6 # (r6,r7)=(r0,r1)*2 86*34472Sbostic shlq $3,r0,r0 # (r0,r1)=(r0,r1)*8 87*34472Sbostic addl2 r7,r1 # Add low halves 88*34472Sbostic adwc r6,r0 # Add high halves 89*34472Sbostic/* 90*34472Sbostic * Add in the digit 91*34472Sbostic */ 92*34472Sbostic subl2 $'0,r4 # Get the digit value 93*34472Sbostic addl2 r4,r1 # Add it into the accumulator 94*34472Sbostic adwc $0,r0 # Possible carry into high half 95*34472Sbostic brb ad2 # Join common code 96*34472Sbostic/* 97*34472Sbostic * Here when the digit won't fit in the accumulator 98*34472Sbostic */ 99*34472Sbosticad1: incl r5 # Ignore the digit, bump exponent 100*34472Sbostic/* 101*34472Sbostic * If we have seen a decimal point, decrease the exponent by 1 102*34472Sbostic */ 103*34472Sbosticad2: bbc $decpt,r3,ad3 # Jump if decimal point not seen 104*34472Sbostic decl r5 # Decrease exponent 105*34472Sbosticad3: 106*34472Sbostic/* 107*34472Sbostic * Fetch the next character, back for more 108*34472Sbostic */ 109*34472Sbostic movzbl (r2),r4 # Fetch 110*34472Sbostic incl r2 111*34472Sbostic brb ad0 # Try again 112*34472Sbostic/* 113*34472Sbostic * Not a digit. Could it be a decimal point? 114*34472Sbostic */ 115*34472Sbosticad4: cmpb r4,$'. # If it's not a decimal point, either it's 116*34472Sbostic bneq ad5 # the end of the number or the start of 117*34472Sbostic # the exponent. 118*34472Sbostic bbs $decpt,r3,ad5 119*34472Sbostic orb2 $1<decpt,r3 # If it IS a decimal point, we record that 120*34472Sbostic brb ad3 # we've seen one, and keep collecting 121*34472Sbostic # digits if it is the first one. 122*34472Sbostic 123*34472Sbostic/* 124*34472Sbostic * Check for an exponent 125*34472Sbostic */ 126*34472Sbosticad5: clrl r6 # Initialize the exponent accumulator 127*34472Sbostic 128*34472Sbostic cmpb r4,$'e # We allow both lower case e 129*34472Sbostic beql ex1 # ... and ... 130*34472Sbostic cmpb r4,$'E # upper-case E 131*34472Sbostic bneq ex7 132*34472Sbostic/* 133*34472Sbostic * Does the exponent have a sign? 134*34472Sbostic */ 135*34472Sbosticex1: movzbl (r2),r4 # Get next character 136*34472Sbostic incl r2 137*34472Sbostic cmpb r4,$'+ # Positive sign? 138*34472Sbostic beql ex2 # ... yes ... 139*34472Sbostic cmpb r4,$'- # Negative sign? 140*34472Sbostic bneq ex3 # ... no ... 141*34472Sbostic orb2 $1<esign,r3 # Indicate exponent is negative 142*34472Sbosticex2: movzbl (r2),r4 # Grab the next character 143*34472Sbostic incl r2 144*34472Sbostic/* 145*34472Sbostic * Accumulate exponent digits in r6 146*34472Sbostic */ 147*34472Sbosticex3: cmpb r4,$'0 # A digit is within the range 148*34472Sbostic blss ex4 # '0' through 149*34472Sbostic cmpb r4,$'9 # '9', 150*34472Sbostic bgtr ex4 # inclusive. 151*34472Sbostic cmpl r6,$214748364 # Exponent outrageously large already? 152*34472Sbostic bgeq ex2 # ... yes 153*34472Sbostic moval (r6)[r6],r6 # r6 *= 5 154*34472Sbostic movaw -'0(r4)[r6],r6 # r6 = r6 * 2 + r4 - '0' 155*34472Sbostic brb ex2 # Go 'round again 156*34472Sbosticex4: 157*34472Sbostic/* 158*34472Sbostic * Now get the final exponent and force it within a reasonable 159*34472Sbostic * range so our scaling loops don't take forever for values 160*34472Sbostic * that will ultimately cause overflow or underflow anyway. 161*34472Sbostic * A tight check on over/underflow will be done by ldexp. 162*34472Sbostic */ 163*34472Sbostic bbc $esign,r3,ex5 # Jump if exponent not negative 164*34472Sbostic mnegl r6,r6 # If sign, negate exponent 165*34472Sbosticex5: addl2 r6,r5 # Add given exponent to calculated exponent 166*34472Sbostic cmpl r5,$-100 # Absurdly small? 167*34472Sbostic bgtr ex6 # ... no 168*34472Sbostic movl $-100,r5 # ... yes, force within limit 169*34472Sbosticex6: cmpl r5,$100 # Absurdly large? 170*34472Sbostic blss ex7 # ... no 171*34472Sbostic movl $100,r5 # ... yes, force within bounds 172*34472Sbosticex7: 173*34472Sbostic/* 174*34472Sbostic * Our number has now been reduced to a mantissa and an exponent. 175*34472Sbostic * The mantissa is a 63-bit positive binary integer in r0,r1, 176*34472Sbostic * and the exponent is a signed power of 10 in r5. The msign 177*34472Sbostic * bit in r3 will be on if the mantissa should ultimately be 178*34472Sbostic * considered negative. 179*34472Sbostic * 180*34472Sbostic * We now have to convert it to a standard format floating point 181*34472Sbostic * number. This will be done by accumulating a binary exponent 182*34472Sbostic * in r2, as we progressively get r5 closer to zero. 183*34472Sbostic * 184*34472Sbostic * Don't bother scaling if the mantissa is zero 185*34472Sbostic */ 186*34472Sbostic tstl r1 187*34472Sbostic bneq 1f 188*34472Sbostic tstl r0 # Mantissa zero? 189*34472Sbostic jeql exit # ... yes 190*34472Sbostic 191*34472Sbostic1: clrl r2 # Initialize binary exponent 192*34472Sbostic tstl r5 # Which way to scale? 193*34472Sbostic bleq sd0 # Scale down if decimal exponent <= 0 194*34472Sbostic/* 195*34472Sbostic * Scale up by "multiplying" r0,r1 by 10 as many times as necessary, 196*34472Sbostic * as follows: 197*34472Sbostic * 198*34472Sbostic * Step 1: Shift r0,r1 right as necessary to ensure that no 199*34472Sbostic * overflow can occur when multiplying. 200*34472Sbostic */ 201*34472Sbosticsu0: cmpl r0,$429496729 # Compare high word to (2**31)/5 202*34472Sbostic blss su1 # Jump out if guaranteed safe 203*34472Sbostic shrq $1,r0,r0 # Else shift right one bit 204*34472Sbostic incl r2 # bump exponent to compensate 205*34472Sbostic brb su0 # and go back to test again. 206*34472Sbostic/* 207*34472Sbostic * Step 2: Multiply r0,r1 by 5, by appropriate shifting and 208*34472Sbostic * double-precision addition 209*34472Sbostic */ 210*34472Sbosticsu1: shlq $2,r0,r6 # (r6,r7) := (r0,r1) * 4 211*34472Sbostic addl2 r7,r1 # Add low-order halves 212*34472Sbostic adwc r6,r0 # and high-order halves 213*34472Sbostic/* 214*34472Sbostic * Step 3: Increment the binary exponent to take care of the final 215*34472Sbostic * factor of 2, and go back if we still need to scale more. 216*34472Sbostic */ 217*34472Sbostic incl r2 # Increment the exponent 218*34472Sbostic decl r5 # ...sobgtr r5,su0 219*34472Sbostic bgtr su0 # and back for more (maybe) 220*34472Sbostic 221*34472Sbostic brb cm0 # Merge to build final value 222*34472Sbostic 223*34472Sbostic/* 224*34472Sbostic * Scale down. We must "divide" r0,r1 by 10 as many times 225*34472Sbostic * as needed, as follows: 226*34472Sbostic * 227*34472Sbostic * Step 0: Right now, the condition codes reflect the state 228*34472Sbostic * of r5. If it's zero, we are done. 229*34472Sbostic */ 230*34472Sbosticsd0: beql cm0 # If finished, build final number 231*34472Sbostic/* 232*34472Sbostic * Step 1: Shift r0,r1 left until the high-order bit (not counting 233*34472Sbostic * the sign bit) is nonzero, so that the division will preserve 234*34472Sbostic * as much precision as possible. 235*34472Sbostic */ 236*34472Sbostic tstl r0 # Is the entire high-order half zero? 237*34472Sbostic bneq sd2 # ...no, go shift one bit at a time 238*34472Sbostic shlq $30,r0,r0 # ...yes, shift left 30, 239*34472Sbostic subl2 $30,r2 # decrement the exponent to compensate, 240*34472Sbostic # and now it's known to be safe to shift 241*34472Sbostic # at least once more. 242*34472Sbosticsd1: shlq $1,r0,r0 # Shift (r0,r1) left one, and 243*34472Sbostic decl r2 # decrement the exponent to compensate 244*34472Sbosticsd2: bbc $30,r0,sd1 # If the high-order bit is off, go shift 245*34472Sbostic/* 246*34472Sbostic * Step 2: Divide the high-order part of (r0,r1) by 5, 247*34472Sbostic * giving a quotient in r1 and a remainder in r7. 248*34472Sbostic */ 249*34472Sbosticsd3: movl r0,r7 # Copy the high-order part 250*34472Sbostic clrl r6 # Zero-extend to 64 bits 251*34472Sbostic ediv $5,r6,r0,r6 # Divide (cannot overflow) 252*34472Sbostic/* 253*34472Sbostic * Step 3: Divide the low-order part of (r0,r1) by 5, 254*34472Sbostic * using the remainder from step 2 for rounding. 255*34472Sbostic * Note that the result of this computation is unsigned, 256*34472Sbostic * so we have to allow for the fact that an ordinary division 257*34472Sbostic * by 5 could overflow. We make allowance by dividing by 10, 258*34472Sbostic * multiplying the quotient by 2, and using the remainder 259*34472Sbostic * to adjust the modified quotient. 260*34472Sbostic */ 261*34472Sbostic addl3 $2,r1,r7 # Dividend is low part of (r0,r1) plus 262*34472Sbostic adwc $0,r6 # 2 for rounding plus 263*34472Sbostic # (2**32) * previous remainder 264*34472Sbostic ediv $10,r6,r1,r7 # r1 := quotient, r7 := remainder. 265*34472Sbostic addl2 r1,r1 # Make r1 result of dividing by 5 266*34472Sbostic cmpl r7,$5 # If remainder is 5 or greater, 267*34472Sbostic blss sd4 # increment the adjustted quotient. 268*34472Sbostic incl r1 269*34472Sbostic/* 270*34472Sbostic * Step 4: Increment the decimal exponent, decrement the binary 271*34472Sbostic * exponent (to make the division by 5 into a division by 10), 272*34472Sbostic * and back for another iteration. 273*34472Sbostic */ 274*34472Sbosticsd4: decl r2 # Binary exponent 275*34472Sbostic aoblss $0,r5,sd2 276*34472Sbostic/* 277*34472Sbostic * We now have the following: 278*34472Sbostic * 279*34472Sbostic * r0: high-order half of a 64-bit integer 280*34472Sbostic * r1: load-order half of the same 64-bit integer 281*34472Sbostic * r2: a binary exponent 282*34472Sbostic * 283*34472Sbostic * Our final result is the integer represented by (r0,r1) 284*34472Sbostic * multiplied by 2 to the power contained in r2. 285*34472Sbostic * We will transform (r0,r1) into a floating-point value, 286*34472Sbostic * set the sign appropriately, and let ldexp do the 287*34472Sbostic * rest of the work. 288*34472Sbostic * 289*34472Sbostic * Step 1: if the high-order bit (excluding the sign) of 290*34472Sbostic * the high-order half (r0) is 1, then we have 63 bits of 291*34472Sbostic * fraction, too many to convert easily. However, we also 292*34472Sbostic * know we won't need them all, so we will just throw the 293*34472Sbostic * low-order bit away (and adjust the exponent appropriately). 294*34472Sbostic */ 295*34472Sbosticcm0: bbc $30,r0,cm1 # jump if no adjustment needed 296*34472Sbostic shrq $1,r0,r0 # lose the low-order bit 297*34472Sbostic incl r2 # increase the exponent to compensate 298*34472Sbostic/* 299*34472Sbostic * Step 2: split the 62-bit number in (r0,r1) into two 300*34472Sbostic * 31-bit positive quantities 301*34472Sbostic */ 302*34472Sbosticcm1: shlq $1,r0,r0 # put the high-order bits in r0 303*34472Sbostic # and a 0 in the bottom of r1 304*34472Sbostic shrl $1,r1,r1 # right-justify the bits in r1 305*34472Sbostic # moving 0 into the sign bit. 306*34472Sbostic/* 307*34472Sbostic * Step 3: convert both halves to floating point 308*34472Sbostic */ 309*34472Sbostic cvld r1 310*34472Sbostic std r6 # low-order part in r6-r7 311*34472Sbostic cvld r0 312*34472Sbostic std r0 # high-order part in r0-r1 313*34472Sbostic/* 314*34472Sbostic * Step 4: multiply the high order part by 2**31 and combine them 315*34472Sbostic */ 316*34472Sbostic ldd two31 317*34472Sbostic muld r0 # multiply 318*34472Sbostic addd r6 # combine 319*34472Sbostic/* 320*34472Sbostic * Step 5: if appropriate, negate the floating value 321*34472Sbostic */ 322*34472Sbostic bbc $msign,r3,cm2 # Jump if mantissa not signed 323*34472Sbostic negd # If negative, make it so 324*34472Sbostic/* 325*34472Sbostic * Step 6: call ldexp to complete the job 326*34472Sbostic */ 327*34472Sbosticcm2: pushl r2 # Put exponent in parameter list 328*34472Sbostic pushd # and also mantissa 329*34472Sbostic calls $3,_ldexp # go combine them 330*34472Sbostic 331*34472Sbosticexit: 332*34472Sbostic ret 333*34472Sbostic 334*34472Sbostic .align 2 335*34472Sbostictwo31: .long 0x50000000 # (=2147483648) 2 ** 31 in floating-point 336*34472Sbostic .long 0 # so atof doesn't have to convert it 337