Typo in the last commit.
[maxima/cygwin.git] / src / csimp.lisp
blob0256a5bc09da18114a69499d610b90710abf0003
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 1980 Massachusetts Institute of Technology ;;;
9 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
11 (in-package :maxima)
13 (macsyma-module csimp)
15 (declare-top (special rsn* $factlim $exponentialize
16 var varlist genvar $%emode $ratprint
17 nn* dn* $errexp sqrt3//2 -sqrt3//2
18 $demoivre errorsw $keepfloat $ratfac))
20 (load-macsyma-macros rzmac)
22 (declare-top (special $nointegrate $lhospitallim $tlimswitch $limsubst
23 $abconvtest plogabs))
25 (defmvar $demoivre nil)
26 (defmvar $nointegrate nil)
27 (defmvar $lhospitallim 4)
28 (defmvar $tlimswitch t)
29 (defmvar $limsubst nil)
30 (defmvar $abconvtest nil)
31 (defvar rsn* nil)
32 (defvar plogabs nil)
34 ;; Simplified shortcuts of constant expressions involving %pi.
35 (defvar %p%i '((mtimes) $%i $%pi))
36 (defvar fourth%pi '((mtimes) ((rat simp) 1 4) $%pi))
37 (defvar half%pi '((mtimes) ((rat simp) 1 2) $%pi))
38 (defvar %pi2 '((mtimes) 2 $%pi))
39 (defvar half%pi3 '((mtimes) ((rat simp) 3 2) $%pi))
41 (defmvar $sumsplitfact t) ;= nil minfactorial is applied after a factocomb.
43 (loop for (a b) on
44 '(%sin %asin %cos %acos %tan %atan
45 %cot %acot %sec %asec %csc %acsc
46 %sinh %asinh %cosh %acosh %tanh %atanh
47 %coth %acoth %sech %asech %csch %acsch)
48 by #'cddr
49 do (putprop a b '$inverse) (putprop b a '$inverse))
51 (defmfun $demoivre (exp)
52 (let ($exponentialize nexp)
53 (cond ((atom exp) exp)
54 ((and (eq (caar exp) 'mexpt) (eq (cadr exp) '$%e)
55 (setq nexp (demoivre (caddr exp))))
56 nexp)
57 (t (recur-apply #'$demoivre exp)))))
59 (defun demoivre (l)
60 (cond ($exponentialize
61 (merror (intl:gettext "demoivre: 'demoivre' and 'exponentialize' cannot both be true.")))
62 (t (setq l (islinear l '$%i))
63 (and l (not (equal (car l) 0))
64 (m* (m^ '$%e (cdr l))
65 (m+ (list '(%cos) (car l))
66 (m* '$%i (list '(%sin) (car l)))))))))
68 ;; If expr is of the form a*var1+b where a is freeof var1
69 ;; then (a . b) is returned else nil.
70 (defun islinear (expr var1)
71 (declare (special *islinp*))
72 (let ((a (let ((*islinp* t))
73 (sdiff expr var1))))
74 (if (freeof var1 a)
75 (cons a (maxima-substitute 0 var1 expr)))))
77 (defmfun $partition (e var1)
78 (let ((e (mratcheck e))
79 (var1 (getopr var1)))
80 (cond
81 (($listp e)
82 (do ((l (cdr e) (cdr l)) (l1) (l2) (x))
83 ((null l) (list '(mlist simp)
84 (cons '(mlist simp) (nreverse l1))
85 (cons '(mlist simp) (nreverse l2))))
86 (setq x (mratcheck (car l)))
87 (cond ((free x var1) (setq l1 (cons x l1)))
88 (t (setq l2 (cons x l2))))))
90 ((mplusp e)
91 (destructuring-bind (constant . variable) (partition e var1 0)
92 (list '(mlist simp) constant variable)))
94 ((mtimesp e)
95 (destructuring-bind (constant . variable) (partition e var1 1)
96 (list '(mlist simp) constant variable)))
99 (merror
100 (intl:gettext
101 "partition: first argument must be a list or '+' or '*' expression; found ~M") e)))))
103 ;; Apply PREDICATE to each element in the sequence SEQ and return
105 ;; (VALUES YES NO),
107 ;; where YES and NO are lists consisting of elements for which PREDICATE is true
108 ;; or false, respectively.
109 (defun partition-by (predicate seq)
110 (let ((yes) (no))
111 (map nil
112 (lambda (x)
113 (if (funcall predicate x)
114 (push x yes)
115 (push x no)))
116 seq)
117 (values yes no)))
119 ;; Partition an expression, EXP, into terms that contain VAR1 and terms that
120 ;; don't contain VAR1. EXP is either considered as a product or a sum (for which
121 ;; you should pass K = 1 or 0, respectively).
123 (defun partition (exp var1 k)
124 (let ((op (if (= k 0) 'mplus 'mtimes))
125 (exp-op (unless (atom exp) (caar exp))))
126 (cond
127 ;; Exit immediately if exp = var1
128 ((alike1 exp var1) (cons k exp))
130 ;; If we have the wrong operation then the expression is either entirely
131 ;; constant or entirely variable.
132 ((not (eq exp-op op))
133 (if (freeof var1 exp)
134 (cons exp k)
135 (cons k exp)))
137 ;; Otherwise, we want to partition the arguments into constant and
138 ;; variable.
140 (multiple-value-bind (constant variable)
141 (partition-by (lambda (x) (freeof var1 x)) (cdr exp))
142 (cons (cond ((null constant) k)
143 ((null (cdr constant)) (car constant))
144 (t (simplifya
145 (cons (list op) (nreverse constant)) t)))
146 (cond ((null variable) k)
147 ((null (cdr variable)) (car variable))
148 (t (simplifya
149 (cons (list op) (nreverse variable)) t)))))))))
151 ;;To use this INTEGERINFO and *ASK* need to be special.
152 ;;(defun integerpw (x)
153 ;; ((lambda (*ask*)
154 ;; (integerp10 (ssimplifya (sublis '((z** . 0) (*z* . 0)) x))))
155 ;; t))
157 ;;(defun integerp10 (x)
158 ;; ((lambda (d)
159 ;; (cond ((or (null x) (not (free x '$%i))) nil)
160 ;; ((mnump x) (integerp x))
161 ;; ((setq d (assolike x integerinfo)) (eq d 'yes))
162 ;; (*ask* (setq d (cond ((integerp x) 'yes) (t (needinfo x))))
163 ;; (setq integerinfo (cons (list x d) integerinfo))
164 ;; (eq d 'yes))))
165 ;; nil))
167 (setq var (make-symbol "foo"))
169 (defun numden (e)
170 (prog (varlist)
171 (setq varlist (list var))
172 (newvar (setq e (fmt e)))
173 (setq e (cdr (ratrep* e)))
174 (setq dn*
175 (simplifya (pdis (ratdenominator e))
176 nil))
177 (setq nn*
178 (simplifya (pdis (ratnumerator e))
179 nil)))
180 (values nn* dn*))
182 (defun fmt (exp)
183 (let (nn*)
184 (cond ((atom exp) exp)
185 ((mnump exp) exp)
186 ((eq (caar exp) 'mexpt)
187 (cond ((and (mnump (caddr exp))
188 (eq ($sign (caddr exp)) '$neg))
189 (list '(mquotient)
191 (cond ((equal (caddr exp) -1)
192 (fmt (cadr exp)))
193 (t (list (list (caar exp))
194 (fmt (cadr exp))
195 (timesk -1 (caddr exp)))))))
196 ((atom (caddr exp))
197 (list (list (caar exp))
198 (fmt (cadr exp))
199 (caddr exp)))
200 ((and (mtimesp (setq nn* (sratsimp (caddr exp))))
201 (mnump (cadr nn*))
202 (equal ($sign (cadr nn*)) '$neg))
203 (list '(mquotient)
205 (list (list (caar exp))
206 (fmt (cadr exp))
207 (cond ((equal (cadr nn*) -1)
208 (cons '(mtimes)
209 (cddr nn*)))
210 (t (neg nn*))))))
211 ((eq (caar nn*) 'mplus)
212 (fmt (spexp (cdr nn*) (cadr exp))))
213 (t (cons (ncons (caar exp))
214 (mapcar #'fmt (cdr exp))))))
215 (t (cons (delsimp (car exp)) (mapcar #'fmt (cdr exp)))))))
217 (defun spexp (expl dn*)
218 (cons '(mtimes) (mapcar #'(lambda (e) (list '(mexpt) dn* e)) expl)))
220 (defun subin (y x)
221 (cond ((not (among var x)) x)
222 (t (maxima-substitute y var x))))
224 ;; Right-hand side (rhs) and left-hand side (lhs) of binary infix expressions.
225 ;; These are unambiguous for relational operators, some other built-in infix operators,
226 ;; and user-defined infix operators (declared by the infix function).
228 ;; a - b and a / b are somewhat problematic, since subtraction and division are not
229 ;; ordinarily represented as such (rather a - b = a + (-1)*b and a / b = a * b^(-1)).
230 ;; Also, - can be unary. So let's not worry about - and / .
232 ;; Other problematic cases: The symbols $< $<= $= $# $>= $> have a LED property,
233 ;; but these symbols never appear in expressions returned by the Maxima parser;
234 ;; MLESSP, MLEQP, MEQUAL etc are substituted. So ignore those symbols here.
235 (let
236 ((relational-ops
237 ;; < <= = # equal notequal >= >
238 '(mlessp mleqp mequal mnotequal $equal $notequal mgeqp mgreaterp
239 %mlessp %mleqp %mequal %mnotequal %equal %notequal %mgeqp %mgreaterp))
241 (other-infix-ops
242 ;; := ::= : :: ->
243 '(mdefine mdefmacro msetq mset marrow
244 %mdefine %mdefmacro %msetq %mset %marrow)))
246 (defmfun $rhs (rel)
247 (if (atom rel)
249 (if (or (member (caar rel) (append relational-ops other-infix-ops) :test #'eq)
250 ;; This test catches user-defined infix operators.
251 (eq (get (caar rel) 'led) 'parse-infix))
252 (caddr rel)
253 0)))
255 (defmfun $lhs (rel)
256 (if (atom rel)
258 (if (or (member (caar rel) (append relational-ops other-infix-ops) :test #'eq)
259 ;; This test catches user-defined infix operators.
260 (eq (get (caar rel) 'led) 'parse-infix))
261 (cadr rel)
262 rel))))
264 (defun ratgreaterp (x y)
265 (cond ((and (ratnump x) (ratnump y))
266 (great x y))
267 ((equal ($asksign (m- x y)) '$pos))))
269 ;; Simplify the exponential function of the type exp(p/q*%i*%pi+x) using the
270 ;; periodicity of the exponential function and special values for rational
271 ;; numbers with a denominator q = 2, 3, 4, or 6. e is the argument of the
272 ;; exponential function. For float and bigfloat numbers in the argument e only
273 ;; simplify for an integer representation or a half integral value.
274 ;; The result is an exponential function with a simplified argument.
275 (defun %especial (e)
276 (prog (varlist y k kk j ans $%emode $ratprint genvar)
277 (let (($keepfloat nil) ($float nil))
278 (unless (setq y (pip ($ratcoef e '$%i))) (return nil))
279 ;; Subtract the term y*%i*%pi from the expression e.
280 (setq k ($expand (add e (mul -1 '$%pi '$%i y)) 1))
281 ;; This is a workaround to get the type (integer, float, or bigfloat)
282 ;; of the expression. kk must evaluate to 1, 1.0, or 1.0b0.
283 ;; Furthermore, if e is nonlinear, kk does not simplify to a number ONE.
284 ;; Because of this we do not simplify something like exp((2+x)^2*%i*%pi)
285 (setq kk (div (sub ($expand e) k) (mul '$%i '$%pi y)))
286 ;; Return if kk is not an integer or kk is ONE, but y not an integer
287 ;; or a half integral value.
288 (if (not (or (integerp kk)
289 (and (onep1 kk)
290 (integerp (add y y)))))
291 (return nil))
292 (setq j (trigred y))
293 (setq ans (spang1 j t)))
294 (cond ((among '%sin ans)
295 (cond ((equal y j) (return nil))
296 ((zerop1 k)
297 ;; To preverse the type we add k into the result.
298 (return (power '$%e (mul '$%pi '$%i (add k j)))))
300 ;; To preserve the type we multiply kk into the result.
301 (return
302 (power '$%e (add (mul kk k) (mul kk '$%pi '$%i j))))))))
303 (setq y (spang1 j nil))
304 ;; To preserve the type we multiply kk into the result.
305 (return (mul (power '$%e (mul kk k)) (add y (mul '$%i ans))))))
307 (defun trigred (r)
308 (prog (m n eo flag)
309 (cond ((numberp r) (return (cond ((even r) 0) (t 1)))))
310 (setq m (cadr r))
311 (cond ((minusp m) (setq m (- m)) (setq flag t)))
312 (setq n (caddr r))
313 loop (cond ((> m n)
314 (setq m (- m n))
315 (setq eo (not eo))
316 (go loop)))
317 (setq m (list '(rat)
318 (cond (flag (- m)) (t m))
320 (return (cond (eo (addk m (cond (flag 1) (t -1))))
321 (t m)))))
323 (defun polyinx (exp x ind)
324 (prog (genvar varlist var $ratfac)
325 (setq var x)
326 (cond ((numberp exp)(return t))
327 ((polyp exp)
328 (cond (ind (go on))
329 (t (return t))))
330 (t (return nil)))
331 on (setq genvar nil)
332 (setq varlist (list x))
333 (newvar exp)
334 (setq exp (cdr (ratrep* exp)))
335 (cond
336 ((or (numberp (cdr exp))
337 (not (eq (car (last genvar)) (cadr exp))))
338 (setq x (pdis (cdr exp)))
339 (return (cond ((eq ind 'leadcoef)
340 (div* (pdis (caddr (car exp))) x))
341 (t (setq exp (car exp))
342 (div* (cond ((atom exp) exp)
344 (pdis (list (car exp)
345 (cadr exp)
346 (caddr exp)))))
348 ))))))
350 (defun polyp (a)
351 (cond ((atom a) t)
352 ((member (caar a) '(mplus mtimes) :test #'eq)
353 (every #'polyp (cdr a)))
354 ((eq (caar a) 'mexpt)
355 (cond ((free (cadr a) var)
356 (free (caddr a) var))
357 (t (and (integerp (caddr a))
358 (> (caddr a) 0)
359 (polyp (cadr a))))))
360 (t (andmapcar #'(lambda (subexp)
361 (free subexp var))
362 (cdr a)))))
364 (defun pip (e)
365 (prog (varlist d c)
366 (newvar e)
367 (cond ((not (member '$%pi varlist :test #'eq)) (return nil)))
368 (setq varlist '($%pi))
369 (newvar e)
370 (let (($ratfac nil))
371 ;; non-nil $ratfac changes form of CRE
372 (setq e (cdr (ratrep* e))))
373 (setq d (cdr e))
374 (cond ((not (atom d)) (return nil))
375 ((equal e '(0 . 1))
376 (setq c 0)
377 (go loop)))
378 (setq c (ptterm (cdar e) 1))
379 loop (cond ((atom c)
380 (cond ((equal c 0) (return nil))
381 ((equal 1 d) (return c))
382 (t (return (list '(rat) c d))))))
383 (setq c (ptterm (cdr c) 0))
384 (go loop)))
386 (defun spang1 (j ind)
387 (prog (ang ep $exponentialize $float $keepfloat)
388 (cond ((floatp j) (setq j (maxima-rationalize j))
389 (setq j (list '(rat simp) (car j) (cdr j)))))
390 (setq ang j)
391 (cond
392 (ind nil)
393 ((numberp j)
394 (cond ((zerop j) (return 1)) (t (return -1))))
395 (t (setq j
396 (trigred (add2* '((rat simp) 1 2)
397 (list (car j)
398 (- (cadr j))
399 (caddr j)))))))
400 (cond ((numberp j) (return 0))
401 ((mnump j) (setq j (cdr j))))
402 (return
403 (cond ((equal j '(1 2)) 1)
404 ((equal j '(-1 2)) -1)
405 ((or (equal j '(1 3))
406 (equal j '(2 3)))
407 (div ($sqrt 3) 2))
408 ((or (equal j '(-1 3))
409 (equal j '(-2 3)))
410 (div ($sqrt 3) -2))
411 ((or (equal j '(1 6))
412 (equal j '(5 6)))
413 '((rat simp) 1 2))
414 ((or (equal j '(-1 6))
415 (equal j '(-5 6)))
416 '((rat simp) -1 2))
417 ((or (equal j '(1 4))
418 (equal j '(3 4)))
419 (div 1 ($sqrt 2)))
420 ((or (equal j '(-1 4))
421 (equal j '(-3 4)))
422 (div -1 ($sqrt 2)))
423 (t (cond ((mnegp ang)
424 (setq ang (timesk -1 ang) ep t)))
425 (setq ang (list '(mtimes simp)
427 '$%pi))
428 (cond (ind (cond (ep (list '(mtimes simp)
430 (list '(%sin simp) ang)))
431 (t (list '(%sin simp) ang))))
432 (t (list '(%cos simp) ang))))))))
434 (defun archk (a b v)
435 (simplify
436 (cond ((and (equal a 1) (equal b 1)) v)
437 ((and (equal b -1) (equal 1 a))
438 (list '(mtimes) -1 v))
439 ((equal 1 b)
440 (list '(mplus) '$%pi (list '(mtimes) -1 v)))
441 (t (list '(mplus) v (list '(mtimes) -1 '$%pi))))))
443 (defun genfind (h v)
444 ;;; finds gensym coresponding to v h
445 (do ((varl (caddr h) (cdr varl))
446 (genl (cadddr h) (cdr genl)))
447 ;;;is car of rat form
448 ((eq (car varl) v) (car genl))))