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