0.pre7.86:
[sbcl.git] / src / code / float.lisp
1 ;;;; This file contains the definitions of float specific number
2 ;;;; support (other than irrational stuff, which is in irrat.) There is
3 ;;;; code in here that assumes there are only two float formats: IEEE
4 ;;;; single and double. (Long-float support has been added, but bugs
5 ;;;; may still remain due to old code which assumes this dichotomy.)
6
7 ;;;; This software is part of the SBCL system. See the README file for
8 ;;;; more information.
9 ;;;;
10 ;;;; This software is derived from the CMU CL system, which was
11 ;;;; written at Carnegie Mellon University and released into the
12 ;;;; public domain. The software is in the public domain and is
13 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
14 ;;;; files for more information.
15
16 (in-package "SB!KERNEL")
17 \f
18 ;;;; utilities
19
20 (eval-when (:compile-toplevel :load-toplevel :execute)
21
22 ;;; These functions let us create floats from bits with the
23 ;;; significand uniformly represented as an integer. This is less
24 ;;; efficient for double floats, but is more convenient when making
25 ;;; special values, etc.
26 (defun single-from-bits (sign exp sig)
27   (declare (type bit sign) (type (unsigned-byte 24) sig)
28            (type (unsigned-byte 8) exp))
29   (make-single-float
30    (dpb exp sb!vm:single-float-exponent-byte
31         (dpb sig sb!vm:single-float-significand-byte
32              (if (zerop sign) 0 -1)))))
33 (defun double-from-bits (sign exp sig)
34   (declare (type bit sign) (type (unsigned-byte 53) sig)
35            (type (unsigned-byte 11) exp))
36   (make-double-float (dpb exp sb!vm:double-float-exponent-byte
37                           (dpb (ash sig -32) sb!vm:double-float-significand-byte
38                                (if (zerop sign) 0 -1)))
39                      (ldb (byte 32 0) sig)))
40 #!+(and long-float x86)
41 (defun long-from-bits (sign exp sig)
42   (declare (type bit sign) (type (unsigned-byte 64) sig)
43            (type (unsigned-byte 15) exp))
44   (make-long-float (logior (ash sign 15) exp)
45                    (ldb (byte 32 32) sig)
46                    (ldb (byte 32 0) sig)))
47                                         
48 ) ; EVAL-WHEN
49 \f
50 ;;;; float parameters
51
52 (defconstant least-positive-single-float (single-from-bits 0 0 1))
53 (defconstant least-positive-short-float least-positive-single-float)
54 (defconstant least-negative-single-float (single-from-bits 1 0 1))
55 (defconstant least-negative-short-float least-negative-single-float)
56 (defconstant least-positive-double-float (double-from-bits 0 0 1))
57 #!-long-float
58 (defconstant least-positive-long-float least-positive-double-float)
59 #!+(and long-float x86)
60 (defconstant least-positive-long-float (long-from-bits 0 0 1))
61 (defconstant least-negative-double-float (double-from-bits 1 0 1))
62 #!-long-float
63 (defconstant least-negative-long-float least-negative-double-float)
64 #!+(and long-float x86)
65 (defconstant least-negative-long-float (long-from-bits 1 0 1))
66
67 (defconstant least-positive-normalized-single-float
68   (single-from-bits 0 sb!vm:single-float-normal-exponent-min 0))
69 (defconstant least-positive-normalized-short-float
70   least-positive-normalized-single-float)
71 (defconstant least-negative-normalized-single-float
72   (single-from-bits 1 sb!vm:single-float-normal-exponent-min 0))
73 (defconstant least-negative-normalized-short-float
74   least-negative-normalized-single-float)
75 (defconstant least-positive-normalized-double-float
76   (double-from-bits 0 sb!vm:double-float-normal-exponent-min 0))
77 #!-long-float
78 (defconstant least-positive-normalized-long-float
79   least-positive-normalized-double-float)
80 #!+(and long-float x86)
81 (defconstant least-positive-normalized-long-float
82   (long-from-bits 0 sb!vm:long-float-normal-exponent-min
83                   (ash sb!vm:long-float-hidden-bit 32)))
84 (defconstant least-negative-normalized-double-float
85   (double-from-bits 1 sb!vm:double-float-normal-exponent-min 0))
86 #!-long-float
87 (defconstant least-negative-normalized-long-float
88   least-negative-normalized-double-float)
89 #!+(and long-float x86)
90 (defconstant least-negative-normalized-long-float
91   (long-from-bits 1 sb!vm:long-float-normal-exponent-min
92                   (ash sb!vm:long-float-hidden-bit 32)))
93
94 (defconstant most-positive-single-float
95   (single-from-bits 0 sb!vm:single-float-normal-exponent-max
96                     (ldb sb!vm:single-float-significand-byte -1)))
97 (defconstant most-positive-short-float most-positive-single-float)
98 (defconstant most-negative-single-float
99   (single-from-bits 1 sb!vm:single-float-normal-exponent-max
100                     (ldb sb!vm:single-float-significand-byte -1)))
101 (defconstant most-negative-short-float most-negative-single-float)
102 (defconstant most-positive-double-float
103   (double-from-bits 0 sb!vm:double-float-normal-exponent-max
104                     (ldb (byte sb!vm:double-float-digits 0) -1)))
105 #!-long-float
106 (defconstant most-positive-long-float most-positive-double-float)
107 #!+(and long-float x86)
108 (defconstant most-positive-long-float
109   (long-from-bits 0 sb!vm:long-float-normal-exponent-max
110                   (ldb (byte sb!vm:long-float-digits 0) -1)))
111 (defconstant most-negative-double-float
112   (double-from-bits 1 sb!vm:double-float-normal-exponent-max
113                     (ldb (byte sb!vm:double-float-digits 0) -1)))
114 #!-long-float
115 (defconstant most-negative-long-float most-negative-double-float)
116 #!+(and long-float x86)
117 (defconstant most-negative-long-float
118   (long-from-bits 1 sb!vm:long-float-normal-exponent-max
119                   (ldb (byte sb!vm:long-float-digits 0) -1)))
120
121 ;;; We don't want to do these DEFCONSTANTs at cross-compilation time,
122 ;;; because the cross-compilation host might not support floating
123 ;;; point infinities. Putting them inside a LET removes
124 ;;; toplevel-formness, so that any EVAL-WHEN trickiness in the
125 ;;; DEFCONSTANT forms is suppressed.
126 (let ()
127 (defconstant single-float-positive-infinity
128   (single-from-bits 0 (1+ sb!vm:single-float-normal-exponent-max) 0))
129 (defconstant short-float-positive-infinity single-float-positive-infinity)
130 (defconstant single-float-negative-infinity
131   (single-from-bits 1 (1+ sb!vm:single-float-normal-exponent-max) 0))
132 (defconstant short-float-negative-infinity single-float-negative-infinity)
133 (defconstant double-float-positive-infinity
134   (double-from-bits 0 (1+ sb!vm:double-float-normal-exponent-max) 0))
135 #!+(not long-float)
136 (defconstant long-float-positive-infinity double-float-positive-infinity)
137 #!+(and long-float x86)
138 (defconstant long-float-positive-infinity
139   (long-from-bits 0 (1+ sb!vm:long-float-normal-exponent-max)
140                   (ash sb!vm:long-float-hidden-bit 32)))
141 (defconstant double-float-negative-infinity
142   (double-from-bits 1 (1+ sb!vm:double-float-normal-exponent-max) 0))
143 #!+(not long-float)
144 (defconstant long-float-negative-infinity double-float-negative-infinity)
145 #!+(and long-float x86)
146 (defconstant long-float-negative-infinity
147   (long-from-bits 1 (1+ sb!vm:long-float-normal-exponent-max)
148                   (ash sb!vm:long-float-hidden-bit 32)))
149 ) ; LET-to-suppress-possible-EVAL-WHENs
150
151 (defconstant single-float-epsilon
152   (single-from-bits 0 (- sb!vm:single-float-bias
153                          (1- sb!vm:single-float-digits)) 1))
154 (defconstant short-float-epsilon single-float-epsilon)
155 (defconstant single-float-negative-epsilon
156   (single-from-bits 0 (- sb!vm:single-float-bias sb!vm:single-float-digits) 1))
157 (defconstant short-float-negative-epsilon single-float-negative-epsilon)
158 (defconstant double-float-epsilon
159   (double-from-bits 0 (- sb!vm:double-float-bias
160                          (1- sb!vm:double-float-digits)) 1))
161 #!-long-float
162 (defconstant long-float-epsilon double-float-epsilon)
163 #!+(and long-float x86)
164 (defconstant long-float-epsilon
165   (long-from-bits 0 (- sb!vm:long-float-bias (1- sb!vm:long-float-digits))
166                   (+ 1 (ash sb!vm:long-float-hidden-bit 32))))
167 (defconstant double-float-negative-epsilon
168   (double-from-bits 0 (- sb!vm:double-float-bias sb!vm:double-float-digits) 1))
169 #!-long-float
170 (defconstant long-float-negative-epsilon double-float-negative-epsilon)
171 #!+(and long-float x86)
172 (defconstant long-float-negative-epsilon
173   (long-from-bits 0 (- sb!vm:long-float-bias sb!vm:long-float-digits)
174                   (+ 1 (ash sb!vm:long-float-hidden-bit 32))))
175 \f
176 ;;;; float predicates and environment query
177
178 #!-sb-fluid
179 (declaim (maybe-inline float-denormalized-p float-infinity-p float-nan-p
180                        float-trapping-nan-p))
181
182 (defun float-denormalized-p (x)
183   #!+sb-doc
184   "Return true if the float X is denormalized."
185   (number-dispatch ((x float))
186     ((single-float)
187      (and (zerop (ldb sb!vm:single-float-exponent-byte (single-float-bits x)))
188           (not (zerop x))))
189     ((double-float)
190      (and (zerop (ldb sb!vm:double-float-exponent-byte
191                       (double-float-high-bits x)))
192           (not (zerop x))))
193     #!+(and long-float x86)
194     ((long-float)
195      (and (zerop (ldb sb!vm:long-float-exponent-byte (long-float-exp-bits x)))
196           (not (zerop x))))))
197
198 (macrolet ((def-frob (name doc single double #!+(and long-float x86) long)
199              `(defun ,name (x)
200                 ,doc
201                 (number-dispatch ((x float))
202                   ((single-float)
203                    (let ((bits (single-float-bits x)))
204                      (and (> (ldb sb!vm:single-float-exponent-byte bits)
205                              sb!vm:single-float-normal-exponent-max)
206                           ,single)))
207                   ((double-float)
208                    (let ((hi (double-float-high-bits x))
209                          (lo (double-float-low-bits x)))
210                      (declare (ignorable lo))
211                      (and (> (ldb sb!vm:double-float-exponent-byte hi)
212                              sb!vm:double-float-normal-exponent-max)
213                           ,double)))
214                   #!+(and long-float x86)
215                   ((long-float)
216                    (let ((exp (long-float-exp-bits x))
217                          (hi (long-float-high-bits x))
218                          (lo (long-float-low-bits x)))
219                      (declare (ignorable lo))
220                      (and (> (ldb sb!vm:long-float-exponent-byte exp)
221                              sb!vm:long-float-normal-exponent-max)
222                           ,long)))))))
223
224   (def-frob float-infinity-p
225     "Return true if the float X is an infinity (+ or -)."
226     (zerop (ldb sb!vm:single-float-significand-byte bits))
227     (and (zerop (ldb sb!vm:double-float-significand-byte hi))
228          (zerop lo))
229     #!+(and long-float x86)
230     (and (zerop (ldb sb!vm:long-float-significand-byte hi))
231          (zerop lo)))
232
233   (def-frob float-nan-p
234     "Return true if the float X is a NaN (Not a Number)."
235     (not (zerop (ldb sb!vm:single-float-significand-byte bits)))
236     (or (not (zerop (ldb sb!vm:double-float-significand-byte hi)))
237         (not (zerop lo)))
238     #!+(and long-float x86)
239     (or (not (zerop (ldb sb!vm:long-float-significand-byte hi)))
240         (not (zerop lo))))
241
242   (def-frob float-trapping-nan-p
243     "Return true if the float X is a trapping NaN (Not a Number)."
244     (zerop (logand (ldb sb!vm:single-float-significand-byte bits)
245                    sb!vm:single-float-trapping-nan-bit))
246     (zerop (logand (ldb sb!vm:double-float-significand-byte hi)
247                    sb!vm:double-float-trapping-nan-bit))
248     #!+(and long-float x86)
249     (zerop (logand (ldb sb!vm:long-float-significand-byte hi)
250                    sb!vm:long-float-trapping-nan-bit))))
251
252 ;;; If denormalized, use a subfunction from INTEGER-DECODE-FLOAT to find the
253 ;;; actual exponent (and hence how denormalized it is), otherwise we just
254 ;;; return the number of digits or 0.
255 #!-sb-fluid (declaim (maybe-inline float-precision))
256 (defun float-precision (f)
257   #!+sb-doc
258   "Return a non-negative number of significant digits in its float argument.
259   Will be less than FLOAT-DIGITS if denormalized or zero."
260   (macrolet ((frob (digits bias decode)
261                `(cond ((zerop f) 0)
262                       ((float-denormalized-p f)
263                        (multiple-value-bind (ignore exp) (,decode f)
264                          (declare (ignore ignore))
265                          (truly-the fixnum
266                                     (+ ,digits (1- ,digits) ,bias exp))))
267                       (t
268                        ,digits))))
269     (number-dispatch ((f float))
270       ((single-float)
271        (frob sb!vm:single-float-digits sb!vm:single-float-bias
272          integer-decode-single-denorm))
273       ((double-float)
274        (frob sb!vm:double-float-digits sb!vm:double-float-bias
275          integer-decode-double-denorm))
276       #!+long-float
277       ((long-float)
278        (frob sb!vm:long-float-digits sb!vm:long-float-bias
279          integer-decode-long-denorm)))))
280
281 (defun float-sign (float1 &optional (float2 (float 1 float1)))
282   #!+sb-doc
283   "Return a floating-point number that has the same sign as
284    float1 and, if float2 is given, has the same absolute value
285    as float2."
286   (declare (float float1 float2))
287   (* (if (etypecase float1
288            (single-float (minusp (single-float-bits float1)))
289            (double-float (minusp (double-float-high-bits float1)))
290            #!+long-float
291            (long-float (minusp (long-float-exp-bits float1))))
292          (float -1 float1)
293          (float 1 float1))
294      (abs float2)))
295
296 (defun float-format-digits (format)
297   (ecase format
298     ((short-float single-float) sb!vm:single-float-digits)
299     ((double-float #!-long-float long-float) sb!vm:double-float-digits)
300     #!+long-float
301     (long-float sb!vm:long-float-digits)))
302
303 #!-sb-fluid (declaim (inline float-digits float-radix))
304
305 (defun float-digits (f)
306   (number-dispatch ((f float))
307     ((single-float) sb!vm:single-float-digits)
308     ((double-float) sb!vm:double-float-digits)
309     #!+long-float
310     ((long-float) sb!vm:long-float-digits)))
311
312 (defun float-radix (x)
313   #!+sb-doc
314   "Return (as an integer) the radix b of its floating-point argument."
315   ;; ANSI says this function "should signal an error if [..] argument
316   ;; is not a float". Since X is otherwise ignored, Python doesn't
317   ;; check the type by default, so we have to do it ourself:
318   (unless (floatp x)
319     (error 'type-error :datum x :expected-type 'float))
320   2)
321 \f
322 ;;;; INTEGER-DECODE-FLOAT and DECODE-FLOAT
323
324 #!-sb-fluid
325 (declaim (maybe-inline integer-decode-single-float
326                        integer-decode-double-float))
327
328 ;;; Handle the denormalized case of INTEGER-DECODE-FLOAT for SINGLE-FLOAT.
329 (defun integer-decode-single-denorm (x)
330   (declare (type single-float x))
331   (let* ((bits (single-float-bits (abs x)))
332          (sig (ash (ldb sb!vm:single-float-significand-byte bits) 1))
333          (extra-bias 0))
334     (declare (type (unsigned-byte 24) sig)
335              (type (integer 0 23) extra-bias))
336     (loop
337       (unless (zerop (logand sig sb!vm:single-float-hidden-bit))
338         (return))
339       (setq sig (ash sig 1))
340       (incf extra-bias))
341     (values sig
342             (- (- sb!vm:single-float-bias)
343                sb!vm:single-float-digits
344                extra-bias)
345             (if (minusp (float-sign x)) -1 1))))
346
347 ;;; Handle the single-float case of INTEGER-DECODE-FLOAT. If an infinity or
348 ;;; NaN, error. If a denorm, call i-d-s-DENORM to handle it.
349 (defun integer-decode-single-float (x)
350   (declare (single-float x))
351   (let* ((bits (single-float-bits (abs x)))
352          (exp (ldb sb!vm:single-float-exponent-byte bits))
353          (sig (ldb sb!vm:single-float-significand-byte bits))
354          (sign (if (minusp (float-sign x)) -1 1))
355          (biased (- exp sb!vm:single-float-bias sb!vm:single-float-digits)))
356     (declare (fixnum biased))
357     (unless (<= exp sb!vm:single-float-normal-exponent-max)
358       (error "can't decode NaN or infinity: ~S" x))
359     (cond ((and (zerop exp) (zerop sig))
360            (values 0 biased sign))
361           ((< exp sb!vm:single-float-normal-exponent-min)
362            (integer-decode-single-denorm x))
363           (t
364            (values (logior sig sb!vm:single-float-hidden-bit) biased sign)))))
365
366 ;;; Like INTEGER-DECODE-SINGLE-DENORM, only doubly so.
367 (defun integer-decode-double-denorm (x)
368   (declare (type double-float x))
369   (let* ((high-bits (double-float-high-bits (abs x)))
370          (sig-high (ldb sb!vm:double-float-significand-byte high-bits))
371          (low-bits (double-float-low-bits x))
372          (sign (if (minusp (float-sign x)) -1 1))
373          (biased (- (- sb!vm:double-float-bias) sb!vm:double-float-digits)))
374     (if (zerop sig-high)
375         (let ((sig low-bits)
376               (extra-bias (- sb!vm:double-float-digits 33))
377               (bit (ash 1 31)))
378           (declare (type (unsigned-byte 32) sig) (fixnum extra-bias))
379           (loop
380             (unless (zerop (logand sig bit)) (return))
381             (setq sig (ash sig 1))
382             (incf extra-bias))
383           (values (ash sig (- sb!vm:double-float-digits 32))
384                   (truly-the fixnum (- biased extra-bias))
385                   sign))
386         (let ((sig (ash sig-high 1))
387               (extra-bias 0))
388           (declare (type (unsigned-byte 32) sig) (fixnum extra-bias))
389           (loop
390             (unless (zerop (logand sig sb!vm:double-float-hidden-bit))
391               (return))
392             (setq sig (ash sig 1))
393             (incf extra-bias))
394           (values (logior (ash sig 32) (ash low-bits (1- extra-bias)))
395                   (truly-the fixnum (- biased extra-bias))
396                   sign)))))
397
398 ;;; Like INTEGER-DECODE-SINGLE-FLOAT, only doubly so.
399 (defun integer-decode-double-float (x)
400   (declare (double-float x))
401   (let* ((abs (abs x))
402          (hi (double-float-high-bits abs))
403          (lo (double-float-low-bits abs))
404          (exp (ldb sb!vm:double-float-exponent-byte hi))
405          (sig (ldb sb!vm:double-float-significand-byte hi))
406          (sign (if (minusp (float-sign x)) -1 1))
407          (biased (- exp sb!vm:double-float-bias sb!vm:double-float-digits)))
408     (declare (fixnum biased))
409     (unless (<= exp sb!vm:double-float-normal-exponent-max)
410       (error "Can't decode NaN or infinity: ~S." x))
411     (cond ((and (zerop exp) (zerop sig) (zerop lo))
412            (values 0 biased sign))
413           ((< exp sb!vm:double-float-normal-exponent-min)
414            (integer-decode-double-denorm x))
415           (t
416            (values
417             (logior (ash (logior (ldb sb!vm:double-float-significand-byte hi)
418                                  sb!vm:double-float-hidden-bit)
419                          32)
420                     lo)
421             biased sign)))))
422
423 #!+(and long-float x86)
424 (defun integer-decode-long-denorm (x)
425   (declare (type long-float x))
426   (let* ((high-bits (long-float-high-bits (abs x)))
427          (sig-high (ldb sb!vm:long-float-significand-byte high-bits))
428          (low-bits (long-float-low-bits x))
429          (sign (if (minusp (float-sign x)) -1 1))
430          (biased (- (- sb!vm:long-float-bias) sb!vm:long-float-digits)))
431     (if (zerop sig-high)
432         (let ((sig low-bits)
433               (extra-bias (- sb!vm:long-float-digits 33))
434               (bit (ash 1 31)))
435           (declare (type (unsigned-byte 32) sig) (fixnum extra-bias))
436           (loop
437             (unless (zerop (logand sig bit)) (return))
438             (setq sig (ash sig 1))
439             (incf extra-bias))
440           (values (ash sig (- sb!vm:long-float-digits 32))
441                   (truly-the fixnum (- biased extra-bias))
442                   sign))
443         (let ((sig (ash sig-high 1))
444               (extra-bias 0))
445           (declare (type (unsigned-byte 32) sig) (fixnum extra-bias))
446           (loop
447             (unless (zerop (logand sig sb!vm:long-float-hidden-bit))
448               (return))
449             (setq sig (ash sig 1))
450             (incf extra-bias))
451           (values (logior (ash sig 32) (ash low-bits (1- extra-bias)))
452                   (truly-the fixnum (- biased extra-bias))
453                   sign)))))
454
455 #!+(and long-float x86)
456 (defun integer-decode-long-float (x)
457   (declare (long-float x))
458   (let* ((hi (long-float-high-bits x))
459          (lo (long-float-low-bits x))
460          (exp-bits (long-float-exp-bits x))
461          (exp (ldb sb!vm:long-float-exponent-byte exp-bits))
462          (sign (if (minusp exp-bits) -1 1))
463          (biased (- exp sb!vm:long-float-bias sb!vm:long-float-digits)))
464     (declare (fixnum biased))
465     (unless (<= exp sb!vm:long-float-normal-exponent-max)
466       (error "can't decode NaN or infinity: ~S" x))
467     (cond ((and (zerop exp) (zerop hi) (zerop lo))
468            (values 0 biased sign))
469           ((< exp sb!vm:long-float-normal-exponent-min)
470            (integer-decode-long-denorm x))
471           (t
472            (values (logior (ash hi 32) lo) biased sign)))))
473
474 ;;; Dispatch to the correct type-specific i-d-f function.
475 (defun integer-decode-float (x)
476   #!+sb-doc
477   "Return three values:
478    1) an integer representation of the significand.
479    2) the exponent for the power of 2 that the significand must be multiplied
480       by to get the actual value. This differs from the DECODE-FLOAT exponent
481       by FLOAT-DIGITS, since the significand has been scaled to have all its
482       digits before the radix point.
483    3) -1 or 1 (i.e. the sign of the argument.)"
484   (number-dispatch ((x float))
485     ((single-float)
486      (integer-decode-single-float x))
487     ((double-float)
488      (integer-decode-double-float x))
489     #!+long-float
490     ((long-float)
491      (integer-decode-long-float x))))
492
493 #!-sb-fluid (declaim (maybe-inline decode-single-float decode-double-float))
494
495 ;;; Handle the denormalized case of DECODE-SINGLE-FLOAT. We call
496 ;;; INTEGER-DECODE-SINGLE-DENORM and then make the result into a float.
497 (defun decode-single-denorm (x)
498   (declare (type single-float x))
499   (multiple-value-bind (sig exp sign) (integer-decode-single-denorm x)
500     (values (make-single-float
501              (dpb sig sb!vm:single-float-significand-byte
502                   (dpb sb!vm:single-float-bias
503                        sb!vm:single-float-exponent-byte
504                        0)))
505             (truly-the fixnum (+ exp sb!vm:single-float-digits))
506             (float sign x))))
507
508 ;;; Handle the single-float case of DECODE-FLOAT. If an infinity or NaN,
509 ;;; error. If a denorm, call d-s-DENORM to handle it.
510 (defun decode-single-float (x)
511   (declare (single-float x))
512   (let* ((bits (single-float-bits (abs x)))
513          (exp (ldb sb!vm:single-float-exponent-byte bits))
514          (sign (float-sign x))
515          (biased (truly-the single-float-exponent
516                             (- exp sb!vm:single-float-bias))))
517     (unless (<= exp sb!vm:single-float-normal-exponent-max)
518       (error "can't decode NaN or infinity: ~S" x))
519     (cond ((zerop x)
520            (values 0.0f0 biased sign))
521           ((< exp sb!vm:single-float-normal-exponent-min)
522            (decode-single-denorm x))
523           (t
524            (values (make-single-float
525                     (dpb sb!vm:single-float-bias
526                          sb!vm:single-float-exponent-byte
527                          bits))
528                    biased sign)))))
529
530 ;;; Like DECODE-SINGLE-DENORM, only doubly so.
531 (defun decode-double-denorm (x)
532   (declare (double-float x))
533   (multiple-value-bind (sig exp sign) (integer-decode-double-denorm x)
534     (values (make-double-float
535              (dpb (logand (ash sig -32) (lognot sb!vm:double-float-hidden-bit))
536                   sb!vm:double-float-significand-byte
537                   (dpb sb!vm:double-float-bias
538                        sb!vm:double-float-exponent-byte 0))
539              (ldb (byte 32 0) sig))
540             (truly-the fixnum (+ exp sb!vm:double-float-digits))
541             (float sign x))))
542
543 ;;; Like DECODE-SINGLE-FLOAT, only doubly so.
544 (defun decode-double-float (x)
545   (declare (double-float x))
546   (let* ((abs (abs x))
547          (hi (double-float-high-bits abs))
548          (lo (double-float-low-bits abs))
549          (exp (ldb sb!vm:double-float-exponent-byte hi))
550          (sign (float-sign x))
551          (biased (truly-the double-float-exponent
552                             (- exp sb!vm:double-float-bias))))
553     (unless (<= exp sb!vm:double-float-normal-exponent-max)
554       (error "can't decode NaN or infinity: ~S" x))
555     (cond ((zerop x)
556            (values 0.0d0 biased sign))
557           ((< exp sb!vm:double-float-normal-exponent-min)
558            (decode-double-denorm x))
559           (t
560            (values (make-double-float
561                     (dpb sb!vm:double-float-bias
562                          sb!vm:double-float-exponent-byte hi)
563                     lo)
564                    biased sign)))))
565
566 #!+(and long-float x86)
567 (defun decode-long-denorm (x)
568   (declare (long-float x))
569   (multiple-value-bind (sig exp sign) (integer-decode-long-denorm x)
570     (values (make-long-float sb!vm:long-float-bias (ash sig -32)
571                              (ldb (byte 32 0) sig))
572             (truly-the fixnum (+ exp sb!vm:long-float-digits))
573             (float sign x))))
574
575 #!+(and long-float x86)
576 (defun decode-long-float (x)
577   (declare (long-float x))
578   (let* ((hi (long-float-high-bits x))
579          (lo (long-float-low-bits x))
580          (exp-bits (long-float-exp-bits x))
581          (exp (ldb sb!vm:long-float-exponent-byte exp-bits))
582          (sign (if (minusp exp-bits) -1l0 1l0))
583          (biased (truly-the long-float-exponent
584                             (- exp sb!vm:long-float-bias))))
585     (unless (<= exp sb!vm:long-float-normal-exponent-max)
586       (error "can't decode NaN or infinity: ~S" x))
587     (cond ((zerop x)
588            (values 0.0l0 biased sign))
589           ((< exp sb!vm:long-float-normal-exponent-min)
590            (decode-long-denorm x))
591           (t
592            (values (make-long-float
593                     (dpb sb!vm:long-float-bias sb!vm:long-float-exponent-byte
594                          exp-bits)
595                     hi
596                     lo)
597                    biased sign)))))
598
599 ;;; Dispatch to the appropriate type-specific function.
600 (defun decode-float (f)
601   #!+sb-doc
602   "Return three values:
603    1) a floating-point number representing the significand. This is always
604       between 0.5 (inclusive) and 1.0 (exclusive).
605    2) an integer representing the exponent.
606    3) -1.0 or 1.0 (i.e. the sign of the argument.)"
607   (number-dispatch ((f float))
608     ((single-float)
609      (decode-single-float f))
610     ((double-float)
611      (decode-double-float f))
612     #!+long-float
613     ((long-float)
614      (decode-long-float f))))
615 \f
616 ;;;; SCALE-FLOAT
617
618 #!-sb-fluid (declaim (maybe-inline scale-single-float scale-double-float))
619
620 ;;; Handle float scaling where the X is denormalized or the result is
621 ;;; denormalized or underflows to 0.
622 (defun scale-float-maybe-underflow (x exp)
623   (multiple-value-bind (sig old-exp) (integer-decode-float x)
624     (let* ((digits (float-digits x))
625            (new-exp (+ exp old-exp digits
626                        (etypecase x
627                          (single-float sb!vm:single-float-bias)
628                          (double-float sb!vm:double-float-bias))))
629            (sign (if (minusp (float-sign x)) 1 0)))
630       (cond
631        ((< new-exp
632            (etypecase x
633              (single-float sb!vm:single-float-normal-exponent-min)
634              (double-float sb!vm:double-float-normal-exponent-min)))
635         (when (sb!vm:current-float-trap :inexact)
636           (error 'floating-point-inexact :operation 'scale-float
637                  :operands (list x exp)))
638         (when (sb!vm:current-float-trap :underflow)
639           (error 'floating-point-underflow :operation 'scale-float
640                  :operands (list x exp)))
641         (let ((shift (1- new-exp)))
642           (if (< shift (- (1- digits)))
643               (float-sign x 0.0)
644               (etypecase x
645                 (single-float (single-from-bits sign 0 (ash sig shift)))
646                 (double-float (double-from-bits sign 0 (ash sig shift)))))))
647        (t
648         (etypecase x
649           (single-float (single-from-bits sign new-exp sig))
650           (double-float (double-from-bits sign new-exp sig))))))))
651
652 ;;; Called when scaling a float overflows, or the original float was a
653 ;;; NaN or infinity. If overflow errors are trapped, then error,
654 ;;; otherwise return the appropriate infinity. If a NaN, signal or not
655 ;;; as appropriate.
656 (defun scale-float-maybe-overflow (x exp)
657   (cond
658    ((float-infinity-p x)
659     ;; Infinity is infinity, no matter how small...
660     x)
661    ((float-nan-p x)
662     (when (and (float-trapping-nan-p x)
663                (sb!vm:current-float-trap :invalid))
664       (error 'floating-point-invalid-operation :operation 'scale-float
665              :operands (list x exp)))
666     x)
667    (t
668     (when (sb!vm:current-float-trap :overflow)
669       (error 'floating-point-overflow :operation 'scale-float
670              :operands (list x exp)))
671     (when (sb!vm:current-float-trap :inexact)
672       (error 'floating-point-inexact :operation 'scale-float
673              :operands (list x exp)))
674     (* (float-sign x)
675        (etypecase x
676          (single-float single-float-positive-infinity)
677          (double-float double-float-positive-infinity))))))
678
679 ;;; Scale a single or double float, calling the correct over/underflow
680 ;;; functions.
681 (defun scale-single-float (x exp)
682   (declare (single-float x) (fixnum exp))
683   (let* ((bits (single-float-bits x))
684          (old-exp (ldb sb!vm:single-float-exponent-byte bits))
685          (new-exp (+ old-exp exp)))
686     (cond
687      ((zerop x) x)
688      ((or (< old-exp sb!vm:single-float-normal-exponent-min)
689           (< new-exp sb!vm:single-float-normal-exponent-min))
690       (scale-float-maybe-underflow x exp))
691      ((or (> old-exp sb!vm:single-float-normal-exponent-max)
692           (> new-exp sb!vm:single-float-normal-exponent-max))
693       (scale-float-maybe-overflow x exp))
694      (t
695       (make-single-float (dpb new-exp
696                               sb!vm:single-float-exponent-byte
697                               bits))))))
698 (defun scale-double-float (x exp)
699   (declare (double-float x) (fixnum exp))
700   (let* ((hi (double-float-high-bits x))
701          (lo (double-float-low-bits x))
702          (old-exp (ldb sb!vm:double-float-exponent-byte hi))
703          (new-exp (+ old-exp exp)))
704     (cond
705      ((zerop x) x)
706      ((or (< old-exp sb!vm:double-float-normal-exponent-min)
707           (< new-exp sb!vm:double-float-normal-exponent-min))
708       (scale-float-maybe-underflow x exp))
709      ((or (> old-exp sb!vm:double-float-normal-exponent-max)
710           (> new-exp sb!vm:double-float-normal-exponent-max))
711       (scale-float-maybe-overflow x exp))
712      (t
713       (make-double-float (dpb new-exp sb!vm:double-float-exponent-byte hi)
714                          lo)))))
715
716 #!+(and x86 long-float)
717 (defun scale-long-float (x exp)
718   (declare (long-float x) (fixnum exp))
719   (scale-float x exp))
720
721 ;;; Dispatch to the correct type-specific scale-float function.
722 (defun scale-float (f ex)
723   #!+sb-doc
724   "Return the value (* f (expt (float 2 f) ex)), but with no unnecessary loss
725   of precision or overflow."
726   (number-dispatch ((f float))
727     ((single-float)
728      (scale-single-float f ex))
729     ((double-float)
730      (scale-double-float f ex))
731     #!+long-float
732     ((long-float)
733      (scale-long-float f ex))))
734 \f
735 ;;;; converting to/from floats
736
737 (defun float (number &optional (other () otherp))
738   #!+sb-doc
739   "Converts any REAL to a float. If OTHER is not provided, it returns a
740   SINGLE-FLOAT if NUMBER is not already a FLOAT. If OTHER is provided, the
741   result is the same float format as OTHER."
742   (if otherp
743       (number-dispatch ((number real) (other float))
744         (((foreach rational single-float double-float #!+long-float long-float)
745           (foreach single-float double-float #!+long-float long-float))
746          (coerce number '(dispatch-type other))))
747       (if (floatp number)
748           number
749           (coerce number 'single-float))))
750
751 (macrolet ((frob (name type)
752              `(defun ,name (x)
753                 (number-dispatch ((x real))
754                   (((foreach single-float double-float #!+long-float long-float
755                              fixnum))
756                    (coerce x ',type))
757                   ((bignum)
758                    (bignum-to-float x ',type))
759                   ((ratio)
760                    (float-ratio x ',type))))))
761   (frob %single-float single-float)
762   (frob %double-float double-float)
763   #!+long-float
764   (frob %long-float long-float))
765
766 ;;; Convert a ratio to a float. We avoid any rounding error by doing an
767 ;;; integer division. Accuracy is important to preserve read/print
768 ;;; consistency, since this is ultimately how the reader reads a float. We
769 ;;; scale the numerator by a power of two until the division results in the
770 ;;; desired number of fraction bits, then do round-to-nearest.
771 (defun float-ratio (x format)
772   (let* ((signed-num (numerator x))
773          (plusp (plusp signed-num))
774          (num (if plusp signed-num (- signed-num)))
775          (den (denominator x))
776          (digits (float-format-digits format))
777          (scale 0))
778     (declare (fixnum digits scale))
779     ;; Strip any trailing zeros from the denominator and move it into the scale
780     ;; factor (to minimize the size of the operands.)
781     (let ((den-twos (1- (integer-length (logxor den (1- den))))))
782       (declare (fixnum den-twos))
783       (decf scale den-twos)
784       (setq den (ash den (- den-twos))))
785     ;; Guess how much we need to scale by from the magnitudes of the numerator
786     ;; and denominator. We want one extra bit for a guard bit.
787     (let* ((num-len (integer-length num))
788            (den-len (integer-length den))
789            (delta (- den-len num-len))
790            (shift (1+ (the fixnum (+ delta digits))))
791            (shifted-num (ash num shift)))
792       (declare (fixnum delta shift))
793       (decf scale delta)
794       (labels ((float-and-scale (bits)
795                  (let* ((bits (ash bits -1))
796                         (len (integer-length bits)))
797                    (cond ((> len digits)
798                           (aver (= len (the fixnum (1+ digits))))
799                           (scale-float (floatit (ash bits -1)) (1+ scale)))
800                          (t
801                           (scale-float (floatit bits) scale)))))
802                (floatit (bits)
803                  (let ((sign (if plusp 0 1)))
804                    (case format
805                      (single-float
806                       (single-from-bits sign sb!vm:single-float-bias bits))
807                      (double-float
808                       (double-from-bits sign sb!vm:double-float-bias bits))
809                      #!+long-float
810                      (long-float
811                       (long-from-bits sign sb!vm:long-float-bias bits))))))
812         (loop
813           (multiple-value-bind (fraction-and-guard rem)
814               (truncate shifted-num den)
815             (let ((extra (- (integer-length fraction-and-guard) digits)))
816               (declare (fixnum extra))
817               (cond ((/= extra 1)
818                      (aver (> extra 1)))
819                     ((oddp fraction-and-guard)
820                      (return
821                       (if (zerop rem)
822                           (float-and-scale
823                            (if (zerop (logand fraction-and-guard 2))
824                                fraction-and-guard
825                                (1+ fraction-and-guard)))
826                           (float-and-scale (1+ fraction-and-guard)))))
827                     (t
828                      (return (float-and-scale fraction-and-guard)))))
829             (setq shifted-num (ash shifted-num -1))
830             (incf scale)))))))
831
832 #|
833 These might be useful if we ever have a machine without float/integer
834 conversion hardware. For now, we'll use special ops that
835 uninterruptibly frob the rounding modes & do ieee round-to-integer.
836
837 ;;; The compiler compiles a call to this when we are doing %UNARY-TRUNCATE
838 ;;; and the result is known to be a fixnum. We can avoid some generic
839 ;;; arithmetic in this case.
840 (defun %unary-truncate-single-float/fixnum (x)
841   (declare (single-float x) (values fixnum))
842   (locally (declare (optimize (speed 3) (safety 0)))
843     (let* ((bits (single-float-bits x))
844            (exp (ldb sb!vm:single-float-exponent-byte bits))
845            (frac (logior (ldb sb!vm:single-float-significand-byte bits)
846                          sb!vm:single-float-hidden-bit))
847            (shift (- exp sb!vm:single-float-digits sb!vm:single-float-bias)))
848       (when (> exp sb!vm:single-float-normal-exponent-max)
849         (error 'floating-point-invalid-operation :operator 'truncate
850                :operands (list x)))
851       (if (<= shift (- sb!vm:single-float-digits))
852           0
853           (let ((res (ash frac shift)))
854             (declare (type (unsigned-byte 31) res))
855             (if (minusp bits)
856                 (- res)
857                 res))))))
858
859 ;;; Double-float version of this operation (see above single op).
860 (defun %unary-truncate-double-float/fixnum (x)
861   (declare (double-float x) (values fixnum))
862   (locally (declare (optimize (speed 3) (safety 0)))
863     (let* ((hi-bits (double-float-high-bits x))
864            (exp (ldb sb!vm:double-float-exponent-byte hi-bits))
865            (frac (logior (ldb sb!vm:double-float-significand-byte hi-bits)
866                          sb!vm:double-float-hidden-bit))
867            (shift (- exp (- sb!vm:double-float-digits sb!vm:n-word-bits)
868                      sb!vm:double-float-bias)))
869       (when (> exp sb!vm:double-float-normal-exponent-max)
870         (error 'floating-point-invalid-operation :operator 'truncate
871                :operands (list x)))
872       (if (<= shift (- sb!vm:n-word-bits sb!vm:double-float-digits))
873           0
874           (let* ((res-hi (ash frac shift))
875                  (res (if (plusp shift)
876                           (logior res-hi
877                                   (the fixnum
878                                        (ash (double-float-low-bits x)
879                                             (- shift sb!vm:n-word-bits))))
880                           res-hi)))
881             (declare (type (unsigned-byte 31) res-hi res))
882             (if (minusp hi-bits)
883                 (- res)
884                 res))))))
885 |#
886
887 ;;; This function is called when we are doing a truncate without any funky
888 ;;; divisor, i.e. converting a float or ratio to an integer. Note that we do
889 ;;; *not* return the second value of truncate, so it must be computed by the
890 ;;; caller if needed.
891 ;;;
892 ;;; In the float case, we pick off small arguments so that compiler can use
893 ;;; special-case operations. We use an exclusive test, since (due to round-off
894 ;;; error), (float most-positive-fixnum) may be greater than
895 ;;; most-positive-fixnum.
896 (defun %unary-truncate (number)
897   (number-dispatch ((number real))
898     ((integer) number)
899     ((ratio) (values (truncate (numerator number) (denominator number))))
900     (((foreach single-float double-float #!+long-float long-float))
901      (if (< (float most-negative-fixnum number)
902             number
903             (float most-positive-fixnum number))
904          (truly-the fixnum (%unary-truncate number))
905          (multiple-value-bind (bits exp) (integer-decode-float number)
906            (let ((res (ash bits exp)))
907              (if (minusp number)
908                  (- res)
909                  res)))))))
910
911 ;;; Similar to %UNARY-TRUNCATE, but rounds to the nearest integer. If we
912 ;;; can't use the round primitive, then we do our own round-to-nearest on the
913 ;;; result of i-d-f. [Note that this rounding will really only happen with
914 ;;; double floats, since the whole single-float fraction will fit in a fixnum,
915 ;;; so all single-floats larger than most-positive-fixnum can be precisely
916 ;;; represented by an integer.]
917 (defun %unary-round (number)
918   (number-dispatch ((number real))
919     ((integer) number)
920     ((ratio) (values (round (numerator number) (denominator number))))
921     (((foreach single-float double-float #!+long-float long-float))
922      (if (< (float most-negative-fixnum number)
923             number
924             (float most-positive-fixnum number))
925          (truly-the fixnum (%unary-round number))
926          (multiple-value-bind (bits exp) (integer-decode-float number)
927            (let* ((shifted (ash bits exp))
928                   (rounded (if (and (minusp exp)
929                                     (oddp shifted)
930                                     (eql (logand bits
931                                                  (lognot (ash -1 (- exp))))
932                                          (ash 1 (- -1 exp))))
933                                (1+ shifted)
934                                shifted)))
935              (if (minusp number)
936                  (- rounded)
937                  rounded)))))))
938
939 (defun rational (x)
940   #!+sb-doc
941   "RATIONAL produces a rational number for any real numeric argument. This is
942   more efficient than RATIONALIZE, but it assumes that floating-point is
943   completely accurate, giving a result that isn't as pretty."
944   (number-dispatch ((x real))
945     (((foreach single-float double-float #!+long-float long-float))
946      (multiple-value-bind (bits exp) (integer-decode-float x)
947        (if (eql bits 0)
948            0
949            (let* ((int (if (minusp x) (- bits) bits))
950                   (digits (float-digits x))
951                   (ex (+ exp digits)))
952              (if (minusp ex)
953                  (integer-/-integer int (ash 1 (+ digits (- ex))))
954                  (integer-/-integer (ash int ex) (ash 1 digits)))))))
955     ((rational) x)))
956
957 (defun rationalize (x)
958   #!+sb-doc
959   "Converts any REAL to a RATIONAL. Floats are converted to a simple rational
960   representation exploiting the assumption that floats are only accurate to
961   their precision. RATIONALIZE (and also RATIONAL) preserve the invariant:
962       (= x (float (rationalize x) x))"
963   (number-dispatch ((x real))
964     (((foreach single-float double-float #!+long-float long-float))
965      ;; Thanks to Kim Fateman, who stole this function rationalize-float from
966      ;; macsyma's rational. Macsyma'a rationalize was written by the legendary
967      ;; Gosper (rwg). Guy Steele said about Gosper, "He has been called the
968      ;; only living 17th century mathematician and is also the best pdp-10
969      ;; hacker I know." So, if you can understand or debug this code you win
970      ;; big.
971      (cond ((minusp x) (- (rationalize (- x))))
972            ((zerop x) 0)
973            (t
974             (let ((eps (etypecase x
975                            (single-float single-float-epsilon)
976                            (double-float double-float-epsilon)
977                            #!+long-float
978                            (long-float long-float-epsilon)))
979                   (y ())
980                   (a ()))
981               (do ((xx x (setq y (/ (float 1.0 x) (- xx (float a x)))))
982                    (num (setq a (truncate x))
983                         (+ (* (setq a (truncate y)) num) onum))
984                    (den 1 (+ (* a den) oden))
985                    (onum 1 num)
986                    (oden 0 den))
987                   ((and (not (zerop den))
988                         (not (> (abs (/ (- x (/ (float num x)
989                                                 (float den x)))
990                                         x))
991                                 eps)))
992                    (integer-/-integer num den))
993                 (declare ((dispatch-type x) xx)))))))
994     ((rational) x)))