0.pre7.14:
[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.
124 (eval-when (:load-toplevel :execute)
125 (defconstant single-float-positive-infinity
126   (single-from-bits 0 (1+ sb!vm:single-float-normal-exponent-max) 0))
127 (defconstant short-float-positive-infinity single-float-positive-infinity)
128 (defconstant single-float-negative-infinity
129   (single-from-bits 1 (1+ sb!vm:single-float-normal-exponent-max) 0))
130 (defconstant short-float-negative-infinity single-float-negative-infinity)
131 (defconstant double-float-positive-infinity
132   (double-from-bits 0 (1+ sb!vm:double-float-normal-exponent-max) 0))
133 #!+(not long-float)
134 (defconstant long-float-positive-infinity double-float-positive-infinity)
135 #!+(and 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 (defconstant double-float-negative-infinity
140   (double-from-bits 1 (1+ sb!vm:double-float-normal-exponent-max) 0))
141 #!+(not long-float)
142 (defconstant long-float-negative-infinity double-float-negative-infinity)
143 #!+(and long-float x86)
144 (defconstant long-float-negative-infinity
145   (long-from-bits 1 (1+ sb!vm:long-float-normal-exponent-max)
146                   (ash sb!vm:long-float-hidden-bit 32)))
147 ) ; EVAL-WHEN
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   "Return (as an integer) the radix b of its floating-point argument."
313   (declare (type float x))
314   ;; ANSI says this function "should signal an error if [..] argument
315   ;; is not a float". Since X is otherwise ignored, Python doesn't
316   ;; check the type by default, so we have to do it ourself:
317   (unless (floatp x)
318     (error 'type-error :datum x :expected-type 'float))
319   2)
320 \f
321 ;;;; INTEGER-DECODE-FLOAT and DECODE-FLOAT
322
323 #!-sb-fluid
324 (declaim (maybe-inline integer-decode-single-float
325                        integer-decode-double-float))
326
327 ;;; Handle the denormalized case of INTEGER-DECODE-FLOAT for SINGLE-FLOAT.
328 (defun integer-decode-single-denorm (x)
329   (declare (type single-float x))
330   (let* ((bits (single-float-bits (abs x)))
331          (sig (ash (ldb sb!vm:single-float-significand-byte bits) 1))
332          (extra-bias 0))
333     (declare (type (unsigned-byte 24) sig)
334              (type (integer 0 23) extra-bias))
335     (loop
336       (unless (zerop (logand sig sb!vm:single-float-hidden-bit))
337         (return))
338       (setq sig (ash sig 1))
339       (incf extra-bias))
340     (values sig
341             (- (- sb!vm:single-float-bias)
342                sb!vm:single-float-digits
343                extra-bias)
344             (if (minusp (float-sign x)) -1 1))))
345
346 ;;; Handle the single-float case of INTEGER-DECODE-FLOAT. If an infinity or
347 ;;; NaN, error. If a denorm, call i-d-s-DENORM to handle it.
348 (defun integer-decode-single-float (x)
349   (declare (single-float x))
350   (let* ((bits (single-float-bits (abs x)))
351          (exp (ldb sb!vm:single-float-exponent-byte bits))
352          (sig (ldb sb!vm:single-float-significand-byte bits))
353          (sign (if (minusp (float-sign x)) -1 1))
354          (biased (- exp sb!vm:single-float-bias sb!vm:single-float-digits)))
355     (declare (fixnum biased))
356     (unless (<= exp sb!vm:single-float-normal-exponent-max)
357       (error "can't decode NaN or infinity: ~S" x))
358     (cond ((and (zerop exp) (zerop sig))
359            (values 0 biased sign))
360           ((< exp sb!vm:single-float-normal-exponent-min)
361            (integer-decode-single-denorm x))
362           (t
363            (values (logior sig sb!vm:single-float-hidden-bit) biased sign)))))
364
365 ;;; Like INTEGER-DECODE-SINGLE-DENORM, only doubly so.
366 (defun integer-decode-double-denorm (x)
367   (declare (type double-float x))
368   (let* ((high-bits (double-float-high-bits (abs x)))
369          (sig-high (ldb sb!vm:double-float-significand-byte high-bits))
370          (low-bits (double-float-low-bits x))
371          (sign (if (minusp (float-sign x)) -1 1))
372          (biased (- (- sb!vm:double-float-bias) sb!vm:double-float-digits)))
373     (if (zerop sig-high)
374         (let ((sig low-bits)
375               (extra-bias (- sb!vm:double-float-digits 33))
376               (bit (ash 1 31)))
377           (declare (type (unsigned-byte 32) sig) (fixnum extra-bias))
378           (loop
379             (unless (zerop (logand sig bit)) (return))
380             (setq sig (ash sig 1))
381             (incf extra-bias))
382           (values (ash sig (- sb!vm:double-float-digits 32))
383                   (truly-the fixnum (- biased extra-bias))
384                   sign))
385         (let ((sig (ash sig-high 1))
386               (extra-bias 0))
387           (declare (type (unsigned-byte 32) sig) (fixnum extra-bias))
388           (loop
389             (unless (zerop (logand sig sb!vm:double-float-hidden-bit))
390               (return))
391             (setq sig (ash sig 1))
392             (incf extra-bias))
393           (values (logior (ash sig 32) (ash low-bits (1- extra-bias)))
394                   (truly-the fixnum (- biased extra-bias))
395                   sign)))))
396
397 ;;; Like INTEGER-DECODE-SINGLE-FLOAT, only doubly so.
398 (defun integer-decode-double-float (x)
399   (declare (double-float x))
400   (let* ((abs (abs x))
401          (hi (double-float-high-bits abs))
402          (lo (double-float-low-bits abs))
403          (exp (ldb sb!vm:double-float-exponent-byte hi))
404          (sig (ldb sb!vm:double-float-significand-byte hi))
405          (sign (if (minusp (float-sign x)) -1 1))
406          (biased (- exp sb!vm:double-float-bias sb!vm:double-float-digits)))
407     (declare (fixnum biased))
408     (unless (<= exp sb!vm:double-float-normal-exponent-max)
409       (error "Can't decode NaN or infinity: ~S." x))
410     (cond ((and (zerop exp) (zerop sig) (zerop lo))
411            (values 0 biased sign))
412           ((< exp sb!vm:double-float-normal-exponent-min)
413            (integer-decode-double-denorm x))
414           (t
415            (values
416             (logior (ash (logior (ldb sb!vm:double-float-significand-byte hi)
417                                  sb!vm:double-float-hidden-bit)
418                          32)
419                     lo)
420             biased sign)))))
421
422 #!+(and long-float x86)
423 (defun integer-decode-long-denorm (x)
424   (declare (type long-float x))
425   (let* ((high-bits (long-float-high-bits (abs x)))
426          (sig-high (ldb sb!vm:long-float-significand-byte high-bits))
427          (low-bits (long-float-low-bits x))
428          (sign (if (minusp (float-sign x)) -1 1))
429          (biased (- (- sb!vm:long-float-bias) sb!vm:long-float-digits)))
430     (if (zerop sig-high)
431         (let ((sig low-bits)
432               (extra-bias (- sb!vm:long-float-digits 33))
433               (bit (ash 1 31)))
434           (declare (type (unsigned-byte 32) sig) (fixnum extra-bias))
435           (loop
436             (unless (zerop (logand sig bit)) (return))
437             (setq sig (ash sig 1))
438             (incf extra-bias))
439           (values (ash sig (- sb!vm:long-float-digits 32))
440                   (truly-the fixnum (- biased extra-bias))
441                   sign))
442         (let ((sig (ash sig-high 1))
443               (extra-bias 0))
444           (declare (type (unsigned-byte 32) sig) (fixnum extra-bias))
445           (loop
446             (unless (zerop (logand sig sb!vm:long-float-hidden-bit))
447               (return))
448             (setq sig (ash sig 1))
449             (incf extra-bias))
450           (values (logior (ash sig 32) (ash low-bits (1- extra-bias)))
451                   (truly-the fixnum (- biased extra-bias))
452                   sign)))))
453
454 #!+(and long-float x86)
455 (defun integer-decode-long-float (x)
456   (declare (long-float x))
457   (let* ((hi (long-float-high-bits x))
458          (lo (long-float-low-bits x))
459          (exp-bits (long-float-exp-bits x))
460          (exp (ldb sb!vm:long-float-exponent-byte exp-bits))
461          (sign (if (minusp exp-bits) -1 1))
462          (biased (- exp sb!vm:long-float-bias sb!vm:long-float-digits)))
463     (declare (fixnum biased))
464     (unless (<= exp sb!vm:long-float-normal-exponent-max)
465       (error "can't decode NaN or infinity: ~S" x))
466     (cond ((and (zerop exp) (zerop hi) (zerop lo))
467            (values 0 biased sign))
468           ((< exp sb!vm:long-float-normal-exponent-min)
469            (integer-decode-long-denorm x))
470           (t
471            (values (logior (ash hi 32) lo) biased sign)))))
472
473 ;;; Dispatch to the correct type-specific i-d-f function.
474 (defun integer-decode-float (x)
475   #!+sb-doc
476   "Returns three values:
477    1) an integer representation of the significand.
478    2) the exponent for the power of 2 that the significand must be multiplied
479       by to get the actual value. This differs from the DECODE-FLOAT exponent
480       by FLOAT-DIGITS, since the significand has been scaled to have all its
481       digits before the radix point.
482    3) -1 or 1 (i.e. the sign of the argument.)"
483   (number-dispatch ((x float))
484     ((single-float)
485      (integer-decode-single-float x))
486     ((double-float)
487      (integer-decode-double-float x))
488     #!+long-float
489     ((long-float)
490      (integer-decode-long-float x))))
491
492 #!-sb-fluid (declaim (maybe-inline decode-single-float decode-double-float))
493
494 ;;; Handle the denormalized case of DECODE-SINGLE-FLOAT. We call
495 ;;; INTEGER-DECODE-SINGLE-DENORM and then make the result into a float.
496 (defun decode-single-denorm (x)
497   (declare (type single-float x))
498   (multiple-value-bind (sig exp sign) (integer-decode-single-denorm x)
499     (values (make-single-float
500              (dpb sig sb!vm:single-float-significand-byte
501                   (dpb sb!vm:single-float-bias
502                        sb!vm:single-float-exponent-byte
503                        0)))
504             (truly-the fixnum (+ exp sb!vm:single-float-digits))
505             (float sign x))))
506
507 ;;; Handle the single-float case of DECODE-FLOAT. If an infinity or NaN,
508 ;;; error. If a denorm, call d-s-DENORM to handle it.
509 (defun decode-single-float (x)
510   (declare (single-float x))
511   (let* ((bits (single-float-bits (abs x)))
512          (exp (ldb sb!vm:single-float-exponent-byte bits))
513          (sign (float-sign x))
514          (biased (truly-the single-float-exponent
515                             (- exp sb!vm:single-float-bias))))
516     (unless (<= exp sb!vm:single-float-normal-exponent-max)
517       (error "can't decode NaN or infinity: ~S" x))
518     (cond ((zerop x)
519            (values 0.0f0 biased sign))
520           ((< exp sb!vm:single-float-normal-exponent-min)
521            (decode-single-denorm x))
522           (t
523            (values (make-single-float
524                     (dpb sb!vm:single-float-bias
525                          sb!vm:single-float-exponent-byte
526                          bits))
527                    biased sign)))))
528
529 ;;; Like DECODE-SINGLE-DENORM, only doubly so.
530 (defun decode-double-denorm (x)
531   (declare (double-float x))
532   (multiple-value-bind (sig exp sign) (integer-decode-double-denorm x)
533     (values (make-double-float
534              (dpb (logand (ash sig -32) (lognot sb!vm:double-float-hidden-bit))
535                   sb!vm:double-float-significand-byte
536                   (dpb sb!vm:double-float-bias
537                        sb!vm:double-float-exponent-byte 0))
538              (ldb (byte 32 0) sig))
539             (truly-the fixnum (+ exp sb!vm:double-float-digits))
540             (float sign x))))
541
542 ;;; Like DECODE-SINGLE-FLOAT, only doubly so.
543 (defun decode-double-float (x)
544   (declare (double-float x))
545   (let* ((abs (abs x))
546          (hi (double-float-high-bits abs))
547          (lo (double-float-low-bits abs))
548          (exp (ldb sb!vm:double-float-exponent-byte hi))
549          (sign (float-sign x))
550          (biased (truly-the double-float-exponent
551                             (- exp sb!vm:double-float-bias))))
552     (unless (<= exp sb!vm:double-float-normal-exponent-max)
553       (error "can't decode NaN or infinity: ~S" x))
554     (cond ((zerop x)
555            (values 0.0d0 biased sign))
556           ((< exp sb!vm:double-float-normal-exponent-min)
557            (decode-double-denorm x))
558           (t
559            (values (make-double-float
560                     (dpb sb!vm:double-float-bias
561                          sb!vm:double-float-exponent-byte hi)
562                     lo)
563                    biased sign)))))
564
565 #!+(and long-float x86)
566 (defun decode-long-denorm (x)
567   (declare (long-float x))
568   (multiple-value-bind (sig exp sign) (integer-decode-long-denorm x)
569     (values (make-long-float sb!vm:long-float-bias (ash sig -32)
570                              (ldb (byte 32 0) sig))
571             (truly-the fixnum (+ exp sb!vm:long-float-digits))
572             (float sign x))))
573
574 #!+(and long-float x86)
575 (defun decode-long-float (x)
576   (declare (long-float x))
577   (let* ((hi (long-float-high-bits x))
578          (lo (long-float-low-bits x))
579          (exp-bits (long-float-exp-bits x))
580          (exp (ldb sb!vm:long-float-exponent-byte exp-bits))
581          (sign (if (minusp exp-bits) -1l0 1l0))
582          (biased (truly-the long-float-exponent
583                             (- exp sb!vm:long-float-bias))))
584     (unless (<= exp sb!vm:long-float-normal-exponent-max)
585       (error "can't decode NaN or infinity: ~S" x))
586     (cond ((zerop x)
587            (values 0.0l0 biased sign))
588           ((< exp sb!vm:long-float-normal-exponent-min)
589            (decode-long-denorm x))
590           (t
591            (values (make-long-float
592                     (dpb sb!vm:long-float-bias sb!vm:long-float-exponent-byte
593                          exp-bits)
594                     hi
595                     lo)
596                    biased sign)))))
597
598 ;;; Dispatch to the appropriate type-specific function.
599 (defun decode-float (f)
600   #!+sb-doc
601   "Returns three values:
602    1) a floating-point number representing the significand. This is always
603       between 0.5 (inclusive) and 1.0 (exclusive).
604    2) an integer representing the exponent.
605    3) -1.0 or 1.0 (i.e. the sign of the argument.)"
606   (number-dispatch ((f float))
607     ((single-float)
608      (decode-single-float f))
609     ((double-float)
610      (decode-double-float f))
611     #!+long-float
612     ((long-float)
613      (decode-long-float f))))
614 \f
615 ;;;; SCALE-FLOAT
616
617 #!-sb-fluid (declaim (maybe-inline scale-single-float scale-double-float))
618
619 ;;; Handle float scaling where the X is denormalized or the result is
620 ;;; denormalized or underflows to 0.
621 (defun scale-float-maybe-underflow (x exp)
622   (multiple-value-bind (sig old-exp) (integer-decode-float x)
623     (let* ((digits (float-digits x))
624            (new-exp (+ exp old-exp digits
625                        (etypecase x
626                          (single-float sb!vm:single-float-bias)
627                          (double-float sb!vm:double-float-bias))))
628            (sign (if (minusp (float-sign x)) 1 0)))
629       (cond
630        ((< new-exp
631            (etypecase x
632              (single-float sb!vm:single-float-normal-exponent-min)
633              (double-float sb!vm:double-float-normal-exponent-min)))
634         (when (sb!vm:current-float-trap :inexact)
635           (error 'floating-point-inexact :operation 'scale-float
636                  :operands (list x exp)))
637         (when (sb!vm:current-float-trap :underflow)
638           (error 'floating-point-underflow :operation 'scale-float
639                  :operands (list x exp)))
640         (let ((shift (1- new-exp)))
641           (if (< shift (- (1- digits)))
642               (float-sign x 0.0)
643               (etypecase x
644                 (single-float (single-from-bits sign 0 (ash sig shift)))
645                 (double-float (double-from-bits sign 0 (ash sig shift)))))))
646        (t
647         (etypecase x
648           (single-float (single-from-bits sign new-exp sig))
649           (double-float (double-from-bits sign new-exp sig))))))))
650
651 ;;; Called when scaling a float overflows, or the original float was a
652 ;;; NaN or infinity. If overflow errors are trapped, then error,
653 ;;; otherwise return the appropriate infinity. If a NaN, signal or not
654 ;;; as appropriate.
655 (defun scale-float-maybe-overflow (x exp)
656   (cond
657    ((float-infinity-p x)
658     ;; Infinity is infinity, no matter how small...
659     x)
660    ((float-nan-p x)
661     (when (and (float-trapping-nan-p x)
662                (sb!vm:current-float-trap :invalid))
663       (error 'floating-point-invalid-operation :operation 'scale-float
664              :operands (list x exp)))
665     x)
666    (t
667     (when (sb!vm:current-float-trap :overflow)
668       (error 'floating-point-overflow :operation 'scale-float
669              :operands (list x exp)))
670     (when (sb!vm:current-float-trap :inexact)
671       (error 'floating-point-inexact :operation 'scale-float
672              :operands (list x exp)))
673     (* (float-sign x)
674        (etypecase x
675          (single-float single-float-positive-infinity)
676          (double-float double-float-positive-infinity))))))
677
678 ;;; Scale a single or double float, calling the correct over/underflow
679 ;;; functions.
680 (defun scale-single-float (x exp)
681   (declare (single-float x) (fixnum exp))
682   (let* ((bits (single-float-bits x))
683          (old-exp (ldb sb!vm:single-float-exponent-byte bits))
684          (new-exp (+ old-exp exp)))
685     (cond
686      ((zerop x) x)
687      ((or (< old-exp sb!vm:single-float-normal-exponent-min)
688           (< new-exp sb!vm:single-float-normal-exponent-min))
689       (scale-float-maybe-underflow x exp))
690      ((or (> old-exp sb!vm:single-float-normal-exponent-max)
691           (> new-exp sb!vm:single-float-normal-exponent-max))
692       (scale-float-maybe-overflow x exp))
693      (t
694       (make-single-float (dpb new-exp
695                               sb!vm:single-float-exponent-byte
696                               bits))))))
697 (defun scale-double-float (x exp)
698   (declare (double-float x) (fixnum exp))
699   (let* ((hi (double-float-high-bits x))
700          (lo (double-float-low-bits x))
701          (old-exp (ldb sb!vm:double-float-exponent-byte hi))
702          (new-exp (+ old-exp exp)))
703     (cond
704      ((zerop x) x)
705      ((or (< old-exp sb!vm:double-float-normal-exponent-min)
706           (< new-exp sb!vm:double-float-normal-exponent-min))
707       (scale-float-maybe-underflow x exp))
708      ((or (> old-exp sb!vm:double-float-normal-exponent-max)
709           (> new-exp sb!vm:double-float-normal-exponent-max))
710       (scale-float-maybe-overflow x exp))
711      (t
712       (make-double-float (dpb new-exp sb!vm:double-float-exponent-byte hi)
713                          lo)))))
714
715 #!+(and x86 long-float)
716 (defun scale-long-float (x exp)
717   (declare (long-float x) (fixnum exp))
718   (scale-float x exp))
719
720 ;;; Dispatch to the correct type-specific scale-float function.
721 (defun scale-float (f ex)
722   #!+sb-doc
723   "Returns the value (* f (expt (float 2 f) ex)), but with no unnecessary loss
724   of precision or overflow."
725   (number-dispatch ((f float))
726     ((single-float)
727      (scale-single-float f ex))
728     ((double-float)
729      (scale-double-float f ex))
730     #!+long-float
731     ((long-float)
732      (scale-long-float f ex))))
733 \f
734 ;;;; converting to/from floats
735
736 (defun float (number &optional (other () otherp))
737   #!+sb-doc
738   "Converts any REAL to a float. If OTHER is not provided, it returns a
739   SINGLE-FLOAT if NUMBER is not already a FLOAT. If OTHER is provided, the
740   result is the same float format as OTHER."
741   (if otherp
742       (number-dispatch ((number real) (other float))
743         (((foreach rational single-float double-float #!+long-float long-float)
744           (foreach single-float double-float #!+long-float long-float))
745          (coerce number '(dispatch-type other))))
746       (if (floatp number)
747           number
748           (coerce number 'single-float))))
749
750 (macrolet ((frob (name type)
751              `(defun ,name (x)
752                 (number-dispatch ((x real))
753                   (((foreach single-float double-float #!+long-float long-float
754                              fixnum))
755                    (coerce x ',type))
756                   ((bignum)
757                    (bignum-to-float x ',type))
758                   ((ratio)
759                    (float-ratio x ',type))))))
760   (frob %single-float single-float)
761   (frob %double-float double-float)
762   #!+long-float
763   (frob %long-float long-float))
764
765 ;;; Convert a ratio to a float. We avoid any rounding error by doing an
766 ;;; integer division. Accuracy is important to preserve read/print
767 ;;; consistency, since this is ultimately how the reader reads a float. We
768 ;;; scale the numerator by a power of two until the division results in the
769 ;;; desired number of fraction bits, then do round-to-nearest.
770 (defun float-ratio (x format)
771   (let* ((signed-num (numerator x))
772          (plusp (plusp signed-num))
773          (num (if plusp signed-num (- signed-num)))
774          (den (denominator x))
775          (digits (float-format-digits format))
776          (scale 0))
777     (declare (fixnum digits scale))
778     ;; Strip any trailing zeros from the denominator and move it into the scale
779     ;; factor (to minimize the size of the operands.)
780     (let ((den-twos (1- (integer-length (logxor den (1- den))))))
781       (declare (fixnum den-twos))
782       (decf scale den-twos)
783       (setq den (ash den (- den-twos))))
784     ;; Guess how much we need to scale by from the magnitudes of the numerator
785     ;; and denominator. We want one extra bit for a guard bit.
786     (let* ((num-len (integer-length num))
787            (den-len (integer-length den))
788            (delta (- den-len num-len))
789            (shift (1+ (the fixnum (+ delta digits))))
790            (shifted-num (ash num shift)))
791       (declare (fixnum delta shift))
792       (decf scale delta)
793       (labels ((float-and-scale (bits)
794                  (let* ((bits (ash bits -1))
795                         (len (integer-length bits)))
796                    (cond ((> len digits)
797                           (aver (= len (the fixnum (1+ digits))))
798                           (scale-float (floatit (ash bits -1)) (1+ scale)))
799                          (t
800                           (scale-float (floatit bits) scale)))))
801                (floatit (bits)
802                  (let ((sign (if plusp 0 1)))
803                    (case format
804                      (single-float
805                       (single-from-bits sign sb!vm:single-float-bias bits))
806                      (double-float
807                       (double-from-bits sign sb!vm:double-float-bias bits))
808                      #!+long-float
809                      (long-float
810                       (long-from-bits sign sb!vm:long-float-bias bits))))))
811         (loop
812           (multiple-value-bind (fraction-and-guard rem)
813               (truncate shifted-num den)
814             (let ((extra (- (integer-length fraction-and-guard) digits)))
815               (declare (fixnum extra))
816               (cond ((/= extra 1)
817                      (aver (> extra 1)))
818                     ((oddp fraction-and-guard)
819                      (return
820                       (if (zerop rem)
821                           (float-and-scale
822                            (if (zerop (logand fraction-and-guard 2))
823                                fraction-and-guard
824                                (1+ fraction-and-guard)))
825                           (float-and-scale (1+ fraction-and-guard)))))
826                     (t
827                      (return (float-and-scale fraction-and-guard)))))
828             (setq shifted-num (ash shifted-num -1))
829             (incf scale)))))))
830
831 #|
832 These might be useful if we ever have a machine without float/integer
833 conversion hardware. For now, we'll use special ops that
834 uninterruptibly frob the rounding modes & do ieee round-to-integer.
835
836 ;;; The compiler compiles a call to this when we are doing %UNARY-TRUNCATE
837 ;;; and the result is known to be a fixnum. We can avoid some generic
838 ;;; arithmetic in this case.
839 (defun %unary-truncate-single-float/fixnum (x)
840   (declare (single-float x) (values fixnum))
841   (locally (declare (optimize (speed 3) (safety 0)))
842     (let* ((bits (single-float-bits x))
843            (exp (ldb sb!vm:single-float-exponent-byte bits))
844            (frac (logior (ldb sb!vm:single-float-significand-byte bits)
845                          sb!vm:single-float-hidden-bit))
846            (shift (- exp sb!vm:single-float-digits sb!vm:single-float-bias)))
847       (when (> exp sb!vm:single-float-normal-exponent-max)
848         (error 'floating-point-invalid-operation :operator 'truncate
849                :operands (list x)))
850       (if (<= shift (- sb!vm:single-float-digits))
851           0
852           (let ((res (ash frac shift)))
853             (declare (type (unsigned-byte 31) res))
854             (if (minusp bits)
855                 (- res)
856                 res))))))
857
858 ;;; Double-float version of this operation (see above single op).
859 (defun %unary-truncate-double-float/fixnum (x)
860   (declare (double-float x) (values fixnum))
861   (locally (declare (optimize (speed 3) (safety 0)))
862     (let* ((hi-bits (double-float-high-bits x))
863            (exp (ldb sb!vm:double-float-exponent-byte hi-bits))
864            (frac (logior (ldb sb!vm:double-float-significand-byte hi-bits)
865                          sb!vm:double-float-hidden-bit))
866            (shift (- exp (- sb!vm:double-float-digits sb!vm:word-bits)
867                      sb!vm:double-float-bias)))
868       (when (> exp sb!vm:double-float-normal-exponent-max)
869         (error 'floating-point-invalid-operation :operator 'truncate
870                :operands (list x)))
871       (if (<= shift (- sb!vm:word-bits sb!vm:double-float-digits))
872           0
873           (let* ((res-hi (ash frac shift))
874                  (res (if (plusp shift)
875                           (logior res-hi
876                                   (the fixnum
877                                        (ash (double-float-low-bits x)
878                                             (- shift sb!vm:word-bits))))
879                           res-hi)))
880             (declare (type (unsigned-byte 31) res-hi res))
881             (if (minusp hi-bits)
882                 (- res)
883                 res))))))
884 |#
885
886 ;;; This function is called when we are doing a truncate without any funky
887 ;;; divisor, i.e. converting a float or ratio to an integer. Note that we do
888 ;;; *not* return the second value of truncate, so it must be computed by the
889 ;;; caller if needed.
890 ;;;
891 ;;; In the float case, we pick off small arguments so that compiler can use
892 ;;; special-case operations. We use an exclusive test, since (due to round-off
893 ;;; error), (float most-positive-fixnum) may be greater than
894 ;;; most-positive-fixnum.
895 (defun %unary-truncate (number)
896   (number-dispatch ((number real))
897     ((integer) number)
898     ((ratio) (values (truncate (numerator number) (denominator number))))
899     (((foreach single-float double-float #!+long-float long-float))
900      (if (< (float most-negative-fixnum number)
901             number
902             (float most-positive-fixnum number))
903          (truly-the fixnum (%unary-truncate number))
904          (multiple-value-bind (bits exp) (integer-decode-float number)
905            (let ((res (ash bits exp)))
906              (if (minusp number)
907                  (- res)
908                  res)))))))
909
910 ;;; Similar to %UNARY-TRUNCATE, but rounds to the nearest integer. If we
911 ;;; can't use the round primitive, then we do our own round-to-nearest on the
912 ;;; result of i-d-f. [Note that this rounding will really only happen with
913 ;;; double floats, since the whole single-float fraction will fit in a fixnum,
914 ;;; so all single-floats larger than most-positive-fixnum can be precisely
915 ;;; represented by an integer.]
916 (defun %unary-round (number)
917   (number-dispatch ((number real))
918     ((integer) number)
919     ((ratio) (values (round (numerator number) (denominator number))))
920     (((foreach single-float double-float #!+long-float long-float))
921      (if (< (float most-negative-fixnum number)
922             number
923             (float most-positive-fixnum number))
924          (truly-the fixnum (%unary-round number))
925          (multiple-value-bind (bits exp) (integer-decode-float number)
926            (let* ((shifted (ash bits exp))
927                   (rounded (if (and (minusp exp)
928                                     (oddp shifted)
929                                     (eql (logand bits
930                                                  (lognot (ash -1 (- exp))))
931                                          (ash 1 (- -1 exp))))
932                                (1+ shifted)
933                                shifted)))
934              (if (minusp number)
935                  (- rounded)
936                  rounded)))))))
937
938 (defun rational (x)
939   #!+sb-doc
940   "RATIONAL produces a rational number for any real numeric argument. This is
941   more efficient than RATIONALIZE, but it assumes that floating-point is
942   completely accurate, giving a result that isn't as pretty."
943   (number-dispatch ((x real))
944     (((foreach single-float double-float #!+long-float long-float))
945      (multiple-value-bind (bits exp) (integer-decode-float x)
946        (if (eql bits 0)
947            0
948            (let* ((int (if (minusp x) (- bits) bits))
949                   (digits (float-digits x))
950                   (ex (+ exp digits)))
951              (if (minusp ex)
952                  (integer-/-integer int (ash 1 (+ digits (- ex))))
953                  (integer-/-integer (ash int ex) (ash 1 digits)))))))
954     ((rational) x)))
955
956 (defun rationalize (x)
957   #!+sb-doc
958   "Converts any REAL to a RATIONAL. Floats are converted to a simple rational
959   representation exploiting the assumption that floats are only accurate to
960   their precision. RATIONALIZE (and also RATIONAL) preserve the invariant:
961       (= x (float (rationalize x) x))"
962   (number-dispatch ((x real))
963     (((foreach single-float double-float #!+long-float long-float))
964      ;; Thanks to Kim Fateman, who stole this function rationalize-float from
965      ;; macsyma's rational. Macsyma'a rationalize was written by the legendary
966      ;; Gosper (rwg). Guy Steele said about Gosper, "He has been called the
967      ;; only living 17th century mathematician and is also the best pdp-10
968      ;; hacker I know." So, if you can understand or debug this code you win
969      ;; big.
970      (cond ((minusp x) (- (rationalize (- x))))
971            ((zerop x) 0)
972            (t
973             (let ((eps (etypecase x
974                            (single-float single-float-epsilon)
975                            (double-float double-float-epsilon)
976                            #!+long-float
977                            (long-float long-float-epsilon)))
978                   (y ())
979                   (a ()))
980               (do ((xx x (setq y (/ (float 1.0 x) (- xx (float a x)))))
981                    (num (setq a (truncate x))
982                         (+ (* (setq a (truncate y)) num) onum))
983                    (den 1 (+ (* a den) oden))
984                    (onum 1 num)
985                    (oden 0 den))
986                   ((and (not (zerop den))
987                         (not (> (abs (/ (- x (/ (float num x)
988                                                 (float den x)))
989                                         x))
990                                 eps)))
991                    (integer-/-integer num den))
992                 (declare ((dispatch-type x) xx)))))))
993     ((rational) x)))