xref: /csrg-svn/lib/libc/vax/stdlib/atof.s (revision 42638)
121420Sdist/*
221420Sdist * Copyright (c) 1980 Regents of the University of California.
334480Sbostic * All rights reserved.
434480Sbostic *
5*42638Sbostic * %sccs.include.redist.c%
621420Sdist */
713499Ssam
834819Sbostic#if defined(LIBC_SCCS) && !defined(lint)
9*42638Sbostic	.asciz "@(#)atof.s	5.6 (Berkeley) 06/01/90"
1034819Sbostic#endif /* LIBC_SCCS and not lint */
1121420Sdist
1213499Ssam#include "DEFS.h"
1313499Ssam
1413499Ssam/*
1513499Ssam *	atof: convert ascii to floating
1613499Ssam *
1713499Ssam *	C usage:
1813499Ssam *
1913499Ssam *		double atof (s)
2013499Ssam *		char *s;
2113499Ssam *
2213499Ssam *	Register usage:
2313499Ssam *
2413499Ssam *		r0-1:	value being developed
2513499Ssam *		r2:	first section: pointer to the next character
2613499Ssam *			second section: binary exponent
2713499Ssam *		r3:	flags
2813499Ssam *		r4:	first section: the current character
2913499Ssam *			second section: scratch
3013499Ssam *		r5:	the decimal exponent
3113499Ssam *		r6-7:	scratch
3213499Ssam */
3312208Ssam	.set	msign,0		# mantissa has negative sign
3412208Ssam	.set	esign,1		# exponent has negative sign
3512208Ssam	.set	decpt,2		# decimal point encountered
3612208Ssam
3717328SsamENTRY(atof, R6|R7)
3813499Ssam/*
3913499Ssam *	Initialization
4013499Ssam */
4112208Ssam	clrl	r3		# All flags start out false
4212208Ssam	movl	4(ap),r2	# Address the first character
4312208Ssam	clrl	r5		# Clear starting exponent
4413499Ssam/*
4513499Ssam *	Skip leading white space
4613499Ssam */
4712208Ssamsk0:	movzbl	(r2)+,r4	# Fetch the next (first) character
4812208Ssam	cmpb	$' ,r4		# Is it blank?
4912208Ssam	jeql	sk0		#   ...yes
5012208Ssam	cmpb	r4,$8		# 8 is lowest of white-space group
5112208Ssam	jlss	sk1		# Jump if char too low to be white space
5212208Ssam	cmpb	r4,$13		# 13 is highest of white-space group
5312208Ssam	jleq	sk0		# Jump if character is white space
5412208Ssamsk1:
5513499Ssam/*
5613499Ssam *	Check for a sign
5713499Ssam */
5812208Ssam	cmpb	$'+,r4		# Positive sign?
5912208Ssam	jeql	cs1		#   ... yes
6012208Ssam	cmpb	$'-,r4		# Negative sign?
6112208Ssam	jneq	cs2		#   ... no
6212208Ssam	bisb2	$1<msign,r3	# Indicate a negative mantissa
6312208Ssamcs1:	movzbl	(r2)+,r4	# Skip the character
6412208Ssamcs2:
6513499Ssam/*
6613499Ssam *	Accumulate digits, keeping track of the exponent
6713499Ssam */
6812208Ssam	clrq	r0		# Clear the accumulator
6912208Ssamad0:	cmpb	r4,$'0		# Do we have a digit?
7012208Ssam	jlss	ad4		#   ... no, too small
7112208Ssam	cmpb	r4,$'9
7212208Ssam	jgtr	ad4		#   ... no, too large
7313499Ssam/*
7413499Ssam *	We got a digit.  Accumulate it
7513499Ssam */
7612208Ssam	cmpl	r1,$214748364	# Would this digit cause overflow?
7712208Ssam	jgeq	ad1		#   ... yes
7813499Ssam/*
7913499Ssam *	Multiply (r0,r1) by 10.  This is done by developing
8013499Ssam *	(r0,r1)*2 in (r6,r7), shifting (r0,r1) left three bits,
8113499Ssam *	and adding the two quadwords.
8213499Ssam */
8312208Ssam	ashq	$1,r0,r6	# (r6,r7)=(r0,r1)*2
8412208Ssam	ashq	$3,r0,r0	# (r0,r1)=(r0,r1)*8
8512208Ssam	addl2	r6,r0		# Add low halves
8612208Ssam	adwc	r7,r1		# Add high halves
8713499Ssam/*
8813499Ssam *	Add in the digit
8913499Ssam */
9012208Ssam	subl2	$'0,r4		# Get the digit value
9112208Ssam	addl2	r4,r0		# Add it into the accumulator
9212208Ssam	adwc	$0,r1		# Possible carry into high half
9312208Ssam	jbr	ad2		# Join common code
9413499Ssam/*
9513499Ssam *	Here when the digit won't fit in the accumulator
9613499Ssam */
9712208Ssamad1:	incl	r5		# Ignore the digit, bump exponent
9813499Ssam/*
9913499Ssam *	If we have seen a decimal point, decrease the exponent by 1
10013499Ssam */
10112208Ssamad2:	jbc	$decpt,r3,ad3	# Jump if decimal point not seen
10212208Ssam	decl	r5		# Decrease exponent
10312208Ssamad3:
10413499Ssam/*
10513499Ssam *	Fetch the next character, back for more
10613499Ssam */
10712208Ssam	movzbl	(r2)+,r4	# Fetch
10812208Ssam	jbr	ad0		# Try again
10913499Ssam/*
11013499Ssam *	Not a digit.  Could it be a decimal point?
11113499Ssam */
11212208Ssamad4:	cmpb	r4,$'.		# If it's not a decimal point, either it's
11312208Ssam	jneq	ad5		#   the end of the number or the start of
11412208Ssam				#   the exponent.
11512208Ssam	jbcs	$decpt,r3,ad3	# If it IS a decimal point, we record that
11612208Ssam				#   we've seen one, and keep collecting
11712208Ssam				#   digits if it is the first one.
11813499Ssam/*
11913499Ssam *	Check for an exponent
12013499Ssam */
12112208Ssamad5:	clrl	r6		# Initialize the exponent accumulator
12212208Ssam
12312208Ssam	cmpb	r4,$'e		# We allow both lower case e
12412208Ssam	jeql	ex1		#   ... and ...
12512208Ssam	cmpb	r4,$'E		#   upper-case E
12612208Ssam	jneq	ex7
12713499Ssam/*
12813499Ssam *	Does the exponent have a sign?
12913499Ssam */
13012208Ssamex1:	movzbl	(r2)+,r4	# Get next character
13112208Ssam	cmpb	r4,$'+		# Positive sign?
13212208Ssam	jeql	ex2		#   ... yes ...
13312208Ssam	cmpb	r4,$'-		# Negative sign?
13412208Ssam	jneq	ex3		#   ... no ...
13512208Ssam	bisb2	$1<esign,r3	# Indicate exponent is negative
13612208Ssamex2:	movzbl	(r2)+,r4	# Grab the next character
13713499Ssam/*
13813499Ssam *	Accumulate exponent digits in r6
13913499Ssam */
14012208Ssamex3:	cmpb	r4,$'0		# A digit is within the range
14112208Ssam	jlss	ex4		# '0' through
14212208Ssam	cmpb	r4,$'9		# '9',
14312208Ssam	jgtr	ex4		# inclusive.
14412208Ssam	cmpl	r6,$214748364	# Exponent outrageously large already?
14512208Ssam	jgeq	ex2		#   ... yes
14612208Ssam	moval	(r6)[r6],r6	# r6 *= 5
14712208Ssam	movaw	-'0(r4)[r6],r6	# r6 = r6 * 2 + r4 - '0'
14812208Ssam	jbr	ex2		# Go 'round again
14912208Ssamex4:
15013499Ssam/*
15113499Ssam *	Now get the final exponent and force it within a reasonable
15213499Ssam *	range so our scaling loops don't take forever for values
15313499Ssam *	that will ultimately cause overflow or underflow anyway.
15413499Ssam *	A tight check on over/underflow will be done by ldexp.
15513499Ssam */
15612208Ssam	jbc	$esign,r3,ex5	# Jump if exponent not negative
15712208Ssam	mnegl	r6,r6		# If sign, negate exponent
15812208Ssamex5:	addl2	r6,r5		# Add given exponent to calculated exponent
15912208Ssam	cmpl	r5,$-100	# Absurdly small?
16012208Ssam	jgtr	ex6		#   ... no
16112208Ssam	movl	$-100,r5	#   ... yes, force within limit
16212208Ssamex6:	cmpl	r5,$100		# Absurdly large?
16312208Ssam	jlss	ex7		#   ... no
16412208Ssam	movl	$100,r5		#   ... yes, force within bounds
16512208Ssamex7:
16613499Ssam/*
16713499Ssam *	Our number has now been reduced to a mantissa and an exponent.
16813499Ssam *	The mantissa is a 63-bit positive binary integer in r0,r1,
16913499Ssam *	and the exponent is a signed power of 10 in r5.  The msign
17013499Ssam *	bit in r3 will be on if the mantissa should ultimately be
17113499Ssam *	considered negative.
17213499Ssam *
17313499Ssam *	We now have to convert it to a standard format floating point
17413499Ssam *	number.  This will be done by accumulating a binary exponent
17513499Ssam *	in r2, as we progressively get r5 closer to zero.
17613499Ssam *
17713499Ssam *	Don't bother scaling if the mantissa is zero
17813499Ssam */
17912208Ssam	movq	r0,r0		# Mantissa zero?
18012208Ssam	jeql	exit		#   ... yes
18112208Ssam
18212208Ssam	clrl	r2		# Initialize binary exponent
18312208Ssam	tstl	r5		# Which way to scale?
18412208Ssam	jleq	sd0		# Scale down if decimal exponent <= 0
18513499Ssam/*
18613499Ssam *	Scale up by "multiplying" r0,r1 by 10 as many times as necessary,
18713499Ssam *	as follows:
18813499Ssam *
18913499Ssam *	Step 1: Shift r0,r1 right as necessary to ensure that no
19013499Ssam *	overflow can occur when multiplying.
19113499Ssam */
19212208Ssamsu0:	cmpl	r1,$429496729	# Compare high word to (2**31)/5
19312208Ssam	jlss	su1		# Jump out if guaranteed safe
19412208Ssam	ashq	$-1,r0,r0	# Else shift right one bit
19512208Ssam	incl	r2		#    bump exponent to compensate
19612208Ssam	jbr	su0		#    and go back to test again.
19713499Ssam/*
19813499Ssam *	Step 2: Multiply r0,r1 by 5, by appropriate shifting and
19913499Ssam *	double-precision addition
20013499Ssam */
20112208Ssamsu1:	ashq	$2,r0,r6	# (r6,r7) := (r0,r1) * 4
20212208Ssam	addl2	r6,r0		# Add low-order halves
20312208Ssam	adwc	r7,r1		#   and high-order halves
20413499Ssam/*
20513499Ssam *	Step 3: Increment the binary exponent to take care of the final
20613499Ssam *	factor of 2, and go back if we still need to scale more.
20713499Ssam */
20812208Ssam	incl	r2		# Increment the exponent
20912208Ssam	sobgtr	r5,su0		#    and back for more (maybe)
21012208Ssam
21112208Ssam	jbr	cm0		# Merge to build final value
21212208Ssam
21313499Ssam/*
21413499Ssam *	Scale down.  We must "divide" r0,r1 by 10 as many times
21513499Ssam *	as needed, as follows:
21613499Ssam *
21713499Ssam *	Step 0: Right now, the condition codes reflect the state
21813499Ssam *	of r5.  If it's zero, we are done.
21913499Ssam */
22012208Ssamsd0:	jeql	cm0		# If finished, build final number
22113499Ssam/*
22213499Ssam *	Step 1: Shift r0,r1 left until the high-order bit (not counting
22313499Ssam *	the sign bit) is nonzero, so that the division will preserve
22413499Ssam *	as much precision as possible.
22513499Ssam */
22612208Ssam	tstl	r1		# Is the entire high-order half zero?
22712208Ssam	jneq	sd2		#   ...no, go shift one bit at a time
22812208Ssam	ashq	$30,r0,r0	#   ...yes, shift left 30,
22912208Ssam	subl2	$30,r2		#   decrement the exponent to compensate,
23012208Ssam				#   and now it's known to be safe to shift
23112208Ssam				#   at least once more.
23212208Ssamsd1:	ashq	$1,r0,r0	# Shift (r0,r1) left one, and
23312208Ssam	decl	r2		#   decrement the exponent to compensate
23412208Ssamsd2:	jbc	$30,r1,sd1	# If the high-order bit is off, go shift
23513499Ssam/*
23613499Ssam *	Step 2: Divide the high-order part of (r0,r1) by 5,
23713499Ssam *	giving a quotient in r1 and a remainder in r7.
23813499Ssam */
23912208Ssamsd3:	movl	r1,r6		# Copy the high-order part
24012208Ssam	clrl	r7		# Zero-extend to 64 bits
24112208Ssam	ediv	$5,r6,r1,r7	# Divide (cannot overflow)
24213499Ssam/*
24313499Ssam *	Step 3: Divide the low-order part of (r0,r1) by 5,
24413499Ssam *	using the remainder from step 2 for rounding.
24513499Ssam *	Note that the result of this computation is unsigned,
24613499Ssam *	so we have to allow for the fact that an ordinary division
24713499Ssam *	by 5 could overflow.  We make allowance by dividing by 10,
24813499Ssam *	multiplying the quotient by 2, and using the remainder
24913499Ssam *	to adjust the modified quotient.
25013499Ssam */
25112208Ssam	addl3	$2,r0,r6	# Dividend is low part of (r0,r1) plus
25212208Ssam	adwc	$0,r7		#  2 for rounding plus
25312208Ssam				#  (2**32) * previous remainder
25412208Ssam	ediv	$10,r6,r0,r6	# r0 := quotient, r6 := remainder.
25512208Ssam	addl2	r0,r0		# Make r0 result of dividing by 5
25612208Ssam	cmpl	r6,$5		# If remainder is 5 or greater,
25712208Ssam	jlss	sd4		#   increment the adjustted quotient.
25812208Ssam	incl	r0
25913499Ssam/*
26013499Ssam *	Step 4: Increment the decimal exponent, decrement the binary
26113499Ssam *	exponent (to make the division by 5 into a division by 10),
26213499Ssam *	and back for another iteration.
26313499Ssam */
26412208Ssamsd4:	decl	r2		# Binary exponent
26512208Ssam	aoblss	$0,r5,sd2
26613499Ssam/*
26713499Ssam *	We now have the following:
26813499Ssam *
26913499Ssam *	r0:	low-order half of a 64-bit integer
27013499Ssam *	r1:	high-order half of the same 64-bit integer
27113499Ssam *	r2:	a binary exponent
27213499Ssam *
27313499Ssam *	Our final result is the integer represented by (r0,r1)
27413499Ssam *	multiplied by 2 to the power contained in r2.
27513499Ssam *	We will transform (r0,r1) into a floating-point value,
27613499Ssam *	set the sign appropriately, and let ldexp do the
27713499Ssam *	rest of the work.
27813499Ssam *
27913499Ssam *	Step 1: if the high-order bit (excluding the sign) of
28013499Ssam *	the high-order half (r1) is 1, then we have 63 bits of
28113499Ssam *	fraction, too many to convert easily.  However, we also
28213499Ssam *	know we won't need them all, so we will just throw the
28313499Ssam *	low-order bit away (and adjust the exponent appropriately).
28413499Ssam */
28512208Ssamcm0:	jbc	$30,r1,cm1	# jump if no adjustment needed
28612208Ssam	ashq	$-1,r0,r0	# lose the low-order bit
28712208Ssam	incl	r2		# increase the exponent to compensate
28813499Ssam/*
28913499Ssam *	Step 2: split the 62-bit number in (r0,r1) into two
29013499Ssam *	31-bit positive quantities
29113499Ssam */
29212208Ssamcm1:	ashq	$1,r0,r0	# put the high-order bits in r1
29312208Ssam				#   and a 0 in the bottom of r0
29412208Ssam	rotl	$-1,r0,r0	# right-justify the bits in r0
29512208Ssam				#   moving the 0 from the ashq
29612208Ssam				#   into the sign bit.
29713499Ssam/*
29813499Ssam *	Step 3: convert both halves to floating point
29913499Ssam */
30012208Ssam	cvtld	r0,r6		# low-order part in r6-r7
30112208Ssam	cvtld	r1,r0		# high-order part in r0-r1
30213499Ssam/*
30313499Ssam *	Step 4: multiply the high order part by 2**31 and combine them
30413499Ssam */
30512208Ssam	muld2	two31,r0	# multiply
30612208Ssam	addd2	r6,r0		# combine
30713499Ssam/*
30813499Ssam *	Step 5: if appropriate, negate the floating value
30913499Ssam */
31012208Ssam	jbc	$msign,r3,cm2	# Jump if mantissa not signed
31112208Ssam	mnegd	r0,r0		# If negative, make it so
31213499Ssam/*
31313499Ssam *	Step 6: call ldexp to complete the job
31413499Ssam */
31512208Ssamcm2:	pushl	r2		# Put exponent in parameter list
31612208Ssam	movd	r0,-(sp)	#    and also mantissa
31712208Ssam	calls	$3,_ldexp	# go combine them
31812208Ssam
31913499Ssamexit:
32013499Ssam	ret
32117328Ssam
32217328Ssam	.align	2
32317328Ssamtwo31:	.word	0x5000		# 2 ** 31
32417328Ssam	.word	0		# (=2147483648)
32517328Ssam	.word	0		# in floating-point
32617328Ssam	.word	0		# (so atof doesn't have to convert it)
327