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