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