Fix FP traps on OSX/x86-64.
[sbcl.git] / tests / float.pure.lisp
1 ;;;; floating-point-related tests with no side effects
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; While most of SBCL is derived from the CMU CL system, the test
7 ;;;; files (like this one) were written from scratch after the fork
8 ;;;; from CMU CL.
9 ;;;;
10 ;;;; This software is in the public domain and is provided with
11 ;;;; absolutely no warranty. See the COPYING and CREDITS files for
12 ;;;; more information.
13
14 (cl:in-package :cl-user)
15
16 (dolist (ifnis (list (cons single-float-positive-infinity
17                            single-float-negative-infinity)
18                      (cons double-float-positive-infinity
19                            double-float-negative-infinity)))
20   (destructuring-bind (+ifni . -ifni) ifnis
21     (assert (= (* +ifni 1) +ifni))
22     (assert (= (* +ifni -0.1) -ifni))
23     (assert (= (+ +ifni -0.1) +ifni))
24     (assert (= (- +ifni -0.1) +ifni))
25     (assert (= (sqrt +ifni) +ifni))
26     (assert (= (* -ifni -14) +ifni))
27     (assert (= (/ -ifni 0.1) -ifni))
28     (assert (= (/ -ifni 100/3) -ifni))
29     (assert (not (= +ifni -ifni)))
30     (assert (= -ifni -ifni))
31     (assert (not (= +ifni 100/3)))
32     (assert (not (= -ifni -1.0 -ifni)))
33     (assert (not (= -ifni -17/02 -ifni)))
34     (assert (< -ifni +ifni))
35     (assert (not (< +ifni 100)))
36     (assert (not (< +ifni 100.0)))
37     (assert (not (< +ifni -ifni)))
38     (assert (< 100 +ifni))
39     (assert (< 100.0 +ifni))
40     (assert (>= 100 -ifni))
41     (assert (not (<= 6/7 (* 3 -ifni))))
42     (assert (not (> +ifni +ifni)))))
43
44 ;;; ANSI: FLOAT-RADIX should signal an error if its argument is not a
45 ;;; float.
46 ;;;
47 ;;; (Peter Van Eynde's ansi-test suite caught this, and Eric Marsden
48 ;;; reported a fix for CMU CL, which was ported to sbcl-0.6.12.35.)
49 (assert (typep (nth-value 1 (ignore-errors (float-radix "notfloat")))
50                'type-error))
51
52 (assert (typep (nth-value 1 (ignore-errors
53                               (funcall (fdefinition 'float-radix) "notfloat")))
54                'type-error))
55
56 ;;; Before 0.8.2.14 the cross compiler failed to work with
57 ;;; denormalized numbers
58 (when (subtypep 'single-float 'short-float)
59   (assert (eql least-positive-single-float least-positive-short-float)))
60
61 ;;; bug found by Paul Dietz: FFLOOR and similar did not work for integers
62 (let ((tests '(((ffloor -8 3) (-3.0 1))
63                ((fround -8 3) (-3.0 1))
64                ((ftruncate -8 3) (-2.0 -2))
65                ((fceiling -8 3) (-2.0 -2)))))
66   (loop for (exp res) in tests
67         for real-res = (multiple-value-list (eval exp))
68         do (assert (equal real-res res))))
69
70 ;;; bug 45b reported by PVE
71 (dolist (type '(short single double long))
72   (dolist (sign '(positive negative))
73     (let* ((name (find-symbol (format nil "LEAST-~A-~A-FLOAT"
74                                       sign type)
75                               :cl))
76            (value (symbol-value name)))
77       (assert (zerop (/ value 2))))))
78
79 ;;; bug found by Paul Dietz: bad rounding on small floats
80 (assert (= (fround least-positive-short-float least-positive-short-float) 1.0))
81
82 ;;; bug found by Peter Seibel: scale-float was only accepting float
83 ;;; exponents, when it should accept all integers.  (also bug #269)
84 (assert (= (multiple-value-bind (significand expt sign)
85                (integer-decode-float least-positive-double-float)
86              (* (scale-float (float significand 0.0d0) expt) sign))
87            least-positive-double-float))
88 (assert (= (multiple-value-bind (significand expt sign)
89                (decode-float least-positive-double-float)
90              (* (scale-float significand expt) sign))
91            least-positive-double-float))
92 (assert (= 0.0 (scale-float 1.0 most-negative-fixnum)))
93 (assert (= 0.0d0 (scale-float 1.0d0 (1- most-negative-fixnum))))
94
95 (with-test (:name (:scale-float-overflow :bug-372)
96             :fails-on '(and :darwin (or :ppc :x86))) ;; bug 372
97   (progn
98     (assert (raises-error? (scale-float 1.0 most-positive-fixnum)
99                            floating-point-overflow))
100     (assert (raises-error? (scale-float 1.0d0 (1+ most-positive-fixnum))
101                            floating-point-overflow))))
102
103 ;;; bug found by jsnell when nfroyd tried to implement better LOGAND
104 ;;; type derivation.
105 (assert (= (integer-decode-float (coerce -1756510900000000000
106                                          'single-float))
107            12780299))
108
109 ;;; MISC.564: no out-of-line %ATAN2 for constant folding
110 (assert (typep
111   (funcall
112    (compile
113     nil
114     '(lambda (p1)
115       (declare (optimize (speed 3) (safety 2) (debug 3) (space 0))
116        (type complex p1))
117       (phase (the (eql #c(1.0d0 2.0d0)) p1))))
118    #c(1.0d0 2.0d0))
119     'double-float))
120
121 ;;; More out of line functions (%COS, %SIN, %TAN) for constant folding,
122 ;;; reported by Mika Pihlajamäki
123 (funcall (compile nil '(lambda () (cos (tan (round 0))))))
124 (funcall (compile nil '(lambda () (sin (tan (round 0))))))
125 (funcall (compile nil '(lambda () (tan (tan (round 0))))))
126
127 (with-test (:name (:addition-overflow :bug-372)
128             :fails-on '(or (and :ppc :openbsd)
129                            (and (or :ppc :x86) :darwin)
130                            (and :x86 :netbsd)))
131   (assert (typep (nth-value
132                   1
133                   (ignore-errors
134                     (sb-sys:without-interrupts
135                      (sb-int:set-floating-point-modes :current-exceptions nil
136                                                       :accrued-exceptions nil)
137                      (loop repeat 2 summing most-positive-double-float)
138                      (sleep 2))))
139                  'floating-point-overflow)))
140
141 ;; This is the same test as above.  Even if the above copy passes,
142 ;; this copy will fail if SIGFPE handling ends up clearing the FPU
143 ;; control word, which can happen if the kernel clears the FPU control
144 ;; (a reasonable thing for it to do) and the runtime fails to
145 ;; compensate for this (see RESTORE_FP_CONTROL_WORD in interrupt.c).
146 (with-test (:name (:addition-overflow :bug-372 :take-2)
147             :fails-on '(or (and :ppc :openbsd)
148                            (and (or :ppc :x86) :darwin)
149                            (and :x86 :netbsd)))
150   (assert (typep (nth-value
151                   1
152                   (ignore-errors
153                     (sb-sys:without-interrupts
154                      (sb-int:set-floating-point-modes :current-exceptions nil
155                                                       :accrued-exceptions nil)
156                      (loop repeat 2 summing most-positive-double-float)
157                      (sleep 2))))
158                  'floating-point-overflow)))
159
160 ;;; On x86-64 generating complex floats on the stack failed an aver in
161 ;;; the compiler if the stack slot was the same as the one containing
162 ;;; the real part of the complex. The following expression was able to
163 ;;; trigger this in 0.9.5.62.
164 (with-test (:name :complex-float-stack)
165   (dolist (type '((complex double-float)
166                   (complex single-float)))
167     (compile nil
168              `(lambda (x0 x1 x2 x3 x4 x5 x6 x7)
169                 (declare (type ,type x0 x1 x2 x3 x4 x5 x6 x7))
170                 (let ((x0 (+ x0 x0))
171                       (x1 (+ x1 x1))
172                       (x2 (+ x2 x2))
173                       (x3 (+ x3 x3))
174                       (x4 (+ x4 x4))
175                       (x5 (+ x5 x5))
176                       (x6 (+ x6 x6))
177                       (x7 (+ x7 x7)))
178                   (* (+ x0 x1 x2 x3) (+ x4 x5 x6 x7)
179                      (+ x0 x2 x4 x6) (+ x1 x3 x5 x7)
180                      (+ x0 x3 x4 x7) (+ x1 x2 x5 x6)
181                      (+ x0 x1 x6 x7) (+ x2 x3 x4 x5)))))))
182
183
184 (with-test (:name :nan-comparisons
185             :fails-on '(or :sparc :mips))
186   (sb-int:with-float-traps-masked (:invalid)
187     (macrolet ((test (form)
188                  (let ((nform (subst '(/ 0.0 0.0) 'nan form)))
189                    `(progn
190                       (assert (eval ',nform))
191                       (assert (eval `(let ((nan (/ 0.0 0.0)))
192                                        ,',form)))
193                       (assert (funcall
194                                (compile nil `(lambda () ,',nform))))
195                       (assert (funcall
196                                (compile nil `(lambda (nan) ,',form))
197                                (/ 0.0 0.0)))))))
198       (test (/= nan nan))
199       (test (/= nan nan nan))
200       (test (/= 1.0 nan 2.0 nan))
201       (test (/= nan 1.0 2.0 nan))
202       (test (not (= nan 1.0)))
203       (test (not (= nan nan)))
204       (test (not (= nan nan nan)))
205       (test (not (= 1.0 nan)))
206       (test (not (= nan 1.0)))
207       (test (not (= 1.0 1.0 nan)))
208       (test (not (= 1.0 nan 1.0)))
209       (test (not (= nan 1.0 1.0)))
210       (test (not (>= nan nan)))
211       (test (not (>= nan 1.0)))
212       (test (not (>= 1.0 nan)))
213       (test (not (>= 1.0 nan 0.0)))
214       (test (not (>= 1.0 0.0 nan)))
215       (test (not (>= nan 1.0 0.0)))
216       (test (not (<= nan nan)))
217       (test (not (<= nan 1.0)))
218       (test (not (<= 1.0 nan)))
219       (test (not (<= 1.0 nan 2.0)))
220       (test (not (<= 1.0 2.0 nan)))
221       (test (not (<= nan 1.0 2.0)))
222       (test (not (< nan nan)))
223       (test (not (< -1.0 nan)))
224       (test (not (< nan 1.0)))
225       (test (not (> nan nan)))
226       (test (not (> -1.0 nan)))
227       (test (not (> nan 1.0))))))
228
229 (with-test (:name :log-int/double-accuracy)
230   ;; we used to use single precision for intermediate results
231   (assert (eql 2567.6046442221327d0
232                (log (loop for n from 1 to 1000 for f = 1 then (* f n)
233                           finally (return f))
234                     10d0)))
235   ;; both ways
236   (assert (eql (log 123123123.0d0 10) (log 123123123 10.0d0))))
237
238 (with-test (:name :log-base-zero-return-type)
239   (assert (eql 0.0f0 (log 123 (eval 0))))
240   (assert (eql 0.0d0 (log 123.0d0 (eval 0))))
241   (assert (eql 0.0d0 (log 123 (eval 0.0d0))))
242   (let ((f (compile nil '(lambda (x y)
243                           (declare (optimize speed))
244                           (etypecase x
245                             (single-float
246                              (etypecase y
247                                (single-float (log x y))
248                                (double-float (log x y))))
249                             (double-float
250                              (etypecase y
251                                (single-float (log x y))
252                                (double-float (log x y)))))))))
253     (assert (eql 0.0f0 (funcall f 123.0 0.0)))
254     (assert (eql 0.0d0 (funcall f 123.0d0 0.0)))
255     (assert (eql 0.0d0 (funcall f 123.0d0 0.0d0)))
256     (assert (eql 0.0d0 (funcall f 123.0 0.0d0)))))
257
258 ;; Bug reported by Eric Marsden on July 15 2009. The compiler
259 ;; used not to constant fold calls with arguments of type
260 ;; (EQL foo).
261 (with-test (:name :eql-type-constant-fold)
262   (assert (equal '(FUNCTION (T) (VALUES (MEMBER T) &OPTIONAL))
263                  (sb-kernel:%simple-fun-type
264                   (compile nil `(lambda (x)
265                                   (eql #c(1.0 2.0)
266                                        (the (eql #c(1.0 2.0))
267                                          x))))))))
268
269 ;; This was previously x86-only, with note:
270 ;;   The x86 port used not to reduce the arguments of transcendentals
271 ;;   correctly. On other platforms, we trust libm to DTRT.
272 ;; but it doesn't cost any real amount to just test them all
273 (with-test (:name :range-reduction
274             :fails-on ':x86-64)
275   (flet ((almost= (x y)
276            (< (abs (- x y)) 1d-5)))
277     (macrolet ((foo (op value)
278                  `(assert (almost= (,op (mod ,value (* 2 pi)))
279                                    (,op ,value)))))
280       (let ((big (* pi (expt 2d0 70)))
281             (mid (coerce most-positive-fixnum 'double-float))
282             (odd (* pi most-positive-fixnum)))
283         (foo sin big)
284         (foo sin mid)
285         (foo sin odd)
286         (foo sin (/ odd 2d0))
287
288         (foo cos big)
289         (foo cos mid)
290         (foo cos odd)
291         (foo cos (/ odd 2d0))
292
293         (foo tan big)
294         (foo tan mid)
295         (foo tan odd)))))
296
297 ;; Leakage from the host could result in wrong values for truncation.
298 (with-test (:name :truncate)
299   (assert (plusp (sb-kernel:%unary-truncate/single-float (expt 2f0 33))))
300   (assert (plusp (sb-kernel:%unary-truncate/double-float (expt 2d0 33))))
301   ;; That'd be one strange host, but just in case
302   (assert (plusp (sb-kernel:%unary-truncate/single-float (expt 2f0 65))))
303   (assert (plusp (sb-kernel:%unary-truncate/double-float (expt 2d0 65)))))
304
305 ;; On x86-64, we sometimes forgot to clear the higher order bits of the
306 ;; destination register before using it with an instruction that doesn't
307 ;; clear the (unused) high order bits. Suspect instructions are operations
308 ;; with only one operand: for everything else, the destination has already
309 ;; been loaded with a value, making it safe (by induction).
310 ;;
311 ;; The tests are extremely brittle and could be broken by any number of
312 ;; back- or front-end optimisations. We should just keep the issue above
313 ;; in mind at all times when working with SSE or similar instruction sets.
314 ;;
315 ;; Run only on x86/x86-64m as no other platforms have SB-VM::TOUCH-OBJECT.
316 (macrolet ((with-pinned-floats ((count type &rest names) &body body)
317              "Force COUNT float values to be kept live (and hopefully in registers),
318               fill a temporary register with noise, and execute BODY."
319              (let ((dummy (loop repeat count
320                                 collect (or (pop names)
321                                             (gensym "TEMP")))))
322                `(let ,(loop for i downfrom -1
323                             for var in dummy
324                             for j = (coerce i type)
325                             collect
326                             `(,var ,(complex j j))) ; we don't actually need that, but
327                   (declare (type (complex ,type) ,@dummy)) ; future-proofing can't hurt
328                   ,@(loop for var in dummy
329                           for i upfrom 0
330                           collect `(setf ,var ,(complex i (coerce i type))))
331                   (multiple-value-prog1
332                       (progn
333                         (let ((x ,(complex 1d0 1d0)))
334                           (declare (type (complex double-float) x))
335                           (setf x ,(complex most-positive-fixnum (float most-positive-fixnum 1d0)))
336                           (sb-vm::touch-object x))
337                         (locally ,@body))
338                     ,@(loop for var in dummy
339                             collect `(sb-vm::touch-object ,var)))))))
340   (with-test (:name :clear-sqrtsd :skipped-on '(not (or :x86 :x86-64)))
341     (flet ((test-sqrtsd (float)
342              (declare (optimize speed (safety 1))
343                       (type (double-float (0d0)) float))
344              (with-pinned-floats (14 double-float x0)
345                (let ((x (sqrt float)))
346                  (values (+ x x0) float)))))
347       (declare (notinline test-sqrtsd))
348       (assert (zerop (imagpart (test-sqrtsd 4d0))))))
349
350   (with-test (:name :clear-sqrtsd-single :skipped-on '(not (or :x86 :x86-64)))
351     (flet ((test-sqrtsd-float (float)
352              (declare (optimize speed (safety 1))
353                       (type (single-float (0f0)) float))
354              (with-pinned-floats (14 single-float x0)
355                (let ((x (sqrt float)))
356                  (values (+ x x0) float)))))
357       (declare (notinline test-sqrtsd-float))
358       (assert (zerop (imagpart (test-sqrtsd-float 4f0))))))
359
360   (with-test (:name :clear-cvtss2sd :skipped-on '(not (or :x86 :x86-64)))
361     (flet ((test-cvtss2sd (float)
362              (declare (optimize speed (safety 1))
363                       (type single-float float))
364              (with-pinned-floats (14 double-float x0)
365                (let ((x (float float 0d0)))
366                  (values (+ x x0) (+ 1e0 float))))))
367       (declare (notinline test-cvtss2sd))
368       (assert (zerop (imagpart (test-cvtss2sd 1f0))))))
369
370   (with-test (:name :clear-cvtsd2ss :skipped-on '(not (or :x86 :x86-64)))
371     (flet ((test-cvtsd2ss (float)
372              (declare (optimize speed (safety 1))
373                       (type double-float float))
374              (with-pinned-floats (14 single-float x0)
375                (let ((x (float float 1e0)))
376                  (values (+ x x0) (+ 1d0 float))))))
377       (declare (notinline test-cvtsd2ss))
378       (assert (zerop (imagpart (test-cvtsd2ss 4d0))))))
379
380   (with-test (:name :clear-cvtsi2sd :skipped-on '(not (or :x86 :x86-64)))
381     (flet ((test-cvtsi2sd (int)
382              (declare (optimize speed (safety 0))
383                       (type (unsigned-byte 10) int))
384              (with-pinned-floats (15 double-float x0)
385                (+ (float int 0d0) x0))))
386       (declare (notinline test-cvtsi2sd))
387       (assert (zerop (imagpart (test-cvtsi2sd 4))))))
388
389   (with-test (:name :clear-cvtsi2ss :skipped-on '(not (or :x86 :x86-64)))
390     (flet ((test-cvtsi2ss (int)
391              (declare (optimize speed (safety 0))
392                       (type (unsigned-byte 10) int))
393              (with-pinned-floats (15 single-float x0)
394                (+ (float int 0e0) x0))))
395       (declare (notinline test-cvtsi2ss))
396       (assert (zerop (imagpart (test-cvtsi2ss 4)))))))
397
398 (with-test (:name :round-to-bignum)
399   (assert (= (round 1073741822.3d0) 1073741822))
400   (assert (= (round 1073741822.5d0) 1073741822))
401   (assert (= (round 1073741822.7d0) 1073741823))
402   (assert (= (round 1073741823.3d0) 1073741823))
403   (assert (= (round 1073741823.5d0) 1073741824))
404   (assert (= (round 1073741823.7d0) 1073741824)))
405
406 (with-test (:name :round-single-to-bignum)
407   (assert (= (round 1e14) 100000000376832))
408   (assert (= (round 1e19) 9999999980506447872)))