Replace Python program auto-generated for documentation categories
[maxima/cygwin.git] / src / rpart.lisp
blob7b25b565ca9695d07f91e3d40e620ff49304bfbf
1 ;;; -*- Mode: Lisp; Package: Maxima; Syntax: Common-Lisp; Base: 10 -*- ;;;;
2 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
3 ;;; The data in this file contains enhancments. ;;;;;
4 ;;; ;;;;;
5 ;;; Copyright (c) 1984,1987 by William Schelter,University of Texas ;;;;;
6 ;;; All rights reserved ;;;;;
7 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
8 ;;; (c) Copyright 1982 Massachusetts Institute of Technology ;;;
9 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
11 (in-package :maxima)
13 (macsyma-module rpart)
15 ;;; Complex variable utilities
16 ;;;
17 ;;; Macsyma functions: $realpart $imagpart $rectform $polarform
18 ;;; $cabs $carg
19 ;;; Utility functions: trisplit risplit absarg cabs andmapc andmapcar
21 (load-macsyma-macros rzmac)
23 (declare-top (special $%emode $radexpand rp-polylogp $domain $m1pbranch
24 $logarc rischp $keepfloat))
26 (defmvar implicit-real nil "If t RPART assumes radicals and logs
27 of real quantities are real and doesn't ask sign questions")
29 (defmvar generate-atan2 t "Controls whether RPART will generate ATAN's
30 or ATAN2's, default is to make ATAN2's")
31 ;; generate-atan2 is set to nil when doing integration to avoid
32 ;; generating discontinuities that defint can't handle.
34 ;;; Realpart gives the real part of an expr.
36 (defmfun $realpart (xx) (car (trisplit xx)))
38 (defprop $realpart %realpart verb)
39 (defprop %realpart $realpart noun)
40 (defprop %realpart simp-realpart operators)
42 (defun risplit-signum (x) ;rectangular form for a signum expression
43 (let* ((z (risplit (cadr x))) (a (car z)) (b (cdr z)) (r)) ;signum(a+%i b), where a and b are real
44 (cond ((eq t (meqp b 0)) ;signum(a) -> signum(a) + 0 %i
45 (cons (take '(%signum) a) 0))
46 ((or (eq t (mnqp a 0)) (eq t (mnqp b 0))) ;signum(a + %i b) --> a/sqrt(a^2+b^2) + %i b/sqrt(a^2+b^2)
47 (setq r (take '(%sqrt) (add (power a 2) (power b 2))))
48 (cons (div a r) (div b r)))
49 (t (cons (take '(%realpart) x) (take '(%imagpart) x)))))) ;nothing known
51 (setf (get '%signum 'risplit-function) #'risplit-signum)
53 (defun simp-realpart (expr z simpflag)
54 (oneargcheck expr)
55 (setq z (simpcheck (cadr expr) simpflag))
56 (let ((sgn nil))
57 (cond ((mnump z) z)
58 ((eq (setq sgn ($csign z)) '$imaginary)
60 ((eq sgn '$complex)
61 (cond ((complex-number-p ($expand z) 'bigfloat-or-number-p)
62 ($realpart z))
63 (t
64 (eqtest (list '(%realpart) z) expr))))
65 (t
66 (eqtest (list '(%realpart) z) expr)))))
68 ;;; Imagpart gives the imaginary part of an expr.
70 (defmfun $imagpart (xx) (cdr (trisplit xx)))
72 (defprop $imagpart %imagpart verb)
73 (defprop %imagpart $imagpart noun)
74 (defprop %imagpart simp-imagpart operators)
76 (defun simp-imagpart (expr z simpflag)
77 (oneargcheck expr)
78 (setq z (simpcheck (cadr expr) simpflag))
79 (let ((sgn nil))
80 (cond ((mnump z) 0)
81 ((eq (setq sgn ($csign z)) '$imaginary)
82 (mul -1 '$%i z))
83 ((eq sgn '$complex)
84 (cond ((complex-number-p ($expand z) 'bigfloat-or-number-p)
85 ($imagpart z))
86 (t
87 (eqtest (list '(%imagpart) z) expr))))
88 (t
89 (eqtest (list '(%imagpart) z) expr)))))
91 ;;; Rectform gives a result of the form a+b*%i.
93 (defmfun $rectform (xx)
94 (let ((ris (trisplit xx)))
95 (add (car ris) (mul (cdr ris) '$%i))))
97 ;;; Polarform gives a result of the form a*%e^(%i*b).
99 (defmfun $polarform (xx)
100 (cond ((mbagp xx)
101 (cons (car xx) (mapcar #'$polarform (cdr xx))))
103 (let ((aas (absarg xx)) ($%emode nil))
104 (mul (car aas) (powers '$%e (mul '$%i (cdr aas))))))))
106 ;;; Cabs gives the complex absolute value. Nota bene: an expression may
107 ;;; be syntactically real without being real (e.g. sqrt(x), x<0). Thus
108 ;;; Cabs must lead an independent existence from Abs.
110 (defmfun $cabs (xx) (cabs xx))
112 (defprop $cabs %cabs verb)
113 (defprop %cabs $cabs noun)
114 (defprop %cabs simp-cabs operators)
116 (defun simp-cabs (expr z simpflag)
117 (oneargcheck expr)
118 (setq z (simpcheck (cadr expr) simpflag))
119 (let ((sgn nil))
120 (cond ((member (setq sgn ($csign z)) '($complex $imaginary))
121 (cond ((complex-number-p ($expand z) 'bigfloat-or-number-p)
122 (simplify (list '(mabs) z)))
124 (eqtest (list '(mabs) z) expr))))
125 ((eq sgn '$zero)
127 ((member sgn '($pos $pz))
129 ((eq sgn '$neg)
130 (mul -1 z))
132 (eqtest (list '(mabs) z) expr)))))
134 ;;; Carg gives the complex argument.
136 (defmfun $carg (xx)
137 (cond ((mbagp xx)
138 (cons (car xx) (mapcar #'$carg (cdr xx))))
139 (t (cdr (absarg xx)))))
141 (defprop $carg %carg verb)
142 (defprop %carg $carg noun)
143 (defprop %carg simp-carg operators)
145 (defun simp-carg (expr z simpflag)
146 (oneargcheck expr)
147 (setq z (simpcheck (cadr expr) simpflag))
148 (let ((sgn nil))
149 (cond ((eq z '$%i)
150 (div '$%pi 2))
151 ((member (setq sgn ($csign z)) '($complex $imaginary))
152 (cond ((complex-number-p ($expand z) 'bigfloat-or-number-p)
153 ($carg z))
155 (eqtest (list '(%carg) z) expr))))
156 ((member sgn '($pos $pz $zero))
158 ((eq sgn '$neg)
159 '$%pi)
161 (eqtest (list '(%carg) z) expr)))))
163 ;; The internal cabs, used by other Macsyma programs.
164 (defun cabs (xx) (car (absarg xx t)))
166 ;; Some objects can only appear at the top level of a legal simplified
167 ;; expression: CRE forms and equations in particular.
169 (defun trisplit (el) ; Top level of risplit
170 (cond ((atom el) (risplit el))
171 ((specrepp el) (trisplit (specdisrep el)))
172 ((eq (caar el) 'mequal) (dot-sp-ri (cdr el) '(mequal simp)))
173 (t (risplit el))))
175 ;;; Auxiliaries
177 ;; These are Macsyma equivalents to (mapcar 'trisplit ...). They must
178 ;; differ from other maps for two reasons: the lists are Macsyma lists,
179 ;; and therefore prefixed with list indicators; and the results must
180 ;; be separated: ((a . b) (c . d)) becomes something like ([a,c].[b,d]).
182 (defun dsrl (el) (dot-sp-ri (cdr el) '(mlist simp)))
184 (defun dot-sp-ri (el ind)
185 (dot--ri (mapcar #'trisplit el) ind))
187 ;; Dot--ri does the ((a.b)(c.d))->([a,c].[b,d]) transformation with
188 ;; minimal Cons'ing.
190 (defun dot--ri (el ind)
191 (do ((i el (cdr i)) (k))
192 ((null i) (cons (cons ind (nreverse k)) (cons ind el)))
193 (let ((cdari (cdar i)))
194 (setq k (rplacd (car i) k))
195 (rplaca i cdari))))
197 (defun risplit-mplus (l)
198 (do ((rpart) (ipart) (m (cdr l) (cdr m)))
199 ((null m) (cons (addn rpart t) (addn ipart t)))
200 (let ((sp (risplit (car m))))
201 (cond ((=0 (car sp)))
202 (t (setq rpart (cons (car sp) rpart))))
203 (cond ((=0 (cdr sp)))
204 (t (setq ipart (cons (cdr sp) ipart)))))))
206 (defun risplit-times (l)
207 (let ((risl (do ((purerl nil)
208 (compl nil)
209 (l (cdr l) (cdr l)))
210 ((null l) (cons purerl compl))
211 (let ((sp (risplit (car l))))
212 (cond ((=0 (cdr sp))
213 (setq purerl (rplacd sp purerl)))
214 ((or (atom (car sp)) (atom (cdr sp)))
215 (setq compl (cons sp compl)))
216 ((and (eq (caaar sp) 'mtimes)
217 ;;;Try risplit z/w and notice denominator. If this check were not made,
218 ;;; the real and imaginary parts would not each be over a common denominator.
219 (eq (caadr sp) 'mtimes)
220 (let ((nr (nreverse (cdar sp)))
221 (ni (nreverse (cddr sp))))
222 (cond ((equal (car nr) (car ni))
223 (push (car nr) purerl)
224 (push (cons (muln (nreverse (cdr nr)) t)
225 (muln (nreverse (cdr ni)) t))
226 compl))
228 (setq nr (nreverse nr))
229 (setq ni (nreverse ni))
230 nil)))))
232 (push sp compl)))))))
233 (cond ((null (cdr risl))
234 (cons (muln (car risl) t) 0))
236 (do ((rpart 1) (ipart 0) (m (cdr risl) (cdr m)))
237 ((null m)
238 (cons (muln (cons rpart (car risl)) t)
239 (muln (cons ipart (car risl)) t)))
240 (psetq rpart (sub (mul rpart (caar m)) (mul ipart (cdar m)))
241 ipart (add (mul ipart (caar m)) (mul rpart (cdar m)))))))))
243 ;; Split L = ((mexpt) BASE POW) into real and imaginary parts.
244 (defun risplit-expt (l)
245 (let* ((base (cadr l)) (pow (caddr l))
246 ;; Disable 'simplifications' like sqrt(-x) -> %i*sqrt(x)
247 ($radexpand nil)
248 (sp (risplit base)))
249 (cond
250 ((fixnump pow)
251 (risplit-expt-fixnum-pow sp pow))
253 ((and (ratnump pow)
254 (fixnump (cadr pow))
255 (not (< (cadr pow) (- $maxnegex)))
256 (not (> (cadr pow) $maxposex))
257 (or (= (caddr pow) 2) (=0 (cdr sp))))
258 (if (=0 (cdr sp))
259 (risplit-expt-real^rat base pow)
260 (risplit-expt-sqrt-pow base sp pow)))
262 ((and (floatp base) (floatp pow))
263 (risplit (let (($numer t)) (exptrl base pow))))
266 (destructuring-bind (alpha . beta) (risplit pow)
267 (destructuring-bind (r . theta) (absarg1 base)
268 (risplit-expt-general-form r theta alpha beta)))))))
270 ;; Split BASE^POWER into real and imaginary parts. POWER is assumed to be a
271 ;; fixnum. SP is (RISPLIT BASE)
272 (defun risplit-expt-fixnum-pow (sp power)
273 ;; We use the squared absolute value of BASE several times
274 ;; below. Unfortunately, we can't calculate it at the start, since that causes
275 ;; floating point under/overflows in the case mentioned in the comment
276 ;; below. Instead, we calculate it when it's needed (a maximum of once).
277 (destructuring-bind (real . imag) sp
278 (cond
279 ((= power -1)
280 ;; Handle the case of 1/(x+%i*y) carefully. This
281 ;; is needed if x and y are (Lisp) numbers to
282 ;; prevent spurious underflows/overflows. See bug 1908.
283 (if (and (or (numberp real) (ratnump real))
284 (or (numberp imag) (ratnump imag)))
285 (sprecip sp)
286 (let ((abs2 (spabs sp)))
287 (cons (div real abs2) (mul -1 (div imag abs2))))))
289 ((> (abs power) $maxposex)
290 (if (=0 imag)
291 (cons (powers real power) 0)
292 (let ((abs^n (powers (spabs sp) (*red power 2)))
293 (natan (mul power (genatan imag real))))
294 (cons (mul abs^n (take '(%cos) natan))
295 (mul abs^n (take '(%sin) natan))))))
297 ((> power 0)
298 (expanintexpt sp power))
301 (let ((abbas (powers (spabs sp) (- power)))
302 (basspli (expanintexpt sp (- power))))
303 (cons (div (car basspli) abbas)
304 (neg (div (cdr basspli) abbas))))))))
306 ;; Return the "general form" for RISPLIT applied to
307 ;; (r*exp(%i*theta))^(alpha+%i*beta), whose rectform is
309 ;; pre * cos(post) + %i * pre * sin(post)
311 ;; where pre = exp(-theta*beta) * r^alpha
312 ;; and post = beta*log(r) + alpha*theta
313 (defun risplit-expt-general-form (r theta alpha beta)
314 (let ((pre (mul (powers '$%e (mul -1 theta beta))
315 (powers r alpha)))
316 (post (add (mul beta (take '(%log) r))
317 (mul alpha theta))))
318 (cons (mul pre (take '(%cos) post))
319 (mul pre (take '(%sin) post)))))
321 ;; Split BASE^POWER into real and imaginary parts. We assume that BASE is real
322 ;; and that POWER is a rational number.
323 (defun risplit-expt-real^rat (base power)
324 (case (cond ((mnegp base) '$neg)
325 (implicit-real '$pos)
326 (t ($sign base))) ; Use $sign not asksign
327 ($neg (risplit (mul2 (power -1 power) (power (neg base) power))))
328 ($zero (cons (power 0 power) 0))
329 ($pos (cons (power base power) 0))
331 (destructuring-bind (r . theta) (absarg1 base)
332 (risplit-expt-general-form r theta power 0)))))
334 ;; Split BASE^POWER into real and imaginary parts. SP is (RISPLIT BASE). We
335 ;; assume that POWER is a rational number. Moreover, we assume that the
336 ;; denominator of POWER is 2.
337 (defun risplit-expt-sqrt-pow (base sp power)
338 ;; n = abs(2*power) is a non-negative integer
339 (destructuring-bind (real . imag) sp
340 (let* ((abs2 (spabs sp)) (abs (power abs2 1//2))
341 (n (abs (cadr power)))
342 (pos? (> (cadr power) -1))
343 (imag-sign ($sign imag)))
344 (cond
345 ((member imag-sign '($neg $pos))
346 ;; Here, we use the half-angle formulas for cos and sin. Assuming we
347 ;; are always taking the "principal square root" (that with argument
348 ;; less than equal to the argument of base), these come out as
350 ;; cos(arg/2) = +- sqrt((1+real/abs)/2)
351 ;; sin(arg/2) = +- sqrt((1-real/abs)/2)
353 ;; We know that real+%i*imag = abs*exp(%i*arg). Taking square roots,
354 ;; you get that
356 ;; sqrt(real+%i*imag) = sqrt(abs)*exp(%i*arg/2).
357 ;; = sqrt(abs)*cos(arg/2) +
358 ;; %i * sqrt(abs)*sin(arg/2)
359 ;; = (sqrt(abs+real) + %i*sqrt(abs-real))/sqrt(2)
361 ;; but possibly with signs on the square roots. This function always
362 ;; chooses the square root with the non-negative real part. As such, we
363 ;; have to switch the sign of the sine term when we are raising to a
364 ;; positive power and imag < 0 or if raising to a negative power and
365 ;; imag > 0. To see that the first argument of the PORM call below is
366 ;; correct, write out the 2x2 truth table...
367 (divcarcdr
368 (expanintexpt
369 (cons (power (add abs real) 1//2)
370 (porm (eq (eq imag-sign '$pos) pos?)
371 (power (sub abs real) 1//2)))
373 (if pos?
374 (power 2 (div n 2))
375 (power (mul 2 abs2) (div n 2)))))
378 (destructuring-bind (alpha . beta) (risplit power)
379 (destructuring-bind (r . theta) (absarg1 base)
380 (risplit-expt-general-form r theta alpha beta))))))))
382 (defun risplit-noun (l)
383 (cons (simplify (list '(%realpart) l)) (simplify (list '(%imagpart) l))))
386 (defun absarg1 (arg)
387 (let ((arg1 arg) ($keepfloat t))
388 (cond ((and (or (free arg '$%i)
389 (free (setq arg1 (sratsimp arg)) '$%i))
390 (not (eq (csign arg1) t)))
391 (setq arg arg1)
392 (if implicit-real
393 (cons arg 0)
394 (unwind-protect
395 (prog2 (assume `(($notequal) ,arg 0))
396 (absarg arg))
397 (forget `(($notequal) ,arg 0)))))
398 (t (absarg arg)))))
400 ;;; Main function
401 ;;; Takes an expression and returns the dotted pair
402 ;;; (<Real part> . <imaginary part>).
404 (defun risplit (l)
405 (let (($domain '$complex) ($m1pbranch t) $logarc op)
406 (cond ((atom l)
407 ;; Symbols are assumed to represent real values, unless they have
408 ;; been declared to be complex. If they have been declared to be both
409 ;; real and complex, they are taken to be real.
410 (cond ((eq l '$%i) (cons 0 1))
411 ((eq l '$infinity) (cons '$und '$und))
412 ((and (decl-complexp l) (not (decl-realp l))) (risplit-noun l))
413 (t (cons l 0))))
414 ((eq (caar l) 'rat) (cons l 0))
415 ((eq (caar l) 'mplus) (risplit-mplus l))
416 ((eq (caar l) 'mtimes) (risplit-times l))
417 ((eq (caar l) 'mexpt) (risplit-expt l))
418 ((eq (caar l) '%log)
419 (let ((aa (absarg1 (cadr l))))
420 (rplaca aa (take '(%log) (car aa)))))
421 ((eq (caar l) 'bigfloat) (cons l 0)) ;All numbers are real.
422 ((and (member (caar l) '(%integrate %derivative %laplace %sum) :test #'eq)
423 (freel (cddr l) '$%i))
424 (let ((ris (risplit (cadr l))))
425 (cons (simplify (list* (ncons (caar l)) (car ris) (cddr l)))
426 (simplify (list* (ncons (caar l)) (cdr ris) (cddr l))))))
427 ((eq (caar l) '$conjugate)
428 (cons (simplify (list '(%realpart) (cadr l)))
429 (mul -1 (simplify (list '(%imagpart) (cadr l))))))
430 ((let ((ass (assoc (caar l)
431 '((%sin %cosh %cos . %sinh)
432 (%cos %cosh %sin . %sinh)
433 (%sinh %cos %cosh . %sin)
434 (%cosh %cos %sinh . %sin)) :test #'eq)))
435 ;;;This clause handles the very similar trigonometric and hyperbolic functions.
436 ;;; It is driven by the table at the end of the lambda.
437 (and ass
438 (let ((ri (risplit (cadr l))))
439 (cond ((=0 (cdr ri)) ;Pure real case.
440 (cons (take (list (car ass)) (car ri)) 0))
442 (cons (mul (take (list (car ass)) (car ri))
443 (take (list (cadr ass)) (cdr ri)))
444 (negate-if (eq (caar l) '%cos)
445 (mul (take (list (caddr ass)) (car ri))
446 (take (list (cdddr ass)) (cdr ri)))))))))))
447 ((member (caar l) '(%tan %tanh) :test #'eq)
448 (let ((sp (risplit (cadr l))))
449 ;;;The similar tan and tanh cases.
450 (cond ((=0 (cdr sp))
451 (cons l 0))
453 (let* ((2rl (mul (car sp) 2))
454 (2im (mul (cdr sp) 2))
455 (denom (inv (if (eq (caar l) '%tan)
456 (add (take '(%cosh) 2im) (take '(%cos) 2rl))
457 (add (take '(%cos) 2im) (take '(%cosh) 2rl))))))
458 (if (eq (caar l) '%tan)
459 (cons (mul (take '(%sin) 2rl) denom)
460 (mul (take '(%sinh) 2im) denom))
461 (cons (mul (take '(%sinh) 2rl) denom)
462 (mul (take '(%sin) 2im) denom))))))))
463 ((and (member (caar l) '(%atan %csc %sec %cot %csch %sech %coth) :test #'eq)
464 (=0 (cdr (risplit (cadr l)))))
465 (cons l 0))
466 ((and (eq (caar l) '$atan2)
467 (not (zerop1 (caddr l)))
468 (=0 (cdr (risplit (div (cadr l) (caddr l))))))
469 ;; Case atan2(y,x) and y/x a real expression.
470 (cons l 0))
471 ((or (arcp (caar l)) (eq (caar l) '$atan2))
472 (let ((ans (risplit (logarc (caar l) (cadr l)))))
473 (when (eq (caar l) '$atan2)
474 (setq ans (cons (sratsimp (car ans)) (sratsimp (cdr ans)))))
475 (if (and (free l '$%i) (=0 (cdr ans)))
476 (cons l 0)
477 ans)))
478 ((eq (caar l) '%plog)
479 ;; (princ '|Warning: Principal value not guaranteed for Plog in Rectform/|)
480 (risplit (cons '(%log) (cdr l))))
481 ;; Look for a risplit-function on the property list to handle the
482 ;; realpart and imagpart for this function.
483 ((setq op (safe-get (mop l) 'risplit-function))
484 (funcall op l))
485 ;;; ^ All the above are guaranteed pure real.
486 ;;; The handling of lists and matrices below has to be thought through.
487 ((eq (caar l) 'mlist) (dsrl l))
488 ((eq (caar l) '$matrix)
489 (dot--ri (mapcar #'dsrl (cdr l)) '($matrix simp)))
490 ;;;The Coversinemyfoot clause covers functions which can be converted
491 ;;; to functions known by risplit, such as the more useless trigonometrics.
492 ((let ((foot (coversinemyfoot l)))
493 (and foot (risplit foot))))
494 ((or (safe-get (mop l) 'real-valued)
495 (decl-realp (mop l)))
496 ;; Simplification for a real-valued function
497 (cons l 0))
498 ((or (safe-get (mop l) 'commutes-with-conjugate)
499 (safe-get (mop l) 'conjugate-function))
500 ;; A function with Mirror symmetry. The general expressions for
501 ;; the realpart and imagpart simplifies accordingly.
502 (cons (mul (div 1 2)
503 (add (simplify (list '($conjugate) l)) l))
504 (mul (div 1 2) '$%i
505 (sub (simplify (list '($conjugate) l)) l))))
506 ;;; A MAJOR ASSUMPTION:
507 ;;; All random functions are pure real, regardless of argument.
508 ;;; This is evidently assumed by some of the integration functions.
509 ;;; Perhaps the best compromise is to return 'realpart/'imagpart
510 ;;; under the control of a switch set by the integrators. First
511 ;;; all such dependencies must be found in the integ
512 ((and rp-polylogp (mqapplyp l) (eq (subfunname l) '$li)) (cons l 0))
513 ((prog2 (setq op (if (eq (caar l) 'mqapply) (caaadr l) (caar l)))
514 (decl-complexp op))
515 (risplit-noun l))
516 ((and (eq (caar l) '%product) (not (free (cadr l) '$%i)))
517 (risplit-noun l))
518 (($subvarp l)
519 ;; return a real answer for subscripted variable
520 (cons l 0))
522 (cons (list '(%realpart simp) l)
523 (list '(%imagpart simp) l))))))
525 (defun coversinemyfoot (l)
526 (prog (recip)
527 (cond ((not (member (caar l) '(%csc %sec %cot %csch %sech %coth) :test #'eq)))
528 ((null (setq recip (get (caar l) 'recip))))
529 (t (return (div 1 (cons (list recip) (cdr l))))))))
531 (defun powers (c d)
532 (cond ((=1 d) c)
533 ((equal d 0) 1) ;equal to preclude 0^(pdl 0)->0:
534 ((=0 c) 0) ; see comment before =0.
535 ((=1 c) 1)
536 (t (power c d))))
538 (defun spabs (sp)
539 ;; SP is a cons of the real part and imaginary part of a complex
540 ;; number. SPABS computes the sum of squares of the real and
541 ;; imaginary parts.
542 (add (powers (car sp) 2)
543 (powers (cdr sp) 2)))
545 ;; Compute 1/(x+%i*y) when both x and y are Lisp numbers or Maxima
546 ;; rationals. Return a cons of the real and imaginary part of the
547 ;; result. We count on the underlying Lisp to be able to compute (/
548 ;; (complex x y)) accurately and without unnecessary overflow or
549 ;; underflow.. If not, complain to your Lisp vendor. Well, it seems
550 ;; that Clisp, CMUCL, and SBCL do a nice job. But others apparently
551 ;; do not. (I tested ecl 9.12.3 and ccl 1.4, which both fail.)
552 ;; Workaround those deficiencies.
553 (defun sprecip (sp)
554 (destructuring-bind (x . y)
556 #+(or cmu sbcl)
557 (let* ((x (bigfloat:to x))
558 (y (bigfloat:to y))
559 (q (bigfloat:/ (bigfloat:complex x y))))
560 (cons (to (bigfloat:realpart q))
561 (to (bigfloat:imagpart q))))
562 #-(or cmu sbcl)
563 (let ((x (bigfloat:to x))
564 (y (bigfloat:to y)))
565 ;; 1/(x+%i*y).
567 ;; Assume abs(x) > abs(y). Let r = y/x. Then
568 ;; 1/(x+%i*y) = 1/x/(1+%i*r)
569 ;; = (1-%i*r)/(x*(1+r*r))
571 ;; The case for abs(x) <= abs(y) is similar with r = x/y:
572 ;; 1/(x+%i*y) = 1/y/(r+%i)
573 ;; = (r-%i)/(y*(1+r^2))
574 (if (> (bigfloat:abs x) (bigfloat:abs y))
575 (let* ((r (bigfloat:/ y x))
576 (dn (bigfloat:* x (bigfloat:+ 1 (bigfloat:* r r)))))
577 (cons (to (bigfloat:/ dn))
578 (to (bigfloat:/ (bigfloat:- r) dn))))
579 (let* ((r (bigfloat:/ x y))
580 (dn (bigfloat:* y (bigfloat:+ 1 (bigfloat:* r r)))))
581 (cons (to (bigfloat:/ r dn))
582 (to (bigfloat:/ (bigfloat:- dn)))))))))
587 (defvar negp* (let ((l (list nil nil t t))) (nconc l l)))
589 (defun divcarcdr (a b)
590 (cons (div (car a) b) (div (cdr a) b)))
593 ;;Expand bas^n, where bas is (<real part> . <imaginary part>)
595 (defun expanintexpt (bas n)
596 (cond ((= n 1) bas)
597 (t (do ((rp (car bas))
598 (ip (cdr bas))
599 (c 1 (quotient (* c ex) i))
600 (ex n (1- ex)) (i 1 (1+ i))
601 (rori t (not rori)) (negp negp* (cdr negp))
602 (rpt nil) (ipt nil))
603 ((< ex 0) (cons (addn rpt t) (addn ipt t)))
604 (declare (fixnum ex i))
605 (set-either rpt ipt
606 rori
607 (cons (negate-if (car negp)
608 (mul c
609 (powers rp ex)
610 (powers ip (1- i))))
611 (cond (rori rpt) (t ipt))))))))
615 ;;; Subtract out multiples of 2*%pi with a minimum of consing.
616 ;;; Attempts to reduce to interval (-pi,pi].
618 (defun 2pistrip (exp)
619 (cond ((atom exp) exp)
620 ((eq (caar exp) 'mtimes)
621 (cond ((and (mnump (cadr exp))
622 (eq (caddr exp) '$%pi)
623 (null (cdddr exp)))
624 (cond ((integerp (cadr exp)) ; 5*%pi
625 (mul (mod (cadr exp) 2) '$%pi))
626 ((floatp (cadr exp)) ; 1.5*%pi
627 (mul (1- (mod (1+ (cadr exp)) 2))
628 '$%pi))
629 ;; Neither 0 nor 1 appears as a coef
630 ((and (listp (cadr exp))
631 (eq 'rat (caaadr exp))) ;5/2*%pi
632 (mul (list* '(rat simp)
633 (- (mod (+ (cadadr exp) (car (cddadr exp)))
634 (* 2 (car (cddadr exp))))
635 (car (cddadr exp)))
636 (cddadr exp))
637 '$%pi))
638 (t exp)))
639 (t exp)))
640 ((eq (caar exp) 'mplus)
641 (let ((res (2pirec (cdr exp))))
642 (if (eq res (cdr exp))
644 (addn res t))))
645 (t exp)))
647 (defun 2pirec (fm) ;Takes a list of exprs
648 (cond ((null (cdr fm)) ;If monad, just return.
649 (let ((2pf (2pistrip (car fm))))
650 (cond ((eq 2pf (car fm)) fm)
651 ((=0 2pf) nil)
652 (t (list 2pf)))))
654 (let ((2pfma (2pistrip (car fm)))
655 (2pfmd (2pirec (cdr fm))))
656 (cond ((or (null 2pfmd) (=0 2pfmd)) 2pfma)
657 ((and (eq 2pfmd (cdr fm)) (eq 2pfma (car fm))) fm)
658 (t (cons 2pfma 2pfmd)))))))
660 ;;; Rectify into polar form; Arguments similar to risplit
662 (defun argnum (n)
663 (if (minusp n)
664 (simplify '$%pi)
668 ;; absarg
669 ;; returns pair (abs . arg)
670 ;; if absflag is true, arg result is not guaranteed to be correct
672 ;; The function of Absflag is to communicate that only the absolute
673 ;; value part of the result is wanted. This allows Absarg to avoid asking
674 ;; questions irrelevant to the absolute value. For instance, Cabs(x) is
675 ;; invariably Abs(x), while the complex phase may be 0 or %pi. Note also
676 ;; the steps taken in Absarg to assure that Asksign's will happen before Sign's
677 ;; as often as possible, so that, for instance, Abs(x) can be simplified to
678 ;; x or -x if the sign of x must be known for some other reason. These
679 ;; techniques, however, are not perfect.
681 (defmacro half () ''((rat simp) 1 2)) ;1/2
683 (defun absarg (l &optional (absflag nil))
684 ;; Commenting out the the expansion of the expression l. It seems to be not
685 ;; necessary, but can cause expression swelling (DK 01/2010).
686 ; (setq l ($expand l))
687 (cond ((atom l)
688 (cond ((eq l '$%i)
689 (cons 1 (simplify '((mtimes) ((rat simp) 1 2) $%pi))))
690 ((numberp l)
691 (cons (abs l) (argnum l)))
692 ((member l '($%e $%pi) :test #'eq) (cons l 0))
693 ((eq l '$infinity) (cons '$inf '$ind))
694 ((decl-complexp l)
695 (cons (list '(mabs simp) l) ; noun form with mabs
696 (list '(%carg simp) l)))
697 (absflag (cons (take '(mabs) l) 0))
699 ;; At this point l is representing a real value. Try to
700 ;; determine the sign and return a general form when the sign is
701 ;; unknown.
702 (let ((gs (if (eq rischp l) '$pos ($sign l))))
703 (cond ((member gs '($pos $pz)) (cons l 0))
704 ((eq gs '$zero) (cons 0 0))
705 ((eq gs '$neg)
706 (cons (neg l) (simplify '$%pi)))
707 (t (cons (take '(mabs) l) (genatan 0 l))))))))
708 ((eq '$zero (let ((sign-imag-errp nil)) (catch 'sign-imag-err ($sign l))))
709 (cond ((some-bfloatp l)
710 (cons bigfloatzero bigfloatzero)) ; contagious
711 ((some-floatp l)
712 (cons 0.0 0.0))
713 (t (cons 0 0))))
714 ((member (caar l) '(rat bigfloat) :test #'eq)
715 (cons (list (car l) (abs (cadr l)) (caddr l))
716 (argnum (cadr l))))
717 ((eq (caar l) 'mtimes)
718 (do ((n (cdr l) (cdr n))
719 (abars)
720 (argl () (cons (cdr abars) argl))
721 (absl () (rplacd abars absl)))
722 (())
723 (unless n
724 (return (cons (muln absl t) (2pistrip (addn argl t)))))
725 (setq abars (absarg (car n) absflag))))
726 ((eq (caar l) 'mexpt)
727 ;; An expression z^a
728 (let ((aa (absarg (cadr l) nil)) ; (abs(z) . arg(z))
729 (sp (risplit (caddr l))) ; (realpart(a) . imagpart(a))
730 ($radexpand nil))
731 (cond ((and (zerop1 (cdr sp))
732 (eq ($sign (sub 1 (take '(mabs) (car sp)))) '$pos))
733 ;; Special case: a is real and abs(a) < 1.
734 ;; This simplifies e.g. carg(sqrt(z)) -> carg(z)/2
735 (cons (mul (power (car aa) (car sp))
736 (power '$%e (neg (mul (cdr aa) (cdr sp)))))
737 (mul (caddr l) (cdr aa))))
739 ;; General case for z and a
740 (let ((arg (add (mul (cdr sp) (take '(%log) (car aa)))
741 (mul (cdr aa) (car sp)))))
742 (cons (mul (power (car aa) (car sp))
743 (power '$%e (neg (mul (cdr aa) (cdr sp)))))
744 (if generate-atan2
745 (take '($atan2)
746 (take '(%sin) arg)
747 (take '(%cos) arg))
748 (take '(%atan) (take '(%tan) arg)))))))))
749 ((and (member (caar l) '(%tan %tanh) :test #'eq)
750 (not (=0 (cdr (risplit (cadr l))))))
751 (let* ((sp (risplit (cadr l)))
752 (2frst (mul (cdr sp) 2))
753 (2scnd (mul (car sp) 2)))
754 (when (eq (caar l) '%tanh)
755 (psetq 2frst 2scnd 2scnd 2frst))
756 (cons (let ((cosh (take '(%cosh) 2frst))
757 (cos (take '(%cos) 2scnd)))
758 (root (div (add cosh (neg cos))
759 (add cosh cos))
761 (take '(%atan)
762 (if (eq (caar l) '%tan)
763 (div (take '(%sinh) 2frst) (take '(%sin) 2scnd))
764 (div (take '(%sin) 2frst) (take '(%sinh) 2scnd)))))))
765 ((specrepp l) (absarg (specdisrep l) absflag))
766 ((let ((foot (coversinemyfoot l)))
767 (and foot (not (=0 (cdr (risplit (cadr l))))) (absarg foot absflag))))
769 (let ((ris (trisplit l)))
770 (xcons
771 ;;; Arguments must be in this order so that the side-effect of the Atan2,
772 ;;; that is, determining the Asksign of the argument, can happen before
773 ;;; Take Mabs does its Sign. Blame JPG for noticing this lossage.
774 (if absflag 0 (genatan (cdr ris) (car ris)))
775 (cond ((equal (car ris) 0) (absarg-mabs (cdr ris)))
776 ((equal (cdr ris) 0) (absarg-mabs (car ris)))
777 (t (powers ($expand (add (powers (car ris) 2)
778 (powers (cdr ris) 2))
779 1 0)
780 (half)))))))))
782 (defun genatan (num den)
783 (let ((arg (take '($atan2) num den)))
784 (if (or generate-atan2
785 (zerop1 den)
786 (free arg '$atan2))
788 (take '(%atan) (div num den)))))
790 (defun absarg-mabs (l)
791 (cond ((eq (csign l) t)
792 (if (member (caar l) '(mabs %cabs) :test #'eq)
794 (list '(mabs simp) l))) ; mabs and not %cabs as noun form
795 ((member ($csign l) '($complex $imaginary))
796 ;; Do not try to simplify a complex expression at this point,
797 ;; this would cause an endless loop. Return a noun form.
798 (list '(mabs simp) l))
800 (take '(mabs) l))))