1.0.27.41: floating point implementation smoothing
[sbcl.git] / src / code / irrat.lisp
1 ;;;; This file contains all the irrational functions. (Actually, most
2 ;;;; of the work is done by calling out to C.)
3
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
12
13 (in-package "SB!KERNEL")
14 \f
15 ;;;; miscellaneous constants, utility functions, and macros
16
17 (defconstant pi
18   #!+long-float 3.14159265358979323846264338327950288419716939937511l0
19   #!-long-float 3.14159265358979323846264338327950288419716939937511d0)
20
21 ;;; Make these INLINE, since the call to C is at least as compact as a
22 ;;; Lisp call, and saves number consing to boot.
23 (eval-when (:compile-toplevel :execute)
24
25 (sb!xc:defmacro def-math-rtn (name num-args)
26   (let ((function (symbolicate "%" (string-upcase name))))
27     `(progn
28        (declaim (inline ,function))
29        (sb!alien:define-alien-routine (,name ,function) double-float
30          ,@(let ((results nil))
31              (dotimes (i num-args (nreverse results))
32                (push (list (intern (format nil "ARG-~D" i))
33                            'double-float)
34                      results)))))))
35
36 (defun handle-reals (function var)
37   `((((foreach fixnum single-float bignum ratio))
38      (coerce (,function (coerce ,var 'double-float)) 'single-float))
39     ((double-float)
40      (,function ,var))))
41
42 ) ; EVAL-WHEN
43 \f
44 #!+x86 ;; for constant folding
45 (macrolet ((def (name ll)
46              `(defun ,name ,ll (,name ,@ll))))
47   (def %atan2 (x y))
48   (def %atan (x))
49   (def %tan (x))
50   (def %tan-quick (x))
51   (def %cos (x))
52   (def %cos-quick (x))
53   (def %sin (x))
54   (def %sin-quick (x))
55   (def %sqrt (x))
56   (def %log (x))
57   (def %exp (x)))
58
59 #!+x86-64 ;; for constant folding
60 (macrolet ((def (name ll)
61              `(defun ,name ,ll (,name ,@ll))))
62   (def %sqrt (x)))
63
64 ;;;; stubs for the Unix math library
65 ;;;;
66 ;;;; Many of these are unnecessary on the X86 because they're built
67 ;;;; into the FPU.
68
69 ;;; trigonometric
70 #!-x86 (def-math-rtn "sin" 1)
71 #!-x86 (def-math-rtn "cos" 1)
72 #!-x86 (def-math-rtn "tan" 1)
73 #!-x86 (def-math-rtn "atan" 1)
74 #!-x86 (def-math-rtn "atan2" 2)
75 #!-win32
76 (progn
77   (def-math-rtn "acos" 1)
78   (def-math-rtn "asin" 1)
79   (def-math-rtn "cosh" 1)
80   (def-math-rtn "sinh" 1)
81   (def-math-rtn "tanh" 1)
82   (def-math-rtn "asinh" 1)
83   (def-math-rtn "acosh" 1)
84   (def-math-rtn "atanh" 1))
85 #!+win32
86 (progn
87   (declaim (inline %asin))
88   (defun %asin (number)
89     (%atan (/ number (sqrt (- 1 (* number number))))))
90   (declaim (inline %acos))
91   (defun %acos (number)
92     (- (/ pi 2) (%asin number)))
93   (declaim (inline %cosh))
94   (defun %cosh (number)
95     (/ (+ (exp number) (exp (- number))) 2))
96   (declaim (inline %sinh))
97   (defun %sinh (number)
98     (/ (- (exp number) (exp (- number))) 2))
99   (declaim (inline %tanh))
100   (defun %tanh (number)
101     (/ (%sinh number) (%cosh number)))
102   (declaim (inline %asinh))
103   (defun %asinh (number)
104     (log (+ number (sqrt (+ (* number number) 1.0d0))) #.(exp 1.0d0)))
105   (declaim (inline %acosh))
106   (defun %acosh (number)
107     (log (+ number (sqrt (- (* number number) 1.0d0))) #.(exp 1.0d0)))
108   (declaim (inline %atanh))
109   (defun %atanh (number)
110     (let ((ratio (/ (+ 1 number) (- 1 number))))
111       ;; Were we effectively zero?
112       (if (= ratio -1.0d0)
113           0.0d0
114           (/ (log ratio #.(exp 1.0d0)) 2.0d0)))))
115
116 ;;; exponential and logarithmic
117 #!-x86 (def-math-rtn "exp" 1)
118 #!-x86 (def-math-rtn "log" 1)
119 #!-x86 (def-math-rtn "log10" 1)
120 #!-win32(def-math-rtn "pow" 2)
121 #!-(or x86 x86-64) (def-math-rtn "sqrt" 1)
122 #!-win32 (def-math-rtn "hypot" 2)
123 #!-x86 (def-math-rtn "log1p" 1)
124
125 #!+win32
126 (progn
127   ;; FIXME: libc hypot "computes the sqrt(x*x+y*y) without undue overflow or underflow"
128   ;; ...we just do the stupid simple thing.
129   (declaim (inline %hypot))
130   (defun %hypot (x y)
131     (sqrt (+ (* x x) (* y y)))))
132 \f
133 ;;;; power functions
134
135 (defun exp (number)
136   #!+sb-doc
137   "Return e raised to the power NUMBER."
138   (number-dispatch ((number number))
139     (handle-reals %exp number)
140     ((complex)
141      (* (exp (realpart number))
142         (cis (imagpart number))))))
143
144 ;;; INTEXP -- Handle the rational base, integer power case.
145
146 (declaim (type (or integer null) *intexp-maximum-exponent*))
147 (defparameter *intexp-maximum-exponent* nil)
148
149 ;;; This function precisely calculates base raised to an integral
150 ;;; power. It separates the cases by the sign of power, for efficiency
151 ;;; reasons, as powers can be calculated more efficiently if power is
152 ;;; a positive integer. Values of power are calculated as positive
153 ;;; integers, and inverted if negative.
154 (defun intexp (base power)
155   (when (and *intexp-maximum-exponent*
156              (> (abs power) *intexp-maximum-exponent*))
157     (error "The absolute value of ~S exceeds ~S."
158             power '*intexp-maximum-exponent*))
159   (cond ((minusp power)
160          (/ (intexp base (- power))))
161         ((eql base 2)
162          (ash 1 power))
163         (t
164          (do ((nextn (ash power -1) (ash power -1))
165               (total (if (oddp power) base 1)
166                      (if (oddp power) (* base total) total)))
167              ((zerop nextn) total)
168            (setq base (* base base))
169            (setq power nextn)))))
170
171 ;;; If an integer power of a rational, use INTEXP above. Otherwise, do
172 ;;; floating point stuff. If both args are real, we try %POW right
173 ;;; off, assuming it will return 0 if the result may be complex. If
174 ;;; so, we call COMPLEX-POW which directly computes the complex
175 ;;; result. We also separate the complex-real and real-complex cases
176 ;;; from the general complex case.
177 (defun expt (base power)
178   #!+sb-doc
179   "Return BASE raised to the POWER."
180   (if (zerop power)
181       (let ((result (1+ (* base power))))
182         (if (and (floatp result) (float-nan-p result))
183             (float 1 result)
184             result))
185     (labels (;; determine if the double float is an integer.
186              ;;  0 - not an integer
187              ;;  1 - an odd int
188              ;;  2 - an even int
189              (isint (ihi lo)
190                (declare (type (unsigned-byte 31) ihi)
191                         (type (unsigned-byte 32) lo)
192                         (optimize (speed 3) (safety 0)))
193                (let ((isint 0))
194                  (declare (type fixnum isint))
195                  (cond ((>= ihi #x43400000)     ; exponent >= 53
196                         (setq isint 2))
197                        ((>= ihi #x3ff00000)
198                         (let ((k (- (ash ihi -20) #x3ff)))      ; exponent
199                           (declare (type (mod 53) k))
200                           (cond ((> k 20)
201                                  (let* ((shift (- 52 k))
202                                         (j (logand (ash lo (- shift))))
203                                         (j2 (ash j shift)))
204                                    (declare (type (mod 32) shift)
205                                             (type (unsigned-byte 32) j j2))
206                                    (when (= j2 lo)
207                                      (setq isint (- 2 (logand j 1))))))
208                                 ((= lo 0)
209                                  (let* ((shift (- 20 k))
210                                         (j (ash ihi (- shift)))
211                                         (j2 (ash j shift)))
212                                    (declare (type (mod 32) shift)
213                                             (type (unsigned-byte 31) j j2))
214                                    (when (= j2 ihi)
215                                      (setq isint (- 2 (logand j 1))))))))))
216                  isint))
217              (real-expt (x y rtype)
218                (let ((x (coerce x 'double-float))
219                      (y (coerce y 'double-float)))
220                  (declare (double-float x y))
221                  (let* ((x-hi (sb!kernel:double-float-high-bits x))
222                         (x-lo (sb!kernel:double-float-low-bits x))
223                         (x-ihi (logand x-hi #x7fffffff))
224                         (y-hi (sb!kernel:double-float-high-bits y))
225                         (y-lo (sb!kernel:double-float-low-bits y))
226                         (y-ihi (logand y-hi #x7fffffff)))
227                    (declare (type (signed-byte 32) x-hi y-hi)
228                             (type (unsigned-byte 31) x-ihi y-ihi)
229                             (type (unsigned-byte 32) x-lo y-lo))
230                    ;; y==zero: x**0 = 1
231                    (when (zerop (logior y-ihi y-lo))
232                      (return-from real-expt (coerce 1d0 rtype)))
233                    ;; +-NaN return x+y
234                    ;; FIXME: Hardcoded qNaN/sNaN values are not portable.
235                    (when (or (> x-ihi #x7ff00000)
236                              (and (= x-ihi #x7ff00000) (/= x-lo 0))
237                              (> y-ihi #x7ff00000)
238                              (and (= y-ihi #x7ff00000) (/= y-lo 0)))
239                      (return-from real-expt (coerce (+ x y) rtype)))
240                    (let ((yisint (if (< x-hi 0) (isint y-ihi y-lo) 0)))
241                      (declare (type fixnum yisint))
242                      ;; special value of y
243                      (when (and (zerop y-lo) (= y-ihi #x7ff00000))
244                        ;; y is +-inf
245                        (return-from real-expt
246                          (cond ((and (= x-ihi #x3ff00000) (zerop x-lo))
247                                 ;; +-1**inf is NaN
248                                 (coerce (- y y) rtype))
249                                ((>= x-ihi #x3ff00000)
250                                 ;; (|x|>1)**+-inf = inf,0
251                                 (if (>= y-hi 0)
252                                     (coerce y rtype)
253                                     (coerce 0 rtype)))
254                                (t
255                                 ;; (|x|<1)**-,+inf = inf,0
256                                 (if (< y-hi 0)
257                                     (coerce (- y) rtype)
258                                     (coerce 0 rtype))))))
259
260                      (let ((abs-x (abs x)))
261                        (declare (double-float abs-x))
262                        ;; special value of x
263                        (when (and (zerop x-lo)
264                                   (or (= x-ihi #x7ff00000) (zerop x-ihi)
265                                       (= x-ihi #x3ff00000)))
266                          ;; x is +-0,+-inf,+-1
267                          (let ((z (if (< y-hi 0)
268                                       (/ 1 abs-x)       ; z = (1/|x|)
269                                       abs-x)))
270                            (declare (double-float z))
271                            (when (< x-hi 0)
272                              (cond ((and (= x-ihi #x3ff00000) (zerop yisint))
273                                     ;; (-1)**non-int
274                                     (let ((y*pi (* y pi)))
275                                       (declare (double-float y*pi))
276                                       (return-from real-expt
277                                         (complex
278                                          (coerce (%cos y*pi) rtype)
279                                          (coerce (%sin y*pi) rtype)))))
280                                    ((= yisint 1)
281                                     ;; (x<0)**odd = -(|x|**odd)
282                                     (setq z (- z)))))
283                            (return-from real-expt (coerce z rtype))))
284
285                        (if (>= x-hi 0)
286                            ;; x>0
287                            (coerce (sb!kernel::%pow x y) rtype)
288                            ;; x<0
289                            (let ((pow (sb!kernel::%pow abs-x y)))
290                              (declare (double-float pow))
291                              (case yisint
292                                (1 ; odd
293                                 (coerce (* -1d0 pow) rtype))
294                                (2 ; even
295                                 (coerce pow rtype))
296                                (t ; non-integer
297                                 (let ((y*pi (* y pi)))
298                                   (declare (double-float y*pi))
299                                   (complex
300                                    (coerce (* pow (%cos y*pi))
301                                            rtype)
302                                    (coerce (* pow (%sin y*pi))
303                                            rtype)))))))))))))
304       (declare (inline real-expt))
305       (number-dispatch ((base number) (power number))
306         (((foreach fixnum (or bignum ratio) (complex rational)) integer)
307          (intexp base power))
308         (((foreach single-float double-float) rational)
309          (real-expt base power '(dispatch-type base)))
310         (((foreach fixnum (or bignum ratio) single-float)
311           (foreach ratio single-float))
312          (real-expt base power 'single-float))
313         (((foreach fixnum (or bignum ratio) single-float double-float)
314           double-float)
315          (real-expt base power 'double-float))
316         ((double-float single-float)
317          (real-expt base power 'double-float))
318         (((foreach (complex rational) (complex float)) rational)
319          (* (expt (abs base) power)
320             (cis (* power (phase base)))))
321         (((foreach fixnum (or bignum ratio) single-float double-float)
322           complex)
323          (if (and (zerop base) (plusp (realpart power)))
324              (* base power)
325              (exp (* power (log base)))))
326         (((foreach (complex float) (complex rational))
327           (foreach complex double-float single-float))
328          (if (and (zerop base) (plusp (realpart power)))
329              (* base power)
330              (exp (* power (log base)))))))))
331
332 ;;; FIXME: Maybe rename this so that it's clearer that it only works
333 ;;; on integers?
334 (defun log2 (x)
335   (declare (type integer x))
336   ;; CMUCL comment:
337   ;;
338   ;;   Write x = 2^n*f where 1/2 < f <= 1.  Then log2(x) = n +
339   ;;   log2(f).  So we grab the top few bits of x and scale that
340   ;;   appropriately, take the log of it and add it to n.
341   ;;
342   ;; Motivated by an attempt to get LOG to work better on bignums.
343   (let ((n (integer-length x)))
344     (if (< n sb!vm:double-float-digits)
345         (log (coerce x 'double-float) 2.0d0)
346         (let ((f (ldb (byte sb!vm:double-float-digits
347                             (- n sb!vm:double-float-digits))
348                       x)))
349           (+ n (log (scale-float (coerce f 'double-float)
350                                  (- sb!vm:double-float-digits))
351                     2.0d0))))))
352
353 (defun log (number &optional (base nil base-p))
354   #!+sb-doc
355   "Return the logarithm of NUMBER in the base BASE, which defaults to e."
356   (if base-p
357       (cond
358         ((zerop base)
359          (if (or (typep number 'double-float) (typep base 'double-float))
360              0.0d0
361              0.0f0))
362         ((and (typep number '(integer (0) *))
363               (typep base '(integer (0) *)))
364          (coerce (/ (log2 number) (log2 base)) 'single-float))
365         ((and (typep number 'integer) (typep base 'double-float))
366          ;; No single float intermediate result
367          (/ (log2 number) (log base 2.0d0)))
368         ((and (typep number 'double-float) (typep base 'integer))
369          (/ (log number 2.0d0) (log2 base)))
370         (t
371          (/ (log number) (log base))))
372       (number-dispatch ((number number))
373         (((foreach fixnum bignum))
374          (if (minusp number)
375              (complex (log (- number)) (coerce pi 'single-float))
376              (coerce (/ (log2 number) (log (exp 1.0d0) 2.0d0)) 'single-float)))
377         ((ratio)
378          (if (minusp number)
379              (complex (log (- number)) (coerce pi 'single-float))
380              (let ((numerator (numerator number))
381                    (denominator (denominator number)))
382                (if (= (integer-length numerator)
383                       (integer-length denominator))
384                    (coerce (%log1p (coerce (- number 1) 'double-float))
385                            'single-float)
386                    (coerce (/ (- (log2 numerator) (log2 denominator))
387                               (log (exp 1.0d0) 2.0d0))
388                            'single-float)))))
389         (((foreach single-float double-float))
390          ;; Is (log -0) -infinity (libm.a) or -infinity + i*pi (Kahan)?
391          ;; Since this doesn't seem to be an implementation issue
392          ;; I (pw) take the Kahan result.
393          (if (< (float-sign number)
394                 (coerce 0 '(dispatch-type number)))
395              (complex (log (- number)) (coerce pi '(dispatch-type number)))
396              (coerce (%log (coerce number 'double-float))
397                      '(dispatch-type number))))
398         ((complex)
399          (complex-log number)))))
400
401 (defun sqrt (number)
402   #!+sb-doc
403   "Return the square root of NUMBER."
404   (number-dispatch ((number number))
405     (((foreach fixnum bignum ratio))
406      (if (minusp number)
407          (complex-sqrt number)
408          (coerce (%sqrt (coerce number 'double-float)) 'single-float)))
409     (((foreach single-float double-float))
410      (if (minusp number)
411          (complex-sqrt (complex number))
412          (coerce (%sqrt (coerce number 'double-float))
413                  '(dispatch-type number))))
414      ((complex)
415       (complex-sqrt number))))
416 \f
417 ;;;; trigonometic and related functions
418
419 (defun abs (number)
420   #!+sb-doc
421   "Return the absolute value of the number."
422   (number-dispatch ((number number))
423     (((foreach single-float double-float fixnum rational))
424      (abs number))
425     ((complex)
426      (let ((rx (realpart number))
427            (ix (imagpart number)))
428        (etypecase rx
429          (rational
430           (sqrt (+ (* rx rx) (* ix ix))))
431          (single-float
432           (coerce (%hypot (coerce rx 'double-float)
433                           (coerce ix 'double-float))
434                   'single-float))
435          (double-float
436           (%hypot rx ix)))))))
437
438 (defun phase (number)
439   #!+sb-doc
440   "Return the angle part of the polar representation of a complex number.
441   For complex numbers, this is (atan (imagpart number) (realpart number)).
442   For non-complex positive numbers, this is 0. For non-complex negative
443   numbers this is PI."
444   (etypecase number
445     (rational
446      (if (minusp number)
447          (coerce pi 'single-float)
448          0.0f0))
449     (single-float
450      (if (minusp (float-sign number))
451          (coerce pi 'single-float)
452          0.0f0))
453     (double-float
454      (if (minusp (float-sign number))
455          (coerce pi 'double-float)
456          0.0d0))
457     (complex
458      (atan (imagpart number) (realpart number)))))
459
460 (defun sin (number)
461   #!+sb-doc
462   "Return the sine of NUMBER."
463   (number-dispatch ((number number))
464     (handle-reals %sin number)
465     ((complex)
466      (let ((x (realpart number))
467            (y (imagpart number)))
468        (complex (* (sin x) (cosh y))
469                 (* (cos x) (sinh y)))))))
470
471 (defun cos (number)
472   #!+sb-doc
473   "Return the cosine of NUMBER."
474   (number-dispatch ((number number))
475     (handle-reals %cos number)
476     ((complex)
477      (let ((x (realpart number))
478            (y (imagpart number)))
479        (complex (* (cos x) (cosh y))
480                 (- (* (sin x) (sinh y))))))))
481
482 (defun tan (number)
483   #!+sb-doc
484   "Return the tangent of NUMBER."
485   (number-dispatch ((number number))
486     (handle-reals %tan number)
487     ((complex)
488      (complex-tan number))))
489
490 (defun cis (theta)
491   #!+sb-doc
492   "Return cos(Theta) + i sin(Theta), i.e. exp(i Theta)."
493   (declare (type real theta))
494   (complex (cos theta) (sin theta)))
495
496 (defun asin (number)
497   #!+sb-doc
498   "Return the arc sine of NUMBER."
499   (number-dispatch ((number number))
500     ((rational)
501      (if (or (> number 1) (< number -1))
502          (complex-asin number)
503          (coerce (%asin (coerce number 'double-float)) 'single-float)))
504     (((foreach single-float double-float))
505      (if (or (> number (coerce 1 '(dispatch-type number)))
506              (< number (coerce -1 '(dispatch-type number))))
507          (complex-asin (complex number))
508          (coerce (%asin (coerce number 'double-float))
509                  '(dispatch-type number))))
510     ((complex)
511      (complex-asin number))))
512
513 (defun acos (number)
514   #!+sb-doc
515   "Return the arc cosine of NUMBER."
516   (number-dispatch ((number number))
517     ((rational)
518      (if (or (> number 1) (< number -1))
519          (complex-acos number)
520          (coerce (%acos (coerce number 'double-float)) 'single-float)))
521     (((foreach single-float double-float))
522      (if (or (> number (coerce 1 '(dispatch-type number)))
523              (< number (coerce -1 '(dispatch-type number))))
524          (complex-acos (complex number))
525          (coerce (%acos (coerce number 'double-float))
526                  '(dispatch-type number))))
527     ((complex)
528      (complex-acos number))))
529
530 (defun atan (y &optional (x nil xp))
531   #!+sb-doc
532   "Return the arc tangent of Y if X is omitted or Y/X if X is supplied."
533   (if xp
534       (flet ((atan2 (y x)
535                (declare (type double-float y x)
536                         (values double-float))
537                (if (zerop x)
538                    (if (zerop y)
539                        (if (plusp (float-sign x))
540                            y
541                            (float-sign y pi))
542                        (float-sign y (/ pi 2)))
543                    (%atan2 y x))))
544         (number-dispatch ((y real) (x real))
545           ((double-float
546             (foreach double-float single-float fixnum bignum ratio))
547            (atan2 y (coerce x 'double-float)))
548           (((foreach single-float fixnum bignum ratio)
549             double-float)
550            (atan2 (coerce y 'double-float) x))
551           (((foreach single-float fixnum bignum ratio)
552             (foreach single-float fixnum bignum ratio))
553            (coerce (atan2 (coerce y 'double-float) (coerce x 'double-float))
554                    'single-float))))
555       (number-dispatch ((y number))
556         (handle-reals %atan y)
557         ((complex)
558          (complex-atan y)))))
559
560 ;;; It seems that every target system has a C version of sinh, cosh,
561 ;;; and tanh. Let's use these for reals because the original
562 ;;; implementations based on the definitions lose big in round-off
563 ;;; error. These bad definitions also mean that sin and cos for
564 ;;; complex numbers can also lose big.
565
566 (defun sinh (number)
567   #!+sb-doc
568   "Return the hyperbolic sine of NUMBER."
569   (number-dispatch ((number number))
570     (handle-reals %sinh number)
571     ((complex)
572      (let ((x (realpart number))
573            (y (imagpart number)))
574        (complex (* (sinh x) (cos y))
575                 (* (cosh x) (sin y)))))))
576
577 (defun cosh (number)
578   #!+sb-doc
579   "Return the hyperbolic cosine of NUMBER."
580   (number-dispatch ((number number))
581     (handle-reals %cosh number)
582     ((complex)
583      (let ((x (realpart number))
584            (y (imagpart number)))
585        (complex (* (cosh x) (cos y))
586                 (* (sinh x) (sin y)))))))
587
588 (defun tanh (number)
589   #!+sb-doc
590   "Return the hyperbolic tangent of NUMBER."
591   (number-dispatch ((number number))
592     (handle-reals %tanh number)
593     ((complex)
594      (complex-tanh number))))
595
596 (defun asinh (number)
597   #!+sb-doc
598   "Return the hyperbolic arc sine of NUMBER."
599   (number-dispatch ((number number))
600     (handle-reals %asinh number)
601     ((complex)
602      (complex-asinh number))))
603
604 (defun acosh (number)
605   #!+sb-doc
606   "Return the hyperbolic arc cosine of NUMBER."
607   (number-dispatch ((number number))
608     ((rational)
609      ;; acosh is complex if number < 1
610      (if (< number 1)
611          (complex-acosh number)
612          (coerce (%acosh (coerce number 'double-float)) 'single-float)))
613     (((foreach single-float double-float))
614      (if (< number (coerce 1 '(dispatch-type number)))
615          (complex-acosh (complex number))
616          (coerce (%acosh (coerce number 'double-float))
617                  '(dispatch-type number))))
618     ((complex)
619      (complex-acosh number))))
620
621 (defun atanh (number)
622   #!+sb-doc
623   "Return the hyperbolic arc tangent of NUMBER."
624   (number-dispatch ((number number))
625     ((rational)
626      ;; atanh is complex if |number| > 1
627      (if (or (> number 1) (< number -1))
628          (complex-atanh number)
629          (coerce (%atanh (coerce number 'double-float)) 'single-float)))
630     (((foreach single-float double-float))
631      (if (or (> number (coerce 1 '(dispatch-type number)))
632              (< number (coerce -1 '(dispatch-type number))))
633          (complex-atanh (complex number))
634          (coerce (%atanh (coerce number 'double-float))
635                  '(dispatch-type number))))
636     ((complex)
637      (complex-atanh number))))
638
639 \f
640 ;;;; not-OLD-SPECFUN stuff
641 ;;;;
642 ;;;; (This was conditional on #-OLD-SPECFUN in the CMU CL sources,
643 ;;;; but OLD-SPECFUN was mentioned nowhere else, so it seems to be
644 ;;;; the standard special function system.)
645 ;;;;
646 ;;;; This is a set of routines that implement many elementary
647 ;;;; transcendental functions as specified by ANSI Common Lisp.  The
648 ;;;; implementation is based on Kahan's paper.
649 ;;;;
650 ;;;; I believe I have accurately implemented the routines and are
651 ;;;; correct, but you may want to check for your self.
652 ;;;;
653 ;;;; These functions are written for CMU Lisp and take advantage of
654 ;;;; some of the features available there.  It may be possible,
655 ;;;; however, to port this to other Lisps.
656 ;;;;
657 ;;;; Some functions are significantly more accurate than the original
658 ;;;; definitions in CMU Lisp.  In fact, some functions in CMU Lisp
659 ;;;; give the wrong answer like (acos #c(-2.0 0.0)), where the true
660 ;;;; answer is pi + i*log(2-sqrt(3)).
661 ;;;;
662 ;;;; All of the implemented functions will take any number for an
663 ;;;; input, but the result will always be a either a complex
664 ;;;; single-float or a complex double-float.
665 ;;;;
666 ;;;; general functions:
667 ;;;;   complex-sqrt
668 ;;;;   complex-log
669 ;;;;   complex-atanh
670 ;;;;   complex-tanh
671 ;;;;   complex-acos
672 ;;;;   complex-acosh
673 ;;;;   complex-asin
674 ;;;;   complex-asinh
675 ;;;;   complex-atan
676 ;;;;   complex-tan
677 ;;;;
678 ;;;; utility functions:
679 ;;;;   scalb logb
680 ;;;;
681 ;;;; internal functions:
682 ;;;;    square coerce-to-complex-type cssqs complex-log-scaled
683 ;;;;
684 ;;;; references:
685 ;;;;   Kahan, W. "Branch Cuts for Complex Elementary Functions, or Much
686 ;;;;   Ado About Nothing's Sign Bit" in Iserles and Powell (eds.) "The
687 ;;;;   State of the Art in Numerical Analysis", pp. 165-211, Clarendon
688 ;;;;   Press, 1987
689 ;;;;
690 ;;;; The original CMU CL code requested:
691 ;;;;   Please send any bug reports, comments, or improvements to
692 ;;;;   Raymond Toy at <email address deleted during 2002 spam avalanche>.
693
694 ;;; FIXME: In SBCL, the floating point infinity constants like
695 ;;; SB!EXT:DOUBLE-FLOAT-POSITIVE-INFINITY aren't available as
696 ;;; constants at cross-compile time, because the cross-compilation
697 ;;; host might not have support for floating point infinities. Thus,
698 ;;; they're effectively implemented as special variable references,
699 ;;; and the code below which uses them might be unnecessarily
700 ;;; inefficient. Perhaps some sort of MAKE-LOAD-TIME-VALUE hackery
701 ;;; should be used instead?  (KLUDGED 2004-03-08 CSR, by replacing the
702 ;;; special variable references with (probably equally slow)
703 ;;; constructors)
704 ;;;
705 ;;; FIXME: As of 2004-05, when PFD noted that IMAGPART and COMPLEX
706 ;;; differ in their interpretations of the real line, IMAGPART was
707 ;;; patch, which without a certain amount of effort would have altered
708 ;;; all the branch cut treatment.  Clients of these COMPLEX- routines
709 ;;; were patched to use explicit COMPLEX, rather than implicitly
710 ;;; passing in real numbers for treatment with IMAGPART, and these
711 ;;; COMPLEX- functions altered to require arguments of type COMPLEX;
712 ;;; however, someone needs to go back to Kahan for the definitive
713 ;;; answer for treatment of negative real floating point numbers and
714 ;;; branch cuts.  If adjustment is needed, it is probably the removal
715 ;;; of explicit calls to COMPLEX in the clients of irrational
716 ;;; functions.  -- a slightly bitter CSR, 2004-05-16
717
718 (declaim (inline square))
719 (defun square (x)
720   (declare (double-float x))
721   (* x x))
722
723 ;;; original CMU CL comment, apparently re. SCALB and LOGB and
724 ;;; perhaps CSSQS:
725 ;;;   If you have these functions in libm, perhaps they should be used
726 ;;;   instead of these Lisp versions. These versions are probably good
727 ;;;   enough, especially since they are portable.
728
729 ;;; Compute 2^N * X without computing 2^N first. (Use properties of
730 ;;; the underlying floating-point format.)
731 (declaim (inline scalb))
732 (defun scalb (x n)
733   (declare (type double-float x)
734            (type double-float-exponent n))
735   (scale-float x n))
736
737 ;;; This is like LOGB, but X is not infinity and non-zero and not a
738 ;;; NaN, so we can always return an integer.
739 (declaim (inline logb-finite))
740 (defun logb-finite (x)
741   (declare (type double-float x))
742   (multiple-value-bind (signif exponent sign)
743       (decode-float x)
744     (declare (ignore signif sign))
745     ;; DECODE-FLOAT is almost right, except that the exponent is off
746     ;; by one.
747     (1- exponent)))
748
749 ;;; Compute an integer N such that 1 <= |2^N * x| < 2.
750 ;;; For the special cases, the following values are used:
751 ;;;    x             logb
752 ;;;   NaN            NaN
753 ;;;   +/- infinity   +infinity
754 ;;;   0              -infinity
755 (defun logb (x)
756   (declare (type double-float x))
757   (cond ((float-nan-p x)
758          x)
759         ((float-infinity-p x)
760          ;; DOUBLE-FLOAT-POSITIVE-INFINITY
761          (double-from-bits 0 (1+ sb!vm:double-float-normal-exponent-max) 0))
762         ((zerop x)
763          ;; The answer is negative infinity, but we are supposed to
764           ;; signal divide-by-zero, so do the actual division
765          (/ -1.0d0 x)
766          )
767         (t
768           (logb-finite x))))
769
770 ;;; This function is used to create a complex number of the
771 ;;; appropriate type:
772 ;;;   Create complex number with real part X and imaginary part Y
773 ;;;   such that has the same type as Z.  If Z has type (complex
774 ;;;   rational), the X and Y are coerced to single-float.
775 #!+long-float (eval-when (:compile-toplevel :load-toplevel :execute)
776                 (error "needs work for long float support"))
777 (declaim (inline coerce-to-complex-type))
778 (defun coerce-to-complex-type (x y z)
779   (declare (double-float x y)
780            (number z))
781   (if (typep (realpart z) 'double-float)
782       (complex x y)
783       ;; Convert anything that's not already a DOUBLE-FLOAT (because
784       ;; the initial argument was a (COMPLEX DOUBLE-FLOAT) and we
785       ;; haven't done anything to lose precision) to a SINGLE-FLOAT.
786       (complex (float x 1f0)
787                (float y 1f0))))
788
789 ;;; Compute |(x+i*y)/2^k|^2 scaled to avoid over/underflow. The
790 ;;; result is r + i*k, where k is an integer.
791 #!+long-float (eval-when (:compile-toplevel :load-toplevel :execute)
792                 (error "needs work for long float support"))
793 (defun cssqs (z)
794   (let ((x (float (realpart z) 1d0))
795         (y (float (imagpart z) 1d0)))
796     ;; Would this be better handled using an exception handler to
797     ;; catch the overflow or underflow signal?  For now, we turn all
798     ;; traps off and look at the accrued exceptions to see if any
799     ;; signal would have been raised.
800     (with-float-traps-masked (:underflow :overflow)
801       (let ((rho (+ (square x) (square y))))
802        (declare (optimize (speed 3) (space 0)))
803       (cond ((and (or (float-nan-p rho)
804                       (float-infinity-p rho))
805                   (or (float-infinity-p (abs x))
806                       (float-infinity-p (abs y))))
807              ;; DOUBLE-FLOAT-POSITIVE-INFINITY
808              (values
809               (double-from-bits 0 (1+ sb!vm:double-float-normal-exponent-max) 0)
810               0))
811             ((let ((threshold
812                     ;; (/ least-positive-double-float double-float-epsilon)
813                     (load-time-value
814                      #!-long-float
815                      (sb!kernel:make-double-float #x1fffff #xfffffffe)
816                      #!+long-float
817                      (error "(/ least-positive-long-float long-float-epsilon)")))
818                    (traps (ldb sb!vm::float-sticky-bits
819                                (sb!vm:floating-point-modes))))
820                 ;; Overflow raised or (underflow raised and rho <
821                 ;; lambda/eps)
822                (or (not (zerop (logand sb!vm:float-overflow-trap-bit traps)))
823                    (and (not (zerop (logand sb!vm:float-underflow-trap-bit
824                                             traps)))
825                         (< rho threshold))))
826               ;; If we're here, neither x nor y are infinity and at
827               ;; least one is non-zero.. Thus logb returns a nice
828               ;; integer.
829               (let ((k (- (logb-finite (max (abs x) (abs y))))))
830                 (values (+ (square (scalb x k))
831                            (square (scalb y k)))
832                         (- k))))
833              (t
834               (values rho 0)))))))
835
836 ;;; principal square root of Z
837 ;;;
838 ;;; Z may be RATIONAL or COMPLEX; the result is always a COMPLEX.
839 (defun complex-sqrt (z)
840   ;; KLUDGE: Here and below, we can't just declare Z to be of type
841   ;; COMPLEX, because one-arg COMPLEX on rationals returns a rational.
842   ;; Since there isn't a rational negative zero, this is OK from the
843   ;; point of view of getting the right answer in the face of branch
844   ;; cuts, but declarations of the form (OR RATIONAL COMPLEX) are
845   ;; still ugly.  -- CSR, 2004-05-16
846   (declare (type (or complex rational) z))
847   (multiple-value-bind (rho k)
848       (cssqs z)
849     (declare (type (or (member 0d0) (double-float 0d0)) rho)
850              (type fixnum k))
851     (let ((x (float (realpart z) 1.0d0))
852           (y (float (imagpart z) 1.0d0))
853           (eta 0d0)
854           (nu 0d0))
855       (declare (double-float x y eta nu))
856
857       (locally
858          ;; space 0 to get maybe-inline functions inlined.
859          (declare (optimize (speed 3) (space 0)))
860
861       (if (not (float-nan-p x))
862           (setf rho (+ (scalb (abs x) (- k)) (sqrt rho))))
863
864       (cond ((oddp k)
865              (setf k (ash k -1)))
866             (t
867              (setf k (1- (ash k -1)))
868              (setf rho (+ rho rho))))
869
870       (setf rho (scalb (sqrt rho) k))
871
872       (setf eta rho)
873       (setf nu y)
874
875       (when (/= rho 0d0)
876             (when (not (float-infinity-p (abs nu)))
877                   (setf nu (/ (/ nu rho) 2d0)))
878             (when (< x 0d0)
879                   (setf eta (abs nu))
880                   (setf nu (float-sign y rho))))
881        (coerce-to-complex-type eta nu z)))))
882
883 ;;; Compute log(2^j*z).
884 ;;;
885 ;;; This is for use with J /= 0 only when |z| is huge.
886 (defun complex-log-scaled (z j)
887   (declare (type (or rational complex) z)
888            (fixnum j))
889   ;; The constants t0, t1, t2 should be evaluated to machine
890   ;; precision.  In addition, Kahan says the accuracy of log1p
891   ;; influences the choices of these constants but doesn't say how to
892   ;; choose them.  We'll just assume his choices matches our
893   ;; implementation of log1p.
894   (let ((t0 (load-time-value
895              #!-long-float
896              (sb!kernel:make-double-float #x3fe6a09e #x667f3bcd)
897              #!+long-float
898              (error "(/ (sqrt 2l0))")))
899         ;; KLUDGE: if repeatable fasls start failing under some weird
900         ;; xc host, this 1.2d0 might be a good place to examine: while
901         ;; it _should_ be the same in all vaguely-IEEE754 hosts, 1.2
902         ;; is not exactly representable, so something could go wrong.
903         (t1 1.2d0)
904         (t2 3d0)
905         (ln2 (load-time-value
906               #!-long-float
907               (sb!kernel:make-double-float #x3fe62e42 #xfefa39ef)
908               #!+long-float
909               (error "(log 2l0)")))
910         (x (float (realpart z) 1.0d0))
911         (y (float (imagpart z) 1.0d0)))
912     (multiple-value-bind (rho k)
913         (cssqs z)
914       (declare (optimize (speed 3)))
915       (let ((beta (max (abs x) (abs y)))
916             (theta (min (abs x) (abs y))))
917         (coerce-to-complex-type (if (and (zerop k)
918                  (< t0 beta)
919                  (or (<= beta t1)
920                      (< rho t2)))
921                                   (/ (%log1p (+ (* (- beta 1.0d0)
922                                        (+ beta 1.0d0))
923                                     (* theta theta)))
924                                      2d0)
925                                   (+ (/ (log rho) 2d0)
926                                      (* (+ k j) ln2)))
927                                 (atan y x)
928                                 z)))))
929
930 ;;; log of Z = log |Z| + i * arg Z
931 ;;;
932 ;;; Z may be any number, but the result is always a complex.
933 (defun complex-log (z)
934   (declare (type (or rational complex) z))
935   (complex-log-scaled z 0))
936
937 ;;; KLUDGE: Let us note the following "strange" behavior. atanh 1.0d0
938 ;;; is +infinity, but the following code returns approx 176 + i*pi/4.
939 ;;; The reason for the imaginary part is caused by the fact that arg
940 ;;; i*y is never 0 since we have positive and negative zeroes. -- rtoy
941 ;;; Compute atanh z = (log(1+z) - log(1-z))/2.
942 (defun complex-atanh (z)
943   (declare (type (or rational complex) z))
944   (let* (;; constants
945          (theta (/ (sqrt most-positive-double-float) 4.0d0))
946          (rho (/ 4.0d0 (sqrt most-positive-double-float)))
947          (half-pi (/ pi 2.0d0))
948          (rp (float (realpart z) 1.0d0))
949          (beta (float-sign rp 1.0d0))
950          (x (* beta rp))
951          (y (* beta (- (float (imagpart z) 1.0d0))))
952          (eta 0.0d0)
953          (nu 0.0d0))
954     ;; Shouldn't need this declare.
955     (declare (double-float x y))
956     (locally
957        (declare (optimize (speed 3)))
958     (cond ((or (> x theta)
959                (> (abs y) theta))
960            ;; To avoid overflow...
961            (setf nu (float-sign y half-pi))
962            ;; ETA is real part of 1/(x + iy).  This is x/(x^2+y^2),
963            ;; which can cause overflow.  Arrange this computation so
964            ;; that it won't overflow.
965            (setf eta (let* ((x-bigger (> x (abs y)))
966                             (r (if x-bigger (/ y x) (/ x y)))
967                             (d (+ 1.0d0 (* r r))))
968                        (if x-bigger
969                            (/ (/ x) d)
970                            (/ (/ r y) d)))))
971           ((= x 1.0d0)
972            ;; Should this be changed so that if y is zero, eta is set
973            ;; to +infinity instead of approx 176?  In any case
974            ;; tanh(176) is 1.0d0 within working precision.
975            (let ((t1 (+ 4d0 (square y)))
976                  (t2 (+ (abs y) rho)))
977              (setf eta (log (/ (sqrt (sqrt t1))
978                                (sqrt t2))))
979              (setf nu (* 0.5d0
980                          (float-sign y
981                                      (+ half-pi (atan (* 0.5d0 t2))))))))
982           (t
983            (let ((t1 (+ (abs y) rho)))
984               ;; Normal case using log1p(x) = log(1 + x)
985              (setf eta (* 0.25d0
986                           (%log1p (/ (* 4.0d0 x)
987                                      (+ (square (- 1.0d0 x))
988                                         (square t1))))))
989              (setf nu (* 0.5d0
990                          (atan (* 2.0d0 y)
991                                (- (* (- 1.0d0 x)
992                                      (+ 1.0d0 x))
993                                   (square t1))))))))
994     (coerce-to-complex-type (* beta eta)
995                             (- (* beta nu))
996                              z))))
997
998 ;;; Compute tanh z = sinh z / cosh z.
999 (defun complex-tanh (z)
1000   (declare (type (or rational complex) z))
1001   (let ((x (float (realpart z) 1.0d0))
1002         (y (float (imagpart z) 1.0d0)))
1003     (locally
1004       ;; space 0 to get maybe-inline functions inlined
1005       (declare (optimize (speed 3) (space 0)))
1006     (cond ((> (abs x)
1007               (load-time-value
1008                #!-long-float
1009                (sb!kernel:make-double-float #x406633ce #x8fb9f87e)
1010                #!+long-float
1011                (error "(/ (+ (log 2l0) (log most-positive-long-float)) 4l0)")))
1012            (coerce-to-complex-type (float-sign x)
1013                                    (float-sign y) z))
1014           (t
1015            (let* ((tv (%tan y))
1016                   (beta (+ 1.0d0 (* tv tv)))
1017                   (s (sinh x))
1018                   (rho (sqrt (+ 1.0d0 (* s s)))))
1019              (if (float-infinity-p (abs tv))
1020                  (coerce-to-complex-type (/ rho s)
1021                                          (/ tv)
1022                                          z)
1023                  (let ((den (+ 1.0d0 (* beta s s))))
1024                    (coerce-to-complex-type (/ (* beta rho s)
1025                                               den)
1026                                            (/ tv den)
1027                                             z)))))))))
1028
1029 ;;; Compute acos z = pi/2 - asin z.
1030 ;;;
1031 ;;; Z may be any NUMBER, but the result is always a COMPLEX.
1032 (defun complex-acos (z)
1033   ;; Kahan says we should only compute the parts needed.  Thus, the
1034   ;; REALPART's below should only compute the real part, not the whole
1035   ;; complex expression.  Doing this can be important because we may get
1036   ;; spurious signals that occur in the part that we are not using.
1037   ;;
1038   ;; However, we take a pragmatic approach and just use the whole
1039   ;; expression.
1040   ;;
1041   ;; NOTE: The formula given by Kahan is somewhat ambiguous in whether
1042   ;; it's the conjugate of the square root or the square root of the
1043   ;; conjugate.  This needs to be checked.
1044   ;;
1045   ;; I checked.  It doesn't matter because (conjugate (sqrt z)) is the
1046   ;; same as (sqrt (conjugate z)) for all z.  This follows because
1047   ;;
1048   ;; (conjugate (sqrt z)) = exp(0.5*log |z|)*exp(-0.5*j*arg z).
1049   ;;
1050   ;; (sqrt (conjugate z)) = exp(0.5*log|z|)*exp(0.5*j*arg conj z)
1051   ;;
1052   ;; and these two expressions are equal if and only if arg conj z =
1053   ;; -arg z, which is clearly true for all z.
1054   (declare (type (or rational complex) z))
1055   (let ((sqrt-1+z (complex-sqrt (+ 1 z)))
1056         (sqrt-1-z (complex-sqrt (- 1 z))))
1057     (with-float-traps-masked (:divide-by-zero)
1058       (complex (* 2 (atan (/ (realpart sqrt-1-z)
1059                              (realpart sqrt-1+z))))
1060                (asinh (imagpart (* (conjugate sqrt-1+z)
1061                                    sqrt-1-z)))))))
1062
1063 ;;; Compute acosh z = 2 * log(sqrt((z+1)/2) + sqrt((z-1)/2))
1064 ;;;
1065 ;;; Z may be any NUMBER, but the result is always a COMPLEX.
1066 (defun complex-acosh (z)
1067   (declare (type (or rational complex) z))
1068   (let ((sqrt-z-1 (complex-sqrt (- z 1)))
1069         (sqrt-z+1 (complex-sqrt (+ z 1))))
1070     (with-float-traps-masked (:divide-by-zero)
1071       (complex (asinh (realpart (* (conjugate sqrt-z-1)
1072                                    sqrt-z+1)))
1073                (* 2 (atan (/ (imagpart sqrt-z-1)
1074                              (realpart sqrt-z+1))))))))
1075
1076 ;;; Compute asin z = asinh(i*z)/i.
1077 ;;;
1078 ;;; Z may be any NUMBER, but the result is always a COMPLEX.
1079 (defun complex-asin (z)
1080   (declare (type (or rational complex) z))
1081   (let ((sqrt-1-z (complex-sqrt (- 1 z)))
1082         (sqrt-1+z (complex-sqrt (+ 1 z))))
1083     (with-float-traps-masked (:divide-by-zero)
1084       (complex (atan (/ (realpart z)
1085                         (realpart (* sqrt-1-z sqrt-1+z))))
1086                (asinh (imagpart (* (conjugate sqrt-1-z)
1087                                    sqrt-1+z)))))))
1088
1089 ;;; Compute asinh z = log(z + sqrt(1 + z*z)).
1090 ;;;
1091 ;;; Z may be any number, but the result is always a complex.
1092 (defun complex-asinh (z)
1093   (declare (type (or rational complex) z))
1094   ;; asinh z = -i * asin (i*z)
1095   (let* ((iz (complex (- (imagpart z)) (realpart z)))
1096          (result (complex-asin iz)))
1097     (complex (imagpart result)
1098              (- (realpart result)))))
1099
1100 ;;; Compute atan z = atanh (i*z) / i.
1101 ;;;
1102 ;;; Z may be any number, but the result is always a complex.
1103 (defun complex-atan (z)
1104   (declare (type (or rational complex) z))
1105   ;; atan z = -i * atanh (i*z)
1106   (let* ((iz (complex (- (imagpart z)) (realpart z)))
1107          (result (complex-atanh iz)))
1108     (complex (imagpart result)
1109              (- (realpart result)))))
1110
1111 ;;; Compute tan z = -i * tanh(i * z)
1112 ;;;
1113 ;;; Z may be any number, but the result is always a complex.
1114 (defun complex-tan (z)
1115   (declare (type (or rational complex) z))
1116   ;; tan z = -i * tanh(i*z)
1117   (let* ((iz (complex (- (imagpart z)) (realpart z)))
1118          (result (complex-tanh iz)))
1119     (complex (imagpart result)
1120              (- (realpart result)))))