134472Sbostic/* 234472Sbostic * Copyright (c) 1988 Regents of the University of California. 335305Sbostic * All rights reserved. 435305Sbostic * 5*42642Sbostic * %sccs.include.redist.c% 634472Sbostic */ 734472Sbostic 834472Sbostic#if defined(LIBC_SCCS) && !defined(lint) 9*42642Sbostic .asciz "@(#)atof.s 5.3 (Berkeley) 06/01/90" 1034472Sbostic#endif /* LIBC_SCCS and not lint */ 1134472Sbostic 1234472Sbostic#include "DEFS.h" 1334472Sbostic 1434472Sbostic/* 1534472Sbostic * atof: convert ascii to floating 1634472Sbostic * 1734472Sbostic * C usage: 1834472Sbostic * 1934472Sbostic * double atof (s) 2034472Sbostic * char *s; 2134472Sbostic * 2234472Sbostic * Register usage: 2334472Sbostic * 2434472Sbostic * r0-1: value being developed 2534472Sbostic * r2: first section: pointer to the next character 2634472Sbostic * second section: binary exponent 2734472Sbostic * r3: flags 2834472Sbostic * r4: first section: the current character 2934472Sbostic * second section: scratch 3034472Sbostic * r5: the decimal exponent 3134472Sbostic * r6-7: scratch 3234472Sbostic */ 3334472Sbostic .set msign,0 # mantissa has negative sign 3434472Sbostic .set esign,1 # exponent has negative sign 3534472Sbostic .set decpt,2 # decimal point encountered 3634472Sbostic 3734472SbosticENTRY(atof, R6|R7) 3834472Sbostic/* 3934472Sbostic * Initialization 4034472Sbostic */ 4134472Sbostic clrl r3 # All flags start out false 4234472Sbostic movl 4(fp),r2 # Address the first character 4334472Sbostic clrl r5 # Clear starting exponent 4434472Sbostic/* 4534472Sbostic * Skip leading white space 4634472Sbostic */ 4734472Sbosticsk0: movzbl (r2),r4 # Fetch the next (first) character 4834472Sbostic incl r2 4934472Sbostic cmpb $' ,r4 # Is it blank? 5034472Sbostic beql sk0 # ...yes 5134472Sbostic cmpb r4,$8 # 8 is lowest of white-space group 5234472Sbostic blss sk1 # Jump if char too low to be white space 5334472Sbostic cmpb r4,$13 # 13 is highest of white-space group 5434472Sbostic bleq sk0 # Jump if character is white space 5534472Sbosticsk1: 5634472Sbostic/* 5734472Sbostic * Check for a sign 5834472Sbostic */ 5934472Sbostic cmpb $'+,r4 # Positive sign? 6034472Sbostic beql cs1 # ... yes 6134472Sbostic cmpb $'-,r4 # Negative sign? 6234472Sbostic bneq cs2 # ... no 6334472Sbostic orb2 $1<msign,r3 # Indicate a negative mantissa 6434472Sbosticcs1: movzbl (r2),r4 # Skip the character 6534472Sbostic incl r2 6634472Sbosticcs2: 6734472Sbostic/* 6834472Sbostic * Accumulate digits, keeping track of the exponent 6934472Sbostic */ 7034472Sbostic clrl r1 7134472Sbostic clrl r0 # Clear the accumulator 7234472Sbosticad0: cmpb r4,$'0 # Do we have a digit? 7334472Sbostic blss ad4 # ... no, too small 7434472Sbostic cmpb r4,$'9 7534472Sbostic bgtr ad4 # ... no, too large 7634472Sbostic/* 7734472Sbostic * We got a digit. Accumulate it 7834472Sbostic */ 7934472Sbostic cmpl r0,$214748364 # Would this digit cause overflow? 8034472Sbostic bgeq ad1 # ... yes 8134472Sbostic/* 8234472Sbostic * Multiply (r0,r1) by 10. This is done by developing 8334472Sbostic * (r0,r1)*2 in (r6,r7), shifting (r0,r1) left three bits, 8434472Sbostic * and adding the two quadwords. 8534472Sbostic */ 8634472Sbostic shlq $1,r0,r6 # (r6,r7)=(r0,r1)*2 8734472Sbostic shlq $3,r0,r0 # (r0,r1)=(r0,r1)*8 8834472Sbostic addl2 r7,r1 # Add low halves 8934472Sbostic adwc r6,r0 # Add high halves 9034472Sbostic/* 9134472Sbostic * Add in the digit 9234472Sbostic */ 9334472Sbostic subl2 $'0,r4 # Get the digit value 9434472Sbostic addl2 r4,r1 # Add it into the accumulator 9534472Sbostic adwc $0,r0 # Possible carry into high half 9634472Sbostic brb ad2 # Join common code 9734472Sbostic/* 9834472Sbostic * Here when the digit won't fit in the accumulator 9934472Sbostic */ 10034472Sbosticad1: incl r5 # Ignore the digit, bump exponent 10134472Sbostic/* 10234472Sbostic * If we have seen a decimal point, decrease the exponent by 1 10334472Sbostic */ 10434472Sbosticad2: bbc $decpt,r3,ad3 # Jump if decimal point not seen 10534472Sbostic decl r5 # Decrease exponent 10634472Sbosticad3: 10734472Sbostic/* 10834472Sbostic * Fetch the next character, back for more 10934472Sbostic */ 11034472Sbostic movzbl (r2),r4 # Fetch 11134472Sbostic incl r2 11234472Sbostic brb ad0 # Try again 11334472Sbostic/* 11434472Sbostic * Not a digit. Could it be a decimal point? 11534472Sbostic */ 11634472Sbosticad4: cmpb r4,$'. # If it's not a decimal point, either it's 11734472Sbostic bneq ad5 # the end of the number or the start of 11834472Sbostic # the exponent. 11934472Sbostic bbs $decpt,r3,ad5 12034472Sbostic orb2 $1<decpt,r3 # If it IS a decimal point, we record that 12134472Sbostic brb ad3 # we've seen one, and keep collecting 12234472Sbostic # digits if it is the first one. 12334472Sbostic 12434472Sbostic/* 12534472Sbostic * Check for an exponent 12634472Sbostic */ 12734472Sbosticad5: clrl r6 # Initialize the exponent accumulator 12834472Sbostic 12934472Sbostic cmpb r4,$'e # We allow both lower case e 13034472Sbostic beql ex1 # ... and ... 13134472Sbostic cmpb r4,$'E # upper-case E 13234472Sbostic bneq ex7 13334472Sbostic/* 13434472Sbostic * Does the exponent have a sign? 13534472Sbostic */ 13634472Sbosticex1: movzbl (r2),r4 # Get next character 13734472Sbostic incl r2 13834472Sbostic cmpb r4,$'+ # Positive sign? 13934472Sbostic beql ex2 # ... yes ... 14034472Sbostic cmpb r4,$'- # Negative sign? 14134472Sbostic bneq ex3 # ... no ... 14234472Sbostic orb2 $1<esign,r3 # Indicate exponent is negative 14334472Sbosticex2: movzbl (r2),r4 # Grab the next character 14434472Sbostic incl r2 14534472Sbostic/* 14634472Sbostic * Accumulate exponent digits in r6 14734472Sbostic */ 14834472Sbosticex3: cmpb r4,$'0 # A digit is within the range 14934472Sbostic blss ex4 # '0' through 15034472Sbostic cmpb r4,$'9 # '9', 15134472Sbostic bgtr ex4 # inclusive. 15234472Sbostic cmpl r6,$214748364 # Exponent outrageously large already? 15334472Sbostic bgeq ex2 # ... yes 15434472Sbostic moval (r6)[r6],r6 # r6 *= 5 15534472Sbostic movaw -'0(r4)[r6],r6 # r6 = r6 * 2 + r4 - '0' 15634472Sbostic brb ex2 # Go 'round again 15734472Sbosticex4: 15834472Sbostic/* 15934472Sbostic * Now get the final exponent and force it within a reasonable 16034472Sbostic * range so our scaling loops don't take forever for values 16134472Sbostic * that will ultimately cause overflow or underflow anyway. 16234472Sbostic * A tight check on over/underflow will be done by ldexp. 16334472Sbostic */ 16434472Sbostic bbc $esign,r3,ex5 # Jump if exponent not negative 16534472Sbostic mnegl r6,r6 # If sign, negate exponent 16634472Sbosticex5: addl2 r6,r5 # Add given exponent to calculated exponent 16734472Sbostic cmpl r5,$-100 # Absurdly small? 16834472Sbostic bgtr ex6 # ... no 16934472Sbostic movl $-100,r5 # ... yes, force within limit 17034472Sbosticex6: cmpl r5,$100 # Absurdly large? 17134472Sbostic blss ex7 # ... no 17234472Sbostic movl $100,r5 # ... yes, force within bounds 17334472Sbosticex7: 17434472Sbostic/* 17534472Sbostic * Our number has now been reduced to a mantissa and an exponent. 17634472Sbostic * The mantissa is a 63-bit positive binary integer in r0,r1, 17734472Sbostic * and the exponent is a signed power of 10 in r5. The msign 17834472Sbostic * bit in r3 will be on if the mantissa should ultimately be 17934472Sbostic * considered negative. 18034472Sbostic * 18134472Sbostic * We now have to convert it to a standard format floating point 18234472Sbostic * number. This will be done by accumulating a binary exponent 18334472Sbostic * in r2, as we progressively get r5 closer to zero. 18434472Sbostic * 18534472Sbostic * Don't bother scaling if the mantissa is zero 18634472Sbostic */ 18734472Sbostic tstl r1 18834472Sbostic bneq 1f 18934472Sbostic tstl r0 # Mantissa zero? 19034472Sbostic jeql exit # ... yes 19134472Sbostic 19234472Sbostic1: clrl r2 # Initialize binary exponent 19334472Sbostic tstl r5 # Which way to scale? 19434472Sbostic bleq sd0 # Scale down if decimal exponent <= 0 19534472Sbostic/* 19634472Sbostic * Scale up by "multiplying" r0,r1 by 10 as many times as necessary, 19734472Sbostic * as follows: 19834472Sbostic * 19934472Sbostic * Step 1: Shift r0,r1 right as necessary to ensure that no 20034472Sbostic * overflow can occur when multiplying. 20134472Sbostic */ 20234472Sbosticsu0: cmpl r0,$429496729 # Compare high word to (2**31)/5 20334472Sbostic blss su1 # Jump out if guaranteed safe 20434472Sbostic shrq $1,r0,r0 # Else shift right one bit 20534472Sbostic incl r2 # bump exponent to compensate 20634472Sbostic brb su0 # and go back to test again. 20734472Sbostic/* 20834472Sbostic * Step 2: Multiply r0,r1 by 5, by appropriate shifting and 20934472Sbostic * double-precision addition 21034472Sbostic */ 21134472Sbosticsu1: shlq $2,r0,r6 # (r6,r7) := (r0,r1) * 4 21234472Sbostic addl2 r7,r1 # Add low-order halves 21334472Sbostic adwc r6,r0 # and high-order halves 21434472Sbostic/* 21534472Sbostic * Step 3: Increment the binary exponent to take care of the final 21634472Sbostic * factor of 2, and go back if we still need to scale more. 21734472Sbostic */ 21834472Sbostic incl r2 # Increment the exponent 21934472Sbostic decl r5 # ...sobgtr r5,su0 22034472Sbostic bgtr su0 # and back for more (maybe) 22134472Sbostic 22234472Sbostic brb cm0 # Merge to build final value 22334472Sbostic 22434472Sbostic/* 22534472Sbostic * Scale down. We must "divide" r0,r1 by 10 as many times 22634472Sbostic * as needed, as follows: 22734472Sbostic * 22834472Sbostic * Step 0: Right now, the condition codes reflect the state 22934472Sbostic * of r5. If it's zero, we are done. 23034472Sbostic */ 23134472Sbosticsd0: beql cm0 # If finished, build final number 23234472Sbostic/* 23334472Sbostic * Step 1: Shift r0,r1 left until the high-order bit (not counting 23434472Sbostic * the sign bit) is nonzero, so that the division will preserve 23534472Sbostic * as much precision as possible. 23634472Sbostic */ 23734472Sbostic tstl r0 # Is the entire high-order half zero? 23834472Sbostic bneq sd2 # ...no, go shift one bit at a time 23934472Sbostic shlq $30,r0,r0 # ...yes, shift left 30, 24034472Sbostic subl2 $30,r2 # decrement the exponent to compensate, 24134472Sbostic # and now it's known to be safe to shift 24234472Sbostic # at least once more. 24334472Sbosticsd1: shlq $1,r0,r0 # Shift (r0,r1) left one, and 24434472Sbostic decl r2 # decrement the exponent to compensate 24534472Sbosticsd2: bbc $30,r0,sd1 # If the high-order bit is off, go shift 24634472Sbostic/* 24734472Sbostic * Step 2: Divide the high-order part of (r0,r1) by 5, 24834472Sbostic * giving a quotient in r1 and a remainder in r7. 24934472Sbostic */ 25034472Sbosticsd3: movl r0,r7 # Copy the high-order part 25134472Sbostic clrl r6 # Zero-extend to 64 bits 25234472Sbostic ediv $5,r6,r0,r6 # Divide (cannot overflow) 25334472Sbostic/* 25434472Sbostic * Step 3: Divide the low-order part of (r0,r1) by 5, 25534472Sbostic * using the remainder from step 2 for rounding. 25634472Sbostic * Note that the result of this computation is unsigned, 25734472Sbostic * so we have to allow for the fact that an ordinary division 25834472Sbostic * by 5 could overflow. We make allowance by dividing by 10, 25934472Sbostic * multiplying the quotient by 2, and using the remainder 26034472Sbostic * to adjust the modified quotient. 26134472Sbostic */ 26234472Sbostic addl3 $2,r1,r7 # Dividend is low part of (r0,r1) plus 26334472Sbostic adwc $0,r6 # 2 for rounding plus 26434472Sbostic # (2**32) * previous remainder 26534472Sbostic ediv $10,r6,r1,r7 # r1 := quotient, r7 := remainder. 26634472Sbostic addl2 r1,r1 # Make r1 result of dividing by 5 26734472Sbostic cmpl r7,$5 # If remainder is 5 or greater, 26834472Sbostic blss sd4 # increment the adjustted quotient. 26934472Sbostic incl r1 27034472Sbostic/* 27134472Sbostic * Step 4: Increment the decimal exponent, decrement the binary 27234472Sbostic * exponent (to make the division by 5 into a division by 10), 27334472Sbostic * and back for another iteration. 27434472Sbostic */ 27534472Sbosticsd4: decl r2 # Binary exponent 27634472Sbostic aoblss $0,r5,sd2 27734472Sbostic/* 27834472Sbostic * We now have the following: 27934472Sbostic * 28034472Sbostic * r0: high-order half of a 64-bit integer 28134472Sbostic * r1: load-order half of the same 64-bit integer 28234472Sbostic * r2: a binary exponent 28334472Sbostic * 28434472Sbostic * Our final result is the integer represented by (r0,r1) 28534472Sbostic * multiplied by 2 to the power contained in r2. 28634472Sbostic * We will transform (r0,r1) into a floating-point value, 28734472Sbostic * set the sign appropriately, and let ldexp do the 28834472Sbostic * rest of the work. 28934472Sbostic * 29034472Sbostic * Step 1: if the high-order bit (excluding the sign) of 29134472Sbostic * the high-order half (r0) is 1, then we have 63 bits of 29234472Sbostic * fraction, too many to convert easily. However, we also 29334472Sbostic * know we won't need them all, so we will just throw the 29434472Sbostic * low-order bit away (and adjust the exponent appropriately). 29534472Sbostic */ 29634472Sbosticcm0: bbc $30,r0,cm1 # jump if no adjustment needed 29734472Sbostic shrq $1,r0,r0 # lose the low-order bit 29834472Sbostic incl r2 # increase the exponent to compensate 29934472Sbostic/* 30034472Sbostic * Step 2: split the 62-bit number in (r0,r1) into two 30134472Sbostic * 31-bit positive quantities 30234472Sbostic */ 30334472Sbosticcm1: shlq $1,r0,r0 # put the high-order bits in r0 30434472Sbostic # and a 0 in the bottom of r1 30534472Sbostic shrl $1,r1,r1 # right-justify the bits in r1 30634472Sbostic # moving 0 into the sign bit. 30734472Sbostic/* 30834472Sbostic * Step 3: convert both halves to floating point 30934472Sbostic */ 31034472Sbostic cvld r1 31134472Sbostic std r6 # low-order part in r6-r7 31234472Sbostic cvld r0 31334472Sbostic std r0 # high-order part in r0-r1 31434472Sbostic/* 31534472Sbostic * Step 4: multiply the high order part by 2**31 and combine them 31634472Sbostic */ 31734472Sbostic ldd two31 31834472Sbostic muld r0 # multiply 31934472Sbostic addd r6 # combine 32034472Sbostic/* 32134472Sbostic * Step 5: if appropriate, negate the floating value 32234472Sbostic */ 32334472Sbostic bbc $msign,r3,cm2 # Jump if mantissa not signed 32434472Sbostic negd # If negative, make it so 32534472Sbostic/* 32634472Sbostic * Step 6: call ldexp to complete the job 32734472Sbostic */ 32834472Sbosticcm2: pushl r2 # Put exponent in parameter list 32934472Sbostic pushd # and also mantissa 33034472Sbostic calls $3,_ldexp # go combine them 33134472Sbostic 33234472Sbosticexit: 33334472Sbostic ret 33434472Sbostic 33534472Sbostic .align 2 33634472Sbostictwo31: .long 0x50000000 # (=2147483648) 2 ** 31 in floating-point 33734472Sbostic .long 0 # so atof doesn't have to convert it 338