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