Wrap the list of command line options if needed.
[maxima.git] / src / limit.lisp
blobd29b89ac957678c86a0f0766905a453ece692727
1 ;;; -*- Mode: Lisp; Package: Maxima; Syntax: Common-Lisp; Base: 10 -*- ;;;;
2 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
3 ;;; The data in this file contains enhancements. ;;;;;
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 limit)
16 ;;; **************************************************************
17 ;;; ** **
18 ;;; ** LIMIT PACKAGE **
19 ;;; ** **
20 ;;; **************************************************************
22 ;;; I believe a large portion of this file is described in Paul
23 ;;; Wang's thesis, "Evaluation of Definite Integrals by Symbolic
24 ;;; Manipulation," MIT/LCS/TR-92, Oct. 1971. This can be found at
25 ;;; https://web.archive.org/web/20191019131847/https://apps.dtic.mil/dtic/tr/fulltext/u2/732005.pdf
28 ;;; TOP LEVEL FUNCTION(S): $LIMIT $LDEFINT
30 (declare-top (special origval
31 *indicator numer denom exp var val
32 taylored logcombed
33 $exponentialize lhp? lhcount
34 loginprod? a context limit-assumptions
35 limit-top))
37 (defconstant +behavior-count+ 4)
38 (defvar *behavior-count-now*)
39 (defvar *getsignl-asksign-ok* nil)
40 (defvar *old-integer-info* nil)
42 (load-macsyma-macros rzmac)
44 (defmvar simplimplus-problems ()
45 "A list of all problems in the stack of recursive calls to simplimplus.")
47 (defmvar limit-answers ()
48 "An association list for storing limit answers.")
50 (defmvar limit-using-taylor ()
51 "Is the current limit computation using taylor expansion?")
53 (defmvar preserve-direction () "Makes `limit' return Direction info.")
55 #+nil
56 (unless (boundp 'integer-info) (setq integer-info ()))
58 ;; For limits toward infinity for the gruntz code, we assume that the limit
59 ;; variable exceeds *large-positive-number*. This value matches the value
60 ;; that the limit code uses for the same purpose.
61 (defmvar *large-positive-number* (expt 10 8))
63 ;; Don't ask sign questions about $ind.
64 (putprop '$ind t 'internal)
66 ;; This should be made to give more information about the error.
67 ;;(DEFun DISCONT ()
68 ;; (cond (errorsw (throw 'errorsw t))
69 ;; (t (merror "Discontinuity Encountered"))))
71 ;;(DEFUN PUTLIMVAL (E V)
72 ;; (let ((exp (cons '(%limit) (list e var val))))
73 ;; (cond ((not (assolike exp limit-answers))
74 ;; (setq limit-answers (cons (cons exp v) limit-answers))
75 ;; v)
76 ;; (t ()))))
78 (defun putlimval (e v &aux exp)
79 (setq exp `((%limit) ,e ,var ,val))
80 (unless (assolike exp limit-answers)
81 (push (cons exp v) limit-answers))
84 (defun getlimval (e)
85 (let ((exp (cons '(%limit) (list e var val))))
86 (assolike exp limit-answers)))
88 (defmacro limit-catch (exp var val)
89 `(let ((errorsw t))
90 (let ((ans (catch 'errorsw
91 (catch 'limit (limit ,exp ,var ,val 'think)))))
92 (if (or (null ans) (eq ans t))
94 ans))))
96 (defmfun $limit (&rest args)
97 (let ((first-try (apply #'toplevel-$limit args)))
98 (if (and (consp first-try) (eq (caar first-try) '%limit))
99 (let ((*getsignl-asksign-ok* t))
100 (apply #'toplevel-$limit args))
102 ;; The function toplevel-$limit sets $numer, $%enumer, %emode, and
103 ;; $%e_to_numlog to false. When any of these option variables are true,
104 ;; we resimplify the limit in the current context.
105 (progn
106 (when (or $numer $%enumer $%emode $%e_to_numlog)
107 (setq first-try (resimplify first-try)))
108 first-try))))
110 ;; Return true iff the expression e has a subexpression that
111 ;; is an indefinite integral.
112 (defun indefinite-integral-p (e x)
113 (cond (($mapatom e) nil)
114 ((and (eq (caar e) '%integrate) (alike x (third e)))
115 (null (fourth e)))
117 (some #'(lambda (q) (indefinite-integral-p q x)) (cdr e)))))
119 (defun toplevel-$limit (&rest args)
120 (let ((limit-assumptions ())
121 (*old-integer-info* ())
122 ($keepfloat t)
123 ($numer nil)
124 ($%enumer nil)
125 ($%emode t)
126 ($%e_to_numlog nil)
127 (limit-top t))
128 (declare (special limit-assumptions limit-top))
129 (unless limitp
130 (setq *old-integer-info* *integer-info*)
131 (setq *integer-info* ()))
133 (unwind-protect
134 (let ((exp1 ()) (lhcount $lhospitallim) (*behavior-count-now* 0)
135 (exp ()) (var ()) (val ()) (dr ())
136 (*indicator ()) (taylored ()) (origval ())
137 (logcombed ()) (lhp? ())
138 (varlist ()) (ans ()) (genvar ()) (loginprod? ())
139 (limit-answers ()) (limitp t) (simplimplus-problems ())
140 (lenargs (length args))
141 (genfoo ()))
142 (declare (special lhcount *behavior-count-now* exp var val *indicator
143 taylored origval logcombed lhp?
144 varlist genvar loginprod? limitp))
145 (prog ()
146 (unless (or (= lenargs 3) (= lenargs 4) (= lenargs 1))
147 (wna-err '$limit))
148 ;; Is it a LIST of Things?
149 (when (setq ans (apply #'limit-list args))
150 (return ans))
151 (setq exp1 (specrepcheck (first args)))
152 (when (and (atom exp1)
153 (member exp1 '(nil t)))
154 ;; The expression is 'T or 'NIL. Return immediately.
155 (return exp1))
156 (cond ((= lenargs 1)
157 (setq var (setq genfoo (gensym)) ; Use a gensym. Not foo.
158 val 0))
160 (setq var (second args))
161 (when ($constantp var)
162 (merror (intl:gettext "limit: second argument must be a variable, not a constant; found: ~M") var))
163 (unless (or ($subvarp var) (atom var))
164 (merror (intl:gettext "limit: variable must be a symbol or subscripted symbol; found: ~M") var))
165 (setq val (infsimp (third args)))
166 ;; infsimp converts -inf to minf. it also converts -infinity to
167 ;; infinity, although perhaps this should generate the error below.
168 (when (and (not (atom val))
169 (some #'(lambda (x) (not (freeof x val)))
170 *infinities*))
171 (merror (intl:gettext "limit: third argument must be a finite value or one of: inf, minf, infinity; found: ~M") val))
172 (when (eq val '$zeroa) (setq dr '$plus))
173 (when (eq val '$zerob) (setq dr '$minus))))
174 (cond ((= lenargs 4)
175 (unless (member (fourth args) '($plus $minus) :test #'eq)
176 (merror (intl:gettext "limit: direction must be either 'plus' or 'minus'; found: ~M") (fourth args)))
177 (setq dr (fourth args))))
178 (if (and (atom var) (not (among var val)))
179 (setq exp exp1)
180 (let ((realvar var)) ;; Var is funny so make it a gensym.
181 (setq var (gensym))
182 (setq exp (maxima-substitute var realvar exp1))
183 (putprop var realvar 'limitsub)))
185 ;; When exp involves an indefinite integral whose integration variable
186 ;; is the limit variable, return a limit nounform. Do this even when
187 ;; limsubst is true. Thus limit(int(f(x),x,a) is trapped here, but
188 ;; limit(int(f(x,z),x,a) is not.
189 (when (indefinite-integral-p exp var)
190 (return (cons (list '%limit) args)))
192 ;; This returns a limit nounform for expressions such as
193 ;; limit(x < 8,x,0), limit(diff(f(x),x,x,0), and ...
194 (unless (eq var genfoo)
195 (when (limunknown exp)
196 (return `((%limit) ,@(cons exp1 (cdr args))))))
198 (setq varlist (ncons var) genvar nil origval val)
199 ;; Transform limits to minf to limits to inf by
200 ;; replacing var with -var everywhere.
201 (when (eq val '$minf)
202 (setq val '$inf
203 origval '$inf
204 exp (subin (m* -1 var) exp)))
206 ;; Transform the limit value.
207 (unless (infinityp val)
209 (let ((*atp* t) (realvar var))
210 ;; *atp* prevents substitution from applying to vars
211 ;; bound by %sum, %product, %integrate, %limit
212 (setq var (gensym))
213 (putprop var t 'internal)
214 (setq exp (derivative-subst exp val var realvar))
215 (setq exp (maxima-substitute (m+ val var) realvar exp)))
216 (setq val (cond ((eq dr '$plus) '$zeroa)
217 ((eq dr '$minus) '$zerob)
218 (t 0)))
219 (setq origval 0))
221 ;; Make assumptions about limit var being very small or very large.
222 ;; Assumptions are forgotten upon exit.
223 (unless (= lenargs 1)
224 (limit-context var val dr))
225 ;; Resimplify in light of new assumptions. Changing ($expand exp 1 0)
226 ;; to ($expand exp 0 0) results in a bad testsuite failure for
227 ;; (assume(a>2), limit(integrate(t/log(t),t,2,a)/a,a,inf)) and
228 ;; some testsuite results that are more messy.
229 (setq exp (resimplify
230 ($minfactorial
231 (extra-simp
232 ($expand exp 1 0)))))
234 (if (not (or (real-epsilonp val) ;; if direction of limit not specified
235 (infinityp val)))
236 (setq ans (both-side exp var val)) ;; compute from both sides
237 (progn
238 (setq exp (mabs-subst exp var val))
239 (setq ans (limit-catch exp var val));; and find limit from one side
241 ;; try gruntz
242 (if (not ans)
243 (setq ans (catch 'taylor-catch
244 (let ((silent-taylor-flag t))
245 (declare (special silent-taylor-flag))
246 (gruntz1 exp var val)))))
248 ;; try taylor series expansion if simple limit didn't work
249 (if (and (null ans) ;; if no limit found and
250 $tlimswitch ;; user says ok to use taylor and
251 (not limit-using-taylor));; not already doing taylor
252 (let ((limit-using-taylor t))
253 (declare (special limit-using-taylor))
254 (setq ans (limit-catch exp var val))))))
256 (if ans
257 (return (clean-limit-exp ans))
258 (return (cons '(%limit) args))))) ;; failure: return nounform
259 (restore-assumptions))))
261 (defun clean-limit-exp (exp)
262 (setq exp (restorelim exp))
263 (if preserve-direction exp (ridofab exp)))
265 ;; Users who want limit to map over equality (mequal) will need to do that
266 ;; manually.
267 (defun limit-list (exp1 &rest rest)
268 (if (and (mbagp exp1) (not (mequalp exp1)))
269 `(,(car exp1) ,@(mapcar #'(lambda (x) (apply #'toplevel-$limit `(,x ,@rest))) (cdr exp1)))
270 ()))
272 (defun limit-context (var val direction) ;Only works on entry!
273 (cond (limit-top
274 (assume '((mgreaterp) lim-epsilon 0))
275 (assume '((mgreaterp) prin-inf 100000000))
276 (setq limit-assumptions (make-limit-assumptions var val direction))
277 (setq limit-top ()))
278 (t ()))
279 limit-assumptions)
281 (defun make-limit-assumptions (var val direction)
282 (let ((new-assumptions))
283 (cond ((or (null var) (null val))
285 ((and (not (infinityp val)) (null direction))
287 ((eq val '$inf)
288 `(,(assume `((mgreaterp) ,var 100000000)) ,@new-assumptions))
289 ((eq val '$minf)
290 `(,(assume `((mgreaterp) -100000000 ,var)) ,@new-assumptions))
291 ((eq direction '$plus)
292 `(,(assume `((mgreaterp) ,var 0)) ,@new-assumptions)) ;All limits around 0
293 ((eq direction '$minus)
294 `(,(assume `((mgreaterp) 0 ,var)) ,@new-assumptions))
296 ()))))
298 (defun restore-assumptions ()
299 ;;;Hackery until assume and forget take reliable args. Nov. 9 1979.
300 ;;;JIM.
301 (do ((assumption-list limit-assumptions (cdr assumption-list)))
302 ((null assumption-list) t)
303 (forget (car assumption-list)))
304 (forget '((mgreaterp) lim-epsilon 0))
305 (forget '((mgreaterp) prin-inf 100000000))
306 (cond ((and (not (null *integer-info*))
307 (not limitp))
308 (do ((list *integer-info* (cdr list)))
309 ((null list) t)
310 (i-$remove `(,(cadar list) ,(caddar list))))
311 (setq *integer-info* *old-integer-info*))))
313 ;; The optional arg allows the caller to decide on the value of
314 ;; preserve-direction. Default is nil, since we immediately ridofab.
315 (defun both-side (exp var val &optional (preserve nil))
316 (let* ((preserve-direction preserve)
317 (la (toplevel-$limit exp var val '$plus)) lb)
318 ; Immediately propagate an und without trying the
319 ; other direction
320 (when (eq la '$und) (return-from both-side '$und))
321 (setf lb (toplevel-$limit exp var val '$minus))
322 ; Immediately propagate an und
323 (when (eq lb '$und) (return-from both-side '$und))
324 (let ((ra (ridofab la))
325 (rb (ridofab lb)))
326 (cond ((eq t (meqp ra rb))
328 ((and (eq ra '$ind)
329 (eq rb '$ind))
330 ; Maxima does not consider equal(ind,ind) to be true, but
331 ; if both one-sided limits are ind then we want to call
332 ; the two-sided limit ind (e.g., limit(sin(1/x),x,0)).
333 '$ind)
334 ((or (not (free la '%limit))
335 (not (free lb '%limit)))
338 (let ((infa (infinityp la))
339 (infb (infinityp lb)))
340 (cond ((and infa infb)
341 ; inf + minf => infinity
342 '$infinity)
343 ((or infa infb)
344 '$und)
346 '$ind))))))))
348 ;; Return true when Maxima should return a limit nounform for limit(e,x,var,val).
349 (defun limunknown (e)
350 (not (limit-ok e var)))
352 ;; Return true when Maxima's limit code should be able to determine limit
353 (defun limit-ok (e x)
354 (cond
355 ((mapatom e) t) ;mapatoms are OK
356 ;; return nil for an indefinite integral
357 ((and (eq (caar e) '%integrate) (alike x (third e)) (null (fourth e))) nil)
358 ;; Return true for integrate(X,z,a,b) provided (a) freeof(x,X) (b) limit-ok(a,x)
359 ;; and (c) limit-ok(b,x). The function simplim%integrate does not recognize
360 ;; $limsubst, but this function does.
361 ((eq (caar e) '%integrate)
362 (and (limit-ok (fourth e) x) (limit-ok (fifth e) x))
363 (or $limsubst ($freeof (third e) x)))
364 ;; when the operator of e either (a) has a simplim%function, (b)
365 ;; is a simplifying operator (including subscripted operators),
366 ;; or (c) is $fib, check that each argument of e is OK.
368 (let* ((op (caar e))
369 (ok (or (get op 'operators)
370 (get op 'simplim%function)
371 (and (eq op 'mqapply) (get (subfunname e) 'specsimp))
372 (eq op '$fib))))
373 (and (or ok $limsubst)
374 (or (every #'(lambda(q) (limit-ok q x)) (cdr e)) ($freeof x e)))))))
376 ;; The functionality of this code has been blended into extra-simp. But
377 ;; there are some differences: (a) when e depends on the global var, this
378 ;; code converts *every* gamma function into a factorial, but extra-simp only
379 ;; converts subexpressions of the form gamma(X), where X depends on var to
380 ;; factorial form (b) this code dispatches minfactorial, but extra-simp
381 ;; doesn't.
383 ;; The function factosimp is not called by the limit code or by any
384 ;; code in source.
385 (defun factosimp(e)
386 (if (involve e '(%gamma)) (setq e ($makefact e)))
387 (cond ((involve e '(mfactorial))
388 (setq e (simplify ($minfactorial e))))
389 (t e)))
391 ;; Define sgn = csign(limit(z,var,val)). Return -1, 0, 1, or nil when
392 ;; sgn is neg, zero, pos, or complex, imaginary or unknown (including when
393 ;; the limit is ind), respectively. Also, when the limit is either zerob or zeroa,
394 ;; return 0.
396 ;; This function obeys the flag *getsignl-asksign-ok*, so it only does
397 ;; an asksign when *getsignl-asksign-ok* is true.
399 ;; When the limit is either zerob or zeroa, it's reasonable to return -1 or 1,
400 ;; respectively, but that causes a testsuite regression. Also when z is
401 ;; positive but limit(z,var,val) is ind, possibly this function could return 1, but
402 ;; it doesn't.
403 (defun getsignl (z)
404 (let ((sgn))
405 (setq z (let ((preserve-direction nil)) (limit-catch z var val)))
406 (cond
407 ;; Don't call csign on ind, und, infinity, zeroa, or zerob.
408 ;; When z is either zeroa or zerob, return 0.
409 ((or (eq z '$ind) (eq z '$und) (eq z '$infinity)) nil)
410 ((eq z '$zeroa) 0)
411 ((eq z '$zerob) 0)
413 (setq sgn (if *getsignl-asksign-ok* ($asksign z) ($csign z)))
414 (cond ((eq sgn '$pos) 1)
415 ((eq sgn '$neg) -1)
416 ((eq sgn '$zero) 0)
417 (t nil))))))
419 (defun restorelim (exp)
420 (cond ((null exp) nil)
421 ((atom exp) (or (and (symbolp exp) (get exp 'limitsub)) exp))
422 ((and (consp (car exp)) (eq (caar exp) 'mrat))
423 (cons (car exp)
424 (cons (restorelim (cadr exp))
425 (restorelim (cddr exp)))))
426 (t (cons (car exp) (mapcar #'restorelim (cdr exp))))))
428 ;; For each subexpression of e of the form abs(X), decide if abs(X) can be
429 ;; replaced by -X or by X. Define ans = limit(X,var, val) and
430 ;; bee = behavior(X,var,val). Cases:
432 ;; (a) negative (ans = -1) & decreasing (bee = -1), do abs(X) --> -X
433 ;; (b) positive (ans = 1) & increasing (bee = 1), do abs(X) --> X
434 ;; (c) zero (ans = 0) & decreasing (bee = -1), do abs(X) --> -X
435 ;; (d) zero (ans = 0) & X increasing (bee = 1), do abs(X) --> X
437 ;; This function misses cases such as abs(1-x^2) for x near 0.
438 ;; For that case, we get ans = 1 & bee = -1.
440 ;; If one-sided limits assumed both lower and upper bounds for the limit
441 ;; variable (something like 0 < x < tiny for a limit of x toward 0 from above),
442 ;; some subexpressions of the form abs(X) could be simplified away before
443 ;; going through this function.
445 ;; This function was rewritten and algorithmally altered by Barton Willis in
446 ;; January 2024. Previously, it was responsible for the bug
447 ;; limit(abs(sin(x))/sin(x), x, inf) = 1. Also, the old version also prevented
448 ;; limit(cos(a*x),x,inf) from doing an asksign on a, and it gave an
449 ;; internal error for limit((abs(sin(x)*cos(x)-x^4) -x)/x^3,x,0,plus).
450 (defun mabs-subst (e var val)
451 (let ((ans) (bee))
452 (cond (($mapatom e) e)
453 ;; Found a subexpression of the form abs(X). Decide if its OK
454 ;; to replace abs(X) by -X or by X. We could skip this when
455 ;; X is freeof var, but I'm not sure that we win by doing do
456 ((and (consp e) (eq (caar e) 'mabs))
457 (setq e (mabs-subst (cadr e) var val)) ;recurse on mabs-subst
458 (setq ans (getsignl e))
459 (setq bee (if ans (behavior e var val) nil))
460 (cond
461 ((and (eql ans -1) (eql bee -1)) (mul -1 e)) ;negative & decreasing
462 ((and (eql ans 1) (eql bee 1)) e) ; positive & increasing
463 ((and (eql ans 0) (eql bee -1)) (mul -1 e)) ;zero & decreasing
464 ((and (eql ans 0) (eql bee 1)) e) ;zero & increasing
465 (t (ftake 'mabs e)))) ; don't know
466 ;; Map mabs-subst over a subscripted function.
467 (($subvarp (mop e))
468 (subfunmake
469 (subfunname e)
470 (mapcar #'(lambda (q) (mabs-subst q var val)) (subfunsubs e))
471 (mapcar #'(lambda (q) (mabs-subst q var val)) (subfunargs e))))
472 ;; Map mabs-subst over the expression.
473 (t (fapply (caar e)
474 (mapcar #'(lambda (q) (mabs-subst q var val)) (cdr e)))))))
476 ;; Called on an expression that might contain $INF, $MINF, $ZEROA, $ZEROB. Tries
477 ;; to simplify it to sort out things like inf^inf or inf+1.
478 (defun simpinf (exp)
479 (simpinf-ic exp (count-general-inf exp)))
481 (defun count-general-inf (expr)
482 (count-atoms-matching
483 (lambda (x) (or (infinityp x) (real-epsilonp x))) expr))
485 (defun count-atoms-matching (predicate expr)
486 "Count the number of atoms in the Maxima expression EXPR matching PREDICATE,
487 ignoring dummy variables and array indices."
488 (cond
489 ((atom expr) (if (funcall predicate expr) 1 0))
490 ;; Don't count atoms that occur as a limit of %integrate, %sum, %product,
491 ;; %limit etc.
492 ((member (caar expr) dummy-variable-operators)
493 (count-atoms-matching predicate (cadr expr)))
494 ;; Ignore array indices
495 ((member 'array (car expr)) 0)
496 (t (loop
497 for arg in (cdr expr)
498 summing (count-atoms-matching predicate arg)))))
500 (defun simpinf-ic (exp &optional infinity-count)
501 (case infinity-count
502 ;; A very slow identity transformation...
503 (0 exp)
505 ;; If there's only one infinity, we replace it by a variable and take the
506 ;; limit as that variable goes to infinity. Use $gensym in case we can't
507 ;; compute the answer and the limit leaks out.
508 (1 (let* ((val (or (inf-typep exp) (epsilon-typep exp)))
509 (var ($gensym))
510 (expr (subst var val exp))
511 (limit (toplevel-$limit expr var val)))
512 (cond
513 ;; Now we look to see whether the computed limit is any simpler than
514 ;; what we shoved in (which we'll define as "doesn't contain EXPR as a
515 ;; subtree"). If so, return it.
516 ((not (subtree-p expr limit :test #'equal))
517 limit)
519 ;; Otherwise, return the original form: apparently, we can't compute
520 ;; the limit we needed, and it's uglier than what we started with.
521 (t exp))))
523 ;; If more than one infinity, we have to be a bit more careful.
524 (otherwise
525 (let* ((arguments (mapcar 'simpinf (cdr exp)))
526 (new-expression (cons (list (caar exp)) arguments))
527 infinities-left)
528 (cond
529 ;; If any of the arguments are undefined, we are too.
530 ((among '$und arguments) '$und)
531 ;; If we ended up with something indeterminate, we punt and just return
532 ;; the input.
533 ((amongl '(%limit $ind) arguments) exp)
535 ;; Exponentiation & multiplication
536 ((mexptp exp) (simpinf-expt (first arguments) (second arguments)))
537 ((mtimesp exp) (simpinf-times arguments))
539 ;; Down to at most one infinity? We do this after exponentiation to
540 ;; avoid zeroa^zeroa => 0^0, which will raise an error rather than just
541 ;; returning und. We do it after multiplication to avoid zeroa * inf =>
542 ;; 0 * inf => 0.
543 ((<= (setf infinities-left (count-general-inf new-expression)) 1)
544 (simpinf-ic new-expression infinities-left))
546 ;; Addition
547 ((mplusp exp) (simpinf-plus arguments))
549 ;; Give up!
550 (t new-expression))))))
552 (defun simpinf-times (arguments)
553 (declare (special exp var val))
554 ;; When we have a product, we need to spot that zeroa * zerob = zerob, zeroa *
555 ;; inf = und etc. Note that (SIMPINF '$ZEROA) => 0, so a nonzero atom is not
556 ;; an infinitesimal. Moreover, we can assume that each of ARGUMENTS is either
557 ;; a number, computed successfully by the recursive SIMPINF call, or maybe a
558 ;; %LIMIT noun-form (in which case, we aren't going to be able to tell the
559 ;; answer).
560 (cond
561 ((member 0 arguments)
562 (cond
563 ((find-if #'infinityp arguments) '$und)
564 ((every #'atom arguments) 0)
565 (t exp)))
567 ((member '$infinity arguments)
568 (if (every #'atom arguments)
569 '$infinity
570 exp))
572 (t (simplimit (cons '(mtimes) arguments) var val))))
574 (defun simpinf-expt (base exponent)
575 ;; In the comments below, zero* represents one of 0, zeroa, zerob.
577 ;; TODO: In some cases we give up too early. E.g. inf^(2 + 1/inf) => inf^2
578 ;; (which should simplify to inf)
579 (case base
580 ;; inf^inf = inf
581 ;; inf^minf = 0
582 ;; inf^zero* = und
583 ;; inf^foo = inf^foo
584 ($inf
585 (case exponent
586 ($inf '$inf)
587 ($minf 0)
588 ((0 $zeroa $zerob) '$und)
589 (t (list '(mexpt) base exponent))))
590 ;; minf^inf = infinity <== Or should it be und?
591 ;; minf^minf = 0
592 ;; minf^zero* = und
593 ;; minf^foo = minf^foo
594 ($minf
595 (case exponent
596 ($inf '$infinity)
597 ($minf 0)
598 ((0 $zeroa $zerob) '$und)
599 (t (list '(mexpt) base exponent))))
600 ;; zero*^inf = 0
601 ;; zero*^minf = und
602 ;; zero*^zero* = und
603 ;; zero*^foo = zero*^foo
604 ((0 $zeroa $zerob)
605 (case exponent
606 ($inf 0)
607 ($minf '$und)
608 ((0 $zeroa $zerob) '$und)
609 (t (list '(mexpt) base exponent))))
610 ;; a^b where a is pretty much anything except for a naked
611 ;; inf,minf,zeroa,zerob or 0.
613 (cond
614 ;; When a isn't crazy, try a^b = e^(b log(a))
615 ((not (amongl (append *infinitesimals* *infinities*) base))
616 (simpinf (m^ '$%e (m* exponent `((%log) ,base)))))
618 ;; No idea. Just return what we've found so far.
619 (t (list '(mexpt) base exponent))))))
621 (defun simpinf-plus (arguments)
622 ;; We know that none of the arguments are infinitesimals, since SIMPINF never
623 ;; returns one of them. As such, we partition our arguments into infinities
624 ;; and everything else. The latter won't have any "hidden" infinities like
625 ;; lim(x,x,inf), since SIMPINF gave up on anything containing a %lim already.
626 (let ((bigs) (others))
627 (dolist (arg arguments)
628 (cond ((infinityp arg) (push arg bigs))
629 (t (push arg others))))
630 (cond
631 ;; inf + minf or the like
632 ((cdr (setf bigs (delete-duplicates bigs))) '$und)
633 ;; inf + smaller + stuff
634 (bigs (car bigs))
635 ;; I don't think this can happen, since SIMPINF goes back to the start if
636 ;; there are fewer than two infinities in the arguments, but let's be
637 ;; careful.
638 (t (cons '(mplus) others)))))
640 ;; Simplify expression with zeroa or zerob.
641 (defun simpab (small)
642 (cond ((null small) ())
643 ((member small '($zeroa $zerob $inf $minf $infinity) :test #'eq) small)
644 ((not (free small '$ind)) '$ind) ;Not exactly right but not
645 ((not (free small '$und)) '$und) ;causing trouble now.
646 ((mapatom small) small)
647 (t (let ((preserve-direction t)
648 (new-small (subst (m^ '$inf -1) '$zeroa
649 (subst (m^ '$minf -1) '$zerob small))))
650 (simpinf new-small)))))
653 ;;;*I* INDICATES: T => USE LIMIT1,THINK, NIL => USE SIMPLIMIT.
654 (defun limit (exp var val *i*)
655 (cond
656 ((among '$und exp) '$und)
657 ((eq var exp) val)
658 ((atom exp) exp)
659 ((not (among var exp))
660 (cond ((amongl '($inf $minf $infinity $ind) exp)
661 (simpinf exp))
662 ((amongl '($zeroa $zerob) exp)
663 ;; Simplify expression with zeroa or zerob.
664 (simpab exp))
665 (t exp)))
666 ((getlimval exp))
667 (t (putlimval exp (cond ((and limit-using-taylor
668 (null taylored)
669 (tlimp exp var))
670 (taylim exp var val *i*))
671 ((ratp exp var) (ratlim exp))
672 ((or (eq *i* t) (radicalp exp var))
673 (limit1 exp var val))
674 ((eq *i* 'think)
675 (cond ((or (mtimesp exp) (mexptp exp))
676 (limit1 exp var val))
677 (t (simplimit exp var val))))
678 (t (simplimit exp var val)))))))
680 (defun limitsimp (exp var)
681 (limitsimp-expt (sin-sq-cos-sq-sub exp) var))
683 ;; if var appears in base and power of expt,
684 ;; push var into power of of expt
685 (defun limitsimp-expt (exp var)
686 (cond ((or (atom exp)
687 (mnump exp)
688 (freeof var exp)) exp)
689 ((and (mexptp exp)
690 (not (freeof var (cadr exp)))
691 (not (freeof var (caddr exp))))
692 (m^ '$%e (simplify `((%log) ,exp))))
693 (t (subst0 (cons (cons (caar exp) ())
694 (mapcar #'(lambda (x)
695 (limitsimp-expt x var))
696 (cdr exp)))
697 exp))))
699 (defun gather-args-of (e fn x)
700 (cond (($mapatom e) nil)
701 ((and (eq fn (caar e)) (not (freeof x e))) (cdr e))
703 (remove-duplicates (reduce #'append
704 (mapcar #'(lambda (q)
705 (gather-args-of q fn x)) (cdr e))) :test #'alike1))))
707 ;; Replace every subexpression of e of the form cos(X)^2 + sin(X)^2, where X
708 ;; depends on x, by 1.
709 (defun sin-sq-cos-sq-sub (e &optional (x var))
710 (let ((ccc nil) (z) (ee))
711 (cond (($mapatom e) e)
712 ((mplusp e)
713 (setq ccc (gather-args-of e '%cos x))
714 (dolist (g ccc)
715 (setq z (gensym))
716 (setq ee (maxima-substitute z (power (ftake '%cos g) 2) e))
717 (setq ee (maxima-substitute (sub 1 z) (power (ftake '%sin g) 2) ee))
718 (when (freeof z (sratsimp ee))
719 (setq e ee)))
721 ;; maybe this isn't needed, but it's not wrong.
722 ((eq 'mqapply (caar e))
723 (subftake (caar (second e))
724 (mapcar #'(lambda (q) (sin-sq-cos-sq-sub q x)) (subfunsubs e))
725 (mapcar #'(lambda (q) (sin-sq-cos-sq-sub q x)) (subfunargs e))))
726 ;; map sin-sq-cos-sq-sub over the args
728 (fapply (caar e) (mapcar #'(lambda (q) (sin-sq-cos-sq-sub q x)) (cdr e)))))))
730 (defun expand-trigs (x var)
731 (cond ((atom x) x)
732 ((mnump x) x)
733 ((and (or (eq (caar x) '%sin)
734 (eq (caar x) '%cos))
735 (not (free (cadr x) var)))
736 ($trigexpand x))
737 ((member 'array (car x))
738 ;; Some kind of array reference. Return it.
740 (t (simplify (cons (ncons (caar x))
741 (mapcar #'(lambda (x)
742 (expand-trigs x var))
743 (cdr x)))))))
745 ;; The functionality of tansc has been blended into extra-simp, so we
746 ;; could orphan tansc. But extra-simp does more than tansc and tansc is
747 ;; called by the definite integration code and by the limit code. So we'll
748 ;; not orphan tansc.
749 (defun tansc (e)
750 (cond ((not (involve e
751 '(%cot %csc %binomial
752 %sec %coth %sech %csch
753 %acot %acsc %asec %acoth
754 %asech %acsch
755 %jacobi_ns %jacobi_nc %jacobi_cs
756 %jacobi_ds %jacobi_dc)))
758 (t (sratsimp (tansc1 e)))))
760 (defun tansc1 (e &aux tem)
761 (cond ((atom e) e)
762 ((and (setq e (cons (car e) (mapcar 'tansc1 (cdr e)))) ()))
763 ((setq tem (assoc (caar e) '((%cot . %tan) (%coth . %tanh)
764 (%sec . %cos) (%sech . %cosh)
765 (%csc . %sin) (%csch . %sinh)) :test #'eq))
766 (tansc1 (m^ (list (ncons (cdr tem)) (cadr e)) -1.)))
767 ((setq tem (assoc (caar e) '((%jacobi_nc . %jacobi_cn)
768 (%jacobi_ns . %jacobi_sn)
769 (%jacobi_cs . %jacobi_sc)
770 (%jacobi_ds . %jacobi_sd)
771 (%jacobi_dc . %jacobi_cd)) :test #'eq))
772 ;; Converts Jacobi elliptic function to its reciprocal
773 ;; function.
774 (tansc1 (m^ (list (ncons (cdr tem)) (cadr e) (third e)) -1.)))
775 ((setq tem (member (caar e) '(%sinh %cosh %tanh) :test #'eq))
776 (let (($exponentialize t))
777 (resimplify e)))
778 ((setq tem (assoc (caar e) '((%acsc . %asin) (%asec . %acos)
779 (%acot . %atan) (%acsch . %asinh)
780 (%asech . %acosh) (%acoth . %atanh)) :test #'eq))
781 (list (ncons (cdr tem)) (m^t (cadr e) -1.)))
782 ((and (eq (caar e) '%binomial) (among var (cdr e)))
783 (m// `((mfactorial) ,(cadr e))
784 (m* `((mfactorial) ,(m+t (cadr e) (m- (caddr e))))
785 `((mfactorial) ,(caddr e)))))
786 (t e)))
788 ;; Like TANSC but dependency on VAR is explicit. Use this instead of
789 ;; TANSC when possible.
790 (defun tansc-var (e var1)
791 (cond ((not (involve-var e var1
792 '(%cot %csc %binomial
793 %sec %coth %sech %csch
794 %acot %acsc %asec %acoth
795 %asech %acsch
796 %jacobi_ns %jacobi_nc %jacobi_cs
797 %jacobi_ds %jacobi_dc)))
800 (labels
801 ((tansc1-v (e &aux tem)
802 ;; Copy of TANSC1, but VAR replaced by VAR1
803 (cond ((atom e)
805 ((and (setq e (cons (car e) (mapcar #'tansc1-v (cdr e))))
806 ()))
807 ((setq tem (assoc (caar e)
808 '((%cot . %tan) (%coth . %tanh)
809 (%sec . %cos) (%sech . %cosh)
810 (%csc . %sin) (%csch . %sinh))
811 :test #'eq))
812 (tansc1-v (m^ (list (ncons (cdr tem)) (cadr e)) -1.)))
813 ((setq tem (assoc (caar e)
814 '((%jacobi_nc . %jacobi_cn)
815 (%jacobi_ns . %jacobi_sn)
816 (%jacobi_cs . %jacobi_sc)
817 (%jacobi_ds . %jacobi_sd)
818 (%jacobi_dc . %jacobi_cd))
819 :test #'eq))
820 ;; Converts Jacobi elliptic function to its reciprocal
821 ;; function.
822 (tansc1-v (m^ (list (ncons (cdr tem)) (cadr e) (third e))
823 -1.)))
824 ((setq tem (member (caar e) '(%sinh %cosh %tanh) :test #'eq))
825 (let (($exponentialize t))
826 (resimplify e)))
827 ((setq tem (assoc (caar e)
828 '((%acsc . %asin) (%asec . %acos)
829 (%acot . %atan) (%acsch . %asinh)
830 (%asech . %acosh) (%acoth . %atanh))
831 :test #'eq))
832 (list (ncons (cdr tem)) (m^t (cadr e) -1.)))
833 ((and (eq (caar e) '%binomial)
834 (among var1 (cdr e)))
835 (m// `((mfactorial) ,(cadr e))
836 (m* `((mfactorial) ,(m+t (cadr e) (m- (caddr e))))
837 `((mfactorial) ,(caddr e)))))
838 (t e))))
839 (sratsimp (tansc1-v e))))))
841 (defun hyperex (ex)
842 (cond ((not (involve ex '(%sin %cos %tan %asin %acos %atan
843 %sinh %cosh %tanh %asinh %acosh %atanh)))
845 (t (hyperex0 ex))))
847 (defun hyperex0 (ex)
848 (cond ((atom ex) ex)
849 ((eq (caar ex) '%sinh)
850 (m// (m+ (m^ '$%e (cadr ex)) (m- (m^ '$%e (m- (cadr ex)))))
852 ((eq (caar ex) '%cosh)
853 (m// (m+ (m^ '$%e (cadr ex)) (m^ '$%e (m- (cadr ex))))
855 ((and (member (caar ex)
856 '(%sin %cos %tan %asin %acos %atan %sinh
857 %cosh %tanh %asinh %acosh %atanh) :test #'eq)
858 (among var ex))
859 (hyperex1 ex))
860 (t (cons (car ex) (mapcar #'hyperex0 (cdr ex))))))
862 (defun hyperex1 (ex)
863 (resimplify ex))
865 ;;Used by tlimit also.
866 (defun limit1 (exp var val)
867 (prog ()
868 (let ((lhprogress? lhp?)
869 (lhp? ())
870 (ans ()))
871 (cond ((setq ans (and (not (atom exp)) (getlimval exp)))
872 (return ans))
873 ((and (not (infinityp val)) (setq ans (simplimsubst val exp)))
874 (return ans))
875 (t nil))
876 ;;;NUMDEN* => (values numerator denominator)
877 (multiple-value-bind (n dn)
878 (numden* exp)
879 (cond ((not (among var dn))
880 (return (simplimit (m// (simplimit n var val) dn) var val)))
881 ((not (among var n))
882 (return (simplimit (m* n (simplimexpt dn -1 (simplimit dn var val) -1)) var val)))
883 ((and lhprogress?
884 (/#alike n (car lhprogress?))
885 (/#alike dn (cdr lhprogress?)))
886 (throw 'lhospital nil)))
887 (return (limit2 n dn var val))))))
890 ;; If e/f is free of var (a special), return true. This code
891 ;; assumes that f is not zero. First, we test if e & f
892 ;; are alike--this check is relatively fast; second, we check
893 ;; if e/f is free of var.
894 (defun /#alike (e f)
895 (or (alike1 e f) (freeof var (sratsimp (div e f)))))
897 (defun limit2 (n dn var val)
898 (prog (n1 d1 lim-sign gcp sheur-ans)
899 (setq n (hyperex n) dn (hyperex dn))
900 (setq d1 (limit dn var val nil)
901 n1 (limit n var val nil))
902 (cond ((or (null n1) (null d1)) (return nil))
903 (t (setq n1 (sratsimp n1) d1 (sratsimp d1))))
904 (cond ((or (involve n '(mfactorial)) (involve dn '(mfactorial)))
905 (let ((ans (limfact2 n dn var val)))
906 (cond (ans (return ans))))))
907 (cond ((and (zerop2 n1) (zerop2 d1))
908 (cond ((not (equal (setq gcp (gcpower n dn)) 1))
909 (return (colexpt n dn gcp)))
910 ((and (real-epsilonp val)
911 (not (free n '%log))
912 (not (free dn '%log)))
913 (return (liminv (m// n dn))))
914 ((setq n1 (try-lhospital-quit n dn nil))
915 (return n1))))
916 ;; when dn # 0, we have ind/ind = ind, otherwise ind/ind = und
917 ((and (eq n1 '$ind) (eq d1 '$ind))
918 (return (if (eq t (mnqp dn 0)) '$ind '$und)))
919 ((and (zerop2 n1) (not (member d1 '($ind $und) :test #'eq))) (return 0))
920 ((zerop2 d1)
921 (setq n1 (ridofab n1))
922 (return (simplimtimes `(,n1 ,(simplimexpt dn -1 d1 -1))))))
923 (setq n1 (ridofab n1))
924 (setq d1 (ridofab d1))
925 (cond ((or (eq d1 '$und)
926 (and (eq n1 '$und) (not (real-infinityp d1))))
927 (return '$und))
928 ((eq d1 '$ind)
929 ;; At this point we have n1/$ind. Look if n1 is one of the
930 ;; infinities or zero.
931 (cond ((and (infinityp n1) (eq ($sign dn) '$pos))
932 (return n1))
933 ((and (infinityp n1) (eq ($sign dn) '$neg))
934 (return (simpinf (m* -1 n1))))
935 ((and (zerop1 n1)
936 (or (eq ($sign dn) '$pos)
937 (eq ($sign dn) '$neg)))
938 (return 0))
939 (t (return '$und))))
940 ((eq n1 '$ind) (return (cond ((infinityp d1) 0)
941 ((equal d1 0) '$und)
942 (t '$ind)))) ;SET LB
943 ((and (real-infinityp d1) (member n1 '($inf $und $minf) :test #'eq))
944 (cond ((and (not (atom dn)) (not (atom n))
945 (cond ((not (equal (setq gcp (gcpower n dn)) 1))
946 (return (colexpt n dn gcp)))
947 ((and (eq '$inf val)
948 (or (involve dn '(mfactorial %gamma))
949 (involve n '(mfactorial %gamma))))
950 (return (limfact n dn))))))
951 ((eq n1 d1) (setq lim-sign 1) (go cp))
952 (t (setq lim-sign -1) (go cp))))
953 ((and (infinityp d1) (infinityp n1))
954 (setq lim-sign (if (or (eq d1 '$minf) (eq n1 '$minf)) -1 1))
955 (go cp))
956 (t (return (simplimtimes `(,n1 ,(m^ d1 -1))))))
957 cp (setq n ($expand n) dn ($expand dn))
958 (cond ((mplusp n)
959 (let ((new-n (m+l (maxi (cdr n)))))
960 (cond ((not (alike1 new-n n))
961 (return (limit (m// new-n dn) var val 'think))))
962 (setq n1 new-n)))
963 (t (setq n1 n)))
964 (cond ((mplusp dn)
965 (let ((new-dn (m+l (maxi (cdr dn)))))
966 (cond ((not (alike1 new-dn dn))
967 (return (limit (m// n new-dn) var val 'think))))
968 (setq d1 new-dn)))
969 (t (setq d1 dn)))
970 (setq sheur-ans (sheur0 n1 d1))
971 (cond ((or (member sheur-ans '($inf $zeroa) :test #'eq)
972 (free sheur-ans var))
973 (return (simplimtimes `(,lim-sign ,sheur-ans))))
974 ((and (alike1 sheur-ans dn)
975 (not (mplusp n))))
976 ((member (setq n1 (cond ((expfactorp n1 d1) (expfactor n1 d1 var))
977 (t ())))
978 '($inf $zeroa) :test #'eq)
979 (return n1))
980 ((not (null (setq n1 (cond ((expfactorp n dn) (expfactor n dn var))
981 (t ())))))
982 (return n1))
983 ((and (alike1 sheur-ans dn) (not (mplusp n))))
984 ((not (alike1 sheur-ans (m// n dn)))
985 (return (simplimit (m// ($expand (m// n sheur-ans))
986 ($expand (m// dn sheur-ans)))
988 val))))
989 (cond ((and (not (and (eq val '$inf) (expp n) (expp dn)))
990 (setq n1 (try-lhospital-quit n dn nil))
991 (not (eq n1 '$und)))
992 (return n1)))
993 (throw 'limit t)))
995 ;; Test whether both n and dn have form
996 ;; product of poly^poly.
998 ;; It's important that both n and dn be free of extended real numbers
999 ;; (minf, zerob, ...), so we check for that too (see bug #4222).
1000 (defun expfactorp (n dn)
1001 (do ((llist (append (cond ((mtimesp n) (cdr n))
1002 (t (ncons n)))
1003 (cond ((mtimesp dn) (cdr dn))
1004 (t (ncons dn))))
1005 (cdr llist))
1006 (exp? t) ;IS EVERY ELEMENT SO FAR
1007 (factor nil)) ;A POLY^POLY?
1008 ((or (null llist)
1009 (not exp?))
1010 exp?)
1011 (setq factor (car llist))
1012 (setq exp?
1013 (and
1014 (not (amongl (list '$minf '$zerob '$zeroa '$ind '$und '$inf '$infinity) factor))
1015 (or (polyinx factor var ())
1016 (and (mexptp factor)
1017 (polyinx (cadr factor) var ())
1018 (polyinx (caddr factor) var ())))))))
1020 (defun expfactor (n dn var) ;Attempts to evaluate limit by grouping
1021 (prog (highest-deg) ; terms with similar exponents.
1022 (let ((new-exp (exppoly n))) ;exppoly unrats expon
1023 (setq n (car new-exp) ;and rtns deg of expons
1024 highest-deg (cdr new-exp)))
1025 (cond ((null n) (return nil))) ;nil means expon is not
1026 (let ((new-exp (exppoly dn))) ;a rat func.
1027 (setq dn (car new-exp)
1028 highest-deg (max highest-deg (cdr new-exp))))
1029 (cond ((or (null dn)
1030 (= highest-deg 0)) ; prevent infinite recursion
1031 (return nil)))
1032 (return
1033 (do ((answer 1)
1034 (degree highest-deg (1- degree))
1035 (numerator n)
1036 (denominator dn)
1037 (numfactors nil)
1038 (denfactors nil))
1039 ((= degree -1)
1040 (m* answer
1041 (limit (m// numerator denominator)
1044 'think)))
1045 (let ((newnumer-factor (get-newexp&factors
1046 numerator
1047 degree
1048 var)))
1049 (setq numerator (car newnumer-factor)
1050 numfactors (cdr newnumer-factor)))
1051 (let ((newdenom-factor (get-newexp&factors
1052 denominator
1053 degree
1054 var)))
1055 (setq denominator (car newdenom-factor)
1056 denfactors (cdr newdenom-factor)))
1057 (setq answer (simplimit (list '(mexpt)
1058 (m* answer
1059 (m// numfactors denfactors))
1060 (cond ((> degree 0) var)
1061 (t 1)))
1063 val))
1064 (cond ((member answer '($ind $und) :test #'equal)
1065 ;; cannot handle limit(exp(x*%i)*x, x, inf);
1066 (return nil))
1067 ((member answer '($inf $minf) :test #'equal)
1068 ;; 0, zeroa, zerob are passed through to next iteration
1069 (return (simplimtimes (list (m// numerator denominator) answer)))))))))
1071 (defun exppoly (exp) ;RETURNS EXPRESSION WITH UNRATTED EXPONENTS
1072 (do ((factor nil)
1073 (highest-deg 0)
1074 (new-exp 1)
1075 (exp (cond ((mtimesp exp)
1076 (cdr exp))
1077 (t (ncons exp)))
1078 (cdr exp)))
1079 ((null exp) (cons new-exp highest-deg))
1080 (setq factor (car exp))
1081 (setq new-exp
1082 (m* (cond ((or (not (mexptp factor))
1083 (not (ratp (caddr factor) var)))
1084 factor)
1085 (t (setq highest-deg
1086 (max highest-deg
1087 (ratdegree (caddr factor))))
1088 (m^ (cadr factor) (unrat (caddr factor)))))
1089 new-exp))))
1091 (defun unrat (exp) ;RETURNS UNRATTED EXPRESSION
1092 (multiple-value-bind (n d)
1093 (numden* exp)
1094 (let ((tem ($divide n d)))
1095 (m+ (cadr tem)
1096 (m// (caddr tem) d)))))
1098 (defun get-newexp&factors (exp degree var) ;RETURNS (CONS NEWEXP FACTORS)
1099 (do ((terms (cond ((mtimesp exp)(cdr exp)) ; SUCH THAT
1100 (t (ncons exp))) ; NEWEXP*FACTORS^(VAR^DEGREE)
1101 (cdr terms)) ; IS EQUAL TO EXP.
1102 (factors 1)
1103 (newexp 1)
1104 (factor nil))
1105 ((null terms)
1106 (cons newexp
1107 factors))
1108 (setq factor (car terms))
1109 (cond ((not (mexptp factor))
1110 (cond ((= degree 0)
1111 (setq factors (m* factor factors)))
1112 (t (setq newexp (m* factor newexp)))))
1113 ((or (= degree -1)
1114 (= (ratdegree (caddr factor))
1115 degree))
1116 (setq factors (m* (m^ (cadr factor)
1117 (leading-coef (caddr factor)))
1118 factors)
1119 newexp (m* (m^ (cadr factor)
1120 (m- (caddr factor)
1121 (m* (leading-coef (caddr factor))
1122 (m^ var degree))))
1123 newexp)))
1124 (t (setq newexp (m* factor newexp))))))
1126 (defun leading-coef (rat)
1127 (ratlim (m// rat (m^ var (ratdegree rat)))))
1129 (defun ratdegree (rat)
1130 (multiple-value-bind (n d)
1131 (numden* rat)
1132 (- (deg n) (deg d))))
1134 (defun limfact2 (n d var val)
1135 (let ((n1 (reflect0 n var val))
1136 (d1 (reflect0 d var val)))
1137 (cond ((and (alike1 n n1)
1138 (alike1 d d1))
1139 nil)
1140 (t (limit (m// n1 d1) var val 'think)))))
1142 ;; takes expression and returns operator at front with all flags removed
1143 ;; except array flag.
1144 ;; array flag must match for alike1 to consider two things to be the same.
1145 ;; ((MTIMES SIMP) ... ) => (MTIMES)
1146 ;; ((PSI SIMP ARRAY) 0) => (PSI ARRAY)
1147 (defun operator-with-array-flag (exp)
1148 (cond ((member 'array (car exp) :test #'eq)
1149 (list (caar exp) 'array))
1150 (t (list (caar exp)))))
1152 (defun reflect0 (exp var val)
1153 (cond ((atom exp) exp)
1154 ((and (eq (caar exp) 'mfactorial)
1155 (let ((argval (limit (cadr exp) var val 'think)))
1156 (or (eq argval '$minf)
1157 (and (numberp argval)
1158 (> 0 argval)))))
1159 (reflect (cadr exp)))
1160 (t (cons (operator-with-array-flag exp)
1161 (mapcar (function
1162 (lambda (term)
1163 (reflect0 term var val)))
1164 (cdr exp))))))
1166 (defun reflect (arg)
1167 (m* -1
1168 '$%pi
1169 (m^ (list (ncons 'mfactorial)
1170 (m+ -1
1171 (m* -1 arg)))
1173 (m^ (list (ncons '%sin)
1174 (m* '$%pi arg))
1175 -1)))
1177 (defun limfact (n d)
1178 (let ((ans ()))
1179 (setq n (stirling0 n)
1180 d (stirling0 d))
1181 (setq ans (toplevel-$limit (m// n d) var '$inf))
1182 (cond ((and (atom ans)
1183 (not (member ans '(und ind ) :test #'eq))) ans)
1184 ((eq (caar ans) '%limit) ())
1185 (t ans))))
1187 ;; substitute asymptotic approximations for gamma, factorial, and
1188 ;; polylogarithm
1189 (defun stirling0 (e)
1190 (cond ((atom e) e)
1191 ((and (setq e (cons (car e) (mapcar 'stirling0 (cdr e))))
1192 nil))
1193 ((eq (caar e) '%gamma)
1194 (let ((ans (limit (cadr e) var val 'think)))
1195 (cond ((memq ans '($inf $minf $infinity))
1196 (stirling (cadr e)))
1197 ((eq ans '$zeroa)
1198 (add (div 1 (cadr e)) (mul -1 '$%gamma)))
1199 ((and (integerp ans) (< ans 0))
1200 (div (if (oddp ans) -1 1)
1201 (mul (ftake 'mfactorial (mul -1 ans)) (sub (cadr e) ans))))
1202 (t (ftake '%gamma (cadr e))))))
1204 ((eq (caar e) 'mfactorial)
1205 (let ((n (limit (cadr e) var val 'think)))
1206 (cond ((eq n '$inf)
1207 (stirling (add 1 (cadr e))))
1208 ((and (integerp n) (< n 0))
1209 (setq n (mul -1 n))
1210 (div (if (oddp n) 1 -1)
1211 (mul (ftake 'mfactorial (sub n 1)) (add var n))))
1212 (t e))))
1213 ((and (eq (caar e) 'mqapply) ;; polylogarithm
1214 (eq (subfunname e) '$li)
1215 (let ((arglim (limit (car (subfunargs e)) var val 'think)))
1216 (or (eq arglim '$inf) (eq arglim '$minf)))
1217 (integerp (car (subfunsubs e))))
1218 (li-asymptotic-expansion (m- (car (subfunsubs e)) 1)
1219 (car (subfunsubs e))
1220 (car (subfunargs e))))
1221 (t e)))
1223 (defun stirling (x)
1224 "Return sqrt(2*%pi/x)*(x/%e)^x, the Stirling approximation of
1225 gamma(x). The argument x can be any valid expression."
1226 (mul (power (div (mul 2 '$%pi) x)
1227 1//2)
1228 (power (div x '$%e)
1229 x)))
1231 (defun no-err-sub (v e &aux ans)
1232 (let ((errorsw t) (*zexptsimp? t)
1233 (errcatch t)
1234 ;; Don't print any error messages
1235 ($errormsg nil))
1236 ;; Should we just use IGNORE-ERRORS instead HANDLER-CASE here? I
1237 ;; (rtoy) am choosing the latter so that unexpected errors will
1238 ;; actually show up instead of being silently discarded.
1239 (handler-case
1240 (setq ans (catch 'errorsw
1241 (ignore-rat-err
1242 (sratsimp (subin v e)))))
1243 (maxima-$error ()
1244 (setq ans nil)))
1245 (cond ((null ans) t) ; Ratfun package returns NIL for failure.
1246 (t ans))))
1248 ;; Like NO-ERR-SUB but dependency on VAR is explicit. Use this
1249 ;; instead when possible.
1250 (defun no-err-sub-var (v e var1 &aux ans)
1251 (let ((errorsw t) (*zexptsimp? t)
1252 (errcatch t)
1253 ;; Don't print any error messages
1254 ($errormsg nil))
1255 ;; Should we just use IGNORE-ERRORS instead HANDLER-CASE here? I
1256 ;; (rtoy) am choosing the latter so that unexpected errors will
1257 ;; actually show up instead of being silently discarded.
1258 (handler-case
1259 (setq ans (catch 'errorsw
1260 (ignore-rat-err
1261 (sratsimp (subin-var v e var1)))))
1262 (maxima-$error ()
1263 (setq ans nil)))
1264 (cond ((null ans) t) ; Ratfun package returns NIL for failure.
1265 (t ans))))
1267 (defun simplim%mabs (e x pt)
1268 (let ((lim (limit (cadr e) x pt 'think)))
1269 (cond ((or (eq lim '$zeroa) (eql lim 0) (eq lim '$ind)) lim)
1270 ((eq lim '$zerob) '$zeroa)
1271 ((eq lim '$und) (throw 'limit nil))
1272 ((or (eq lim '$minf) (eq lim '$inf) (eq lim '$infinity)) '$inf)
1273 (t (ftake 'mabs lim)))))
1274 (setf (get 'mabs 'simplim%function) 'simplim%mabs)
1276 (defun extended-real-p (e)
1277 (member e (list '$minf '$zerob '$zeroa '$ind '$und '$inf '$infinity)))
1279 ;; Evaluate the limit of e as var (special) approaches v using direct substitution.
1280 ;; This function is the last of the chain of methods tried by limit. As such it
1281 ;; shouldn't call higher level functions such as simplimit or limit--doing so
1282 ;; would risk creating an infinite loop.
1284 ;; This function special cases sums, products, and powers. It declines to use
1285 ;; direct substitution on any expression whose main operator has a simplim%function
1286 ;; function. Generally, limits of functions that have a simplim%function should be
1287 ;; handled by those specialized functions, not by simplimsubst. Having said this,
1288 ;; it's OK for simplimsubst to special case an operator and do direct substitution
1289 ;; when its OK. The cases of log, cosine, and sine happen often enough that these
1290 ;; functions are special cased.
1292 ;; Possibly simplimsubst should decline to do direct substitution on functions
1293 ;; that have a limit function, for example inverse_jacobi_ns.
1295 ;; For all other kinds of expressions, this function assumes that if substitution
1296 ;; doesn't result in an error (division by zero, for example), the function
1297 ;; is continuous at the limit point. That's dodgy. This dodginess underscores the
1298 ;; need to define a simplim%function functions that are not continuous on their
1299 ;; domains.
1301 ;; This function sometimes receives an un-simplified expression. Maybe they should be
1302 ;; simplified, maybe not.
1304 ;; Locally setting $numer and $%enumer to nil keeps some limits, for example
1305 ;; limit(sin(x)/x,x,0) from returning 1.0 when numer is true. (Barton Willis)
1307 (defun simplimsubst (v e)
1308 (let ((ans nil) ($numer nil) ($%enumer nil) (ee))
1309 (cond
1310 ;; When e is a number, return it.
1311 (($numberp e) e)
1312 ;; When e is a mapatom, substitute v for var and return.
1313 (($mapatom e) ($substitute v var e))
1314 ;; Special case mexpt expressions. Decline direct substitution for
1315 ;; extended reals.
1316 ((and (mexptp e) (not (extended-real-p v)))
1317 (let ((x (simplimsubst v (second e)))
1318 (n (simplimsubst v (third e))))
1319 ;; Decline direct substitution (DS) for 0^negative. Also decline
1320 ;; DS when x is on the negative real axis and n isn't an integer.
1321 ;; Additionally, we require that DS is OK for both x & n.
1322 (if (and x n (not (and (zerop2 x) (eq t (mgqp 0 n)))) ; not 0^negative
1323 (or (off-negative-real-axisp x) (integerp n)))
1324 (ftake 'mexpt x n) nil)))
1325 ;; Special case product and sum expressions. Again, we decline direct
1326 ;; substitution for extended reals.
1327 ((and (or (mplusp e) (mtimesp e)) (not (extended-real-p v)))
1328 (setq ee (mapcar #'(lambda(q) (simplimsubst v q)) (cdr e)))
1329 (if (some #'(lambda (q) (eq q nil)) ee) nil
1330 (simplifya (cons (list (caar e)) ee) t)))
1331 ;; Decline direct substitution for sums, products, and powers for
1332 ;; the extended real case.
1333 ((and (or (mexptp e) (mplusp e) (mtimesp e)) (extended-real-p v))
1334 nil)
1335 ;; Special case log expressions--possibly the log case happens
1336 ;; often enough to make this worthwhile.
1337 ((and (consp e) (consp (car e)) (eq '%log (caar e)))
1338 (let ((w (simplimsubst v (cadr e))))
1339 (if (and w (off-negative-real-axisp w)) (ftake '%log w) nil)))
1340 ;; Special case %cos and %sin expressions--we could special case others.
1341 ;; The lenient-realp check declines direct substitution for complex arguments--
1342 ;; this check could be relaxed.
1343 ((and (consp e) (consp (car e)) (or (member (caar e) (list '%cos '%sin))))
1344 (let ((op (caar e)))
1345 (setq e (simplimsubst v (second e)))
1346 (if (and e (lenient-realp e) (not (extended-real-p e))) (ftake op e) nil)))
1347 ;; Don't use direct substitution on expressions whose main operator has
1348 ;; a simplim%function.
1349 ((and (consp e) (consp (car e)) (get (caar e) 'simplim%function)) nil)
1350 ;; The function no-err-sub returns true when there is an error
1351 ((not (eq t (setq ans (no-err-sub (ridofab v) e))))
1352 ;; Previously the condition (zerop2 ans) was (=0 ($radcan ans)). In
1353 ;; December 2021, the testsuite + the share testsuite only gives ans = 0,
1354 ;; making the radcan unneeded.
1355 (cond ((and (member v '($zeroa $zerob) :test #'eq) (zerop2 ans))
1356 (setq ans (behavior e var v))
1357 (cond ((eql ans 1) '$zeroa)
1358 ((eql ans -1) '$zerob)
1359 (t nil))) ;behavior can't find direction
1360 (t ans)))
1361 ;; direct substitution fails, so return nil.
1362 (t nil))))
1364 ;;;returns (cons numerator denominator)
1365 (defun numden* (e)
1366 (let ((e (factor (simplify e)))
1367 (numer ())
1368 (denom ()))
1369 (cond ((atom e)
1370 (push e numer))
1371 ((mtimesp e)
1372 (mapc #'forq (cdr e)))
1374 (forq e)))
1375 (cond ((null numer)
1376 (setq numer 1))
1377 ((null (cdr numer))
1378 (setq numer (car numer)))
1380 (setq numer (m*l numer))))
1381 (cond ((null denom)
1382 (setq denom 1))
1383 ((null (cdr denom))
1384 (setq denom (car denom)))
1386 (setq denom (m*l denom))))
1387 (values (factor numer) (factor denom))))
1389 ;;;FACTOR OR QUOTIENT
1390 ;;;Setq's the special vars numer and denom from numden*
1391 (defun forq (e)
1392 (cond ((and (mexptp e)
1393 (not (freeof var e))
1394 (null (pos-neg-p (caddr e))))
1395 (push (m^ (cadr e) (m* -1. (caddr e))) denom))
1396 (t (push e numer))))
1398 ;;;Predicate to tell whether an expression is pos,zero or neg as var -> val.
1399 ;;;returns T if pos,zero. () if negative or don't know.
1400 (defun pos-neg-p (exp)
1401 (let ((ans (limit exp var val 'think)))
1402 (cond ((and (not (member ans '($und $ind $infinity) :test #'eq))
1403 (equal ($imagpart ans) 0))
1404 (let ((sign (getsignl ans)))
1405 (cond ((or (equal sign 1)
1406 (equal sign 0))
1408 ((equal sign -1) nil))))
1409 (t 'unknown))))
1411 (declare-top (unspecial n dn))
1413 (defun expp (e)
1414 (cond ((radicalp e var) nil)
1415 ((member (caar e) '(%log %sin %cos %tan %sinh %cosh %tanh mfactorial
1416 %asin %acos %atan %asinh %acosh %atanh) :test #'eq) nil)
1417 ((simplexp e) t)
1418 ((do ((e (cdr e) (cdr e)))
1419 ((null e) nil)
1420 (and (expp (car e)) (return t))))))
1422 (defun simplexp (e)
1423 (and (mexptp e)
1424 (radicalp (cadr e) var)
1425 (among var (caddr e))
1426 (radicalp (caddr e) var)))
1429 (defun gcpower (a b)
1430 ($gcd (getexp a) (getexp b)))
1432 (defun getexp (exp)
1433 (cond ((and (mexptp exp)
1434 (free (caddr exp) var)
1435 (eq (ask-integer (caddr exp) '$integer) '$yes))
1436 (caddr exp))
1437 ((mtimesp exp) (getexplist (cdr exp)))
1438 (t 1)))
1440 (defun getexplist (list)
1441 (cond ((null (cdr list))
1442 (getexp (car list)))
1443 (t ($gcd (getexp (car list))
1444 (getexplist (cdr list))))))
1446 (defun limroot (exp power)
1447 (cond ((or (atom exp) (not (member (caar exp) '(mtimes mexpt) :test #'eq)))
1448 (limroot (list '(mexpt) exp 1) power)) ;This is strange-JIM.
1449 ((mexptp exp) (m^ (cadr exp)
1450 (sratsimp (m* (caddr exp) (m^ power -1.)))))
1451 (t (m*l (mapcar #'(lambda (x)
1452 (limroot x power))
1453 (cdr exp))))))
1455 ;;NUMERATOR AND DENOMINATOR HAVE EXPONENTS WITH GCD OF GCP.
1456 ;;; Used to call simplimit but some of the transformations used here
1457 ;;; were not stable w.r.t. the simplifier, so try keeping exponent separate
1458 ;;; from bas.
1460 (defun colexpt (n dn gcp)
1461 (let ((bas (m* (limroot n gcp) (limroot dn (m* -1 gcp))))
1462 (expo gcp)
1463 baslim expolim)
1464 (setq baslim (limit bas var val 'think))
1465 (setq expolim (limit expo var val 'think))
1466 (simplimexpt bas expo baslim expolim)))
1468 ;; this function is responsible for the following bug:
1469 ;; limit(x^2 + %i*x, x, inf) -> inf (should be infinity)
1470 (defun ratlim (e)
1471 (setq e (sratsimp ($trigreduce e)))
1472 (cond ((member val '($inf $infinity) :test #'eq)
1473 (setq e (maxima-substitute (m^t 'x -1) var e)))
1474 ((eq val '$minf)
1475 (setq e (maxima-substitute (m^t -1 (m^t 'x -1)) var e)))
1476 ((eq val '$zerob)
1477 (setq e (maxima-substitute (m- 'x) var e)))
1478 ((eq val '$zeroa)
1479 (setq e (maxima-substitute 'x var e)))
1480 ((setq e (maxima-substitute (m+t 'x val) var e))))
1481 (destructuring-let* ((e (let (($ratfac ()))
1482 ($rat (sratsimp e) 'x)))
1483 ((h n . d) e)
1484 (g (genfind h 'x))
1485 (nd (lodeg n g))
1486 (dd (lodeg d g)))
1487 (cond ((and (setq e
1488 (subst var
1490 (sratsimp (m// ($ratdisrep `(,h ,(locoef n g) . 1))
1491 ($ratdisrep `(,h ,(locoef d g) . 1))))))
1492 (> nd dd))
1493 (cond ((not (member val '($zerob $zeroa $inf $minf) :test #'eq))
1495 ((not (equal ($imagpart e) 0))
1497 ((null (setq e (getsignl ($realpart e))))
1499 ((equal e 1) '$zeroa)
1500 ((equal e -1) '$zerob)
1501 (t 0)))
1502 ((equal nd dd) e)
1503 ((not (member val '($zerob $zeroa $infinity $inf $minf) :test #'eq))
1504 (throw 'limit t))
1505 ((eq val '$infinity) '$infinity)
1506 ((not (equal ($imagpart e) 0)) '$infinity)
1507 ((null (setq e (getsignl ($realpart e))))
1508 (throw 'limit t))
1509 ((equal e 1) '$inf)
1510 ((equal e -1) '$minf)
1511 (t 0))))
1513 (defun lodeg (n x)
1514 (if (or (atom n) (not (eq (car n) x)))
1516 (lowdeg (cdr n))))
1518 (defun locoef (n x)
1519 (if (or (atom n) (not (eq (car n) x)))
1521 (car (last n))))
1523 ;; This function tries to determine the increasing/decreasing
1524 ;; behavior of an expression exp with respect to some variable var.
1525 ;; val determines the mode:
1526 ;; - $zeroa: From "positive zero" towards the right
1527 ;; - $zerob: From "negative zero" towards the left
1528 ;; - $inf: From "positive infinity" towards the left
1529 ;; - $minf: From "negative infinity" towards the right
1530 ;; Return values are -1 (decreasing), +1 (increasing) or 0 (don't know).
1531 (defun behavior (exp var val)
1532 ;; $inf/$minf is handled by substituting 1/var for var
1533 ;; and setting val to $zeroa/$zerob.
1534 (cond ((real-infinityp val)
1535 (setq val (cond
1536 ((eq val '$inf) '$zeroa)
1537 ((eq val '$minf) '$zerob))
1538 exp (sratsimp (subin (m^ var -1) exp)))))
1539 (cond
1540 ((not (member val '($zeroa $zerob $inf $minf)))
1542 ;; Shortcut for constants.
1543 ((freeof var exp)
1545 ;; Shortcut for the variable itself.
1546 ((eq exp var)
1547 (if (member val '($zeroa $minf) :test #'eq) 1 -1))
1548 ;; This limits the recursion depth of the function.
1549 ;; Before giving up, always try behavior-by-diff, which doesn't recurse.
1550 ((= *behavior-count-now* +behavior-count+)
1551 (behavior-by-diff exp var val))
1553 (let ((*behavior-count-now* (1+ *behavior-count-now*)) pair sign ans)
1554 (cond
1555 ;; Pull out constant factors with known signs from a product:
1556 ;; behavior(c * f(x)) = signum(c) * behavior(f(x))
1557 ((and (mtimesp exp)
1558 (prog2 (setq pair (partition exp var 1))
1559 (not (equal (car pair) 1))))
1560 (setq sign (getsignl (car pair)))
1561 (if (not (fixnump sign))
1563 (mul sign (behavior (cdr pair) var val))))
1564 ;; Pull out constant terms from a sum:
1565 ;; behavior(c + f(x)) = behavior(f(x))
1566 ((and (mplusp exp)
1567 (prog2 (setq pair (partition exp var 0))
1568 (not (equal (car pair) 0))))
1569 (behavior (cdr pair) var val))
1570 ;; Handle f(x)^c for the case f(0) = 0 and c > 0
1571 ;; (probably other cases could be handled, too)
1572 ((and (mexptp exp)
1573 (free (caddr exp) var)
1574 (=0 (no-err-sub 0 exp))
1575 (equal (getsignl (caddr exp)) 1)
1576 (not (equal 0 (setq ans (behavior-expt (cadr exp) (caddr exp))))))
1577 ans)
1578 ;; Handle 1 / f(x):
1579 ;; behavior(1 / f(x)) = -behavior(f(x))
1580 ((equal ($num exp) 1)
1581 (- (behavior ($denom exp) var val)))
1582 ;; Handle c^f(x) for c > 1:
1583 ;; behavior(c^f(x)) = behavior(f(x))
1584 ((and (mexptp exp)
1585 (free (cadr exp) var)
1586 (equal 1 (getsignl (m- (cadr exp) 1)))
1587 (not (equal 0 (setq ans (behavior (caddr exp) var val)))))
1588 ans)
1589 ;; Handle c^f(x) for 0 < c < 1:
1590 ;; behavior(c^f(x)) = -behavior(f(x))
1591 ((and (mexptp exp)
1592 (free (cadr exp) var)
1593 (equal 1 (getsignl (cadr exp)))
1594 (equal -1 (getsignl (m- (cadr exp) 1)))
1595 (not (equal 0 (setq ans (behavior (caddr exp) var val)))))
1596 (- ans))
1597 ;; atan, erf, sinh and tanh are monotonically increasing,
1598 ;; so their behavior is equal to the behavior of their arguments.
1599 ;; behavior(monotonically_increasing(f(x))) = behavior(f(x))
1600 ((member (caar exp) '(%atan %erf %sinh %tanh) :test #'eq)
1601 (behavior (cadr exp) var val))
1602 ;; Similarly, acot is monotonically decreasing left and right of x = 0.
1603 ;; The singularity doesn't matter for our purposes.
1604 ;; behavior(monotonically_decreasing(f(x))) = -behavior(f(x))
1605 ((eq (caar exp) '%acot)
1606 (- (behavior (cadr exp) var val)))
1607 ;; Note: More functions could be added here.
1608 ;; Ideally, use properties defined on the functions.
1609 ;; Handle log(f(x)) for f(0) = 0:
1610 ;; If behavior(f(x)) = 1, then behavior(log(f(x))) = 1
1611 ((and (mlogp exp)
1612 (=0 (no-err-sub 0 (cadr exp)))
1613 (equal 1 (behavior (cadr exp) var val)))
1615 ;; Try to determine the behavior by taking the derivative.
1616 ((not (equal 0 (setq ans (behavior-by-diff exp var val))))
1617 ans)
1618 ;; If exp is a sum and all terms have the same behavior, return that.
1619 ;; The sum of increasing functions is increasing.
1620 ;; The sum of decreasing functions is decreasing.
1621 ((and (mplusp exp)
1622 (not (equal 0 (setq ans (behavior-all-same exp var val)))))
1623 ans)
1624 (t 0))))))
1626 (defun behavior-all-same (exp var val)
1627 (let* ((exps (cdr exp)) (first-behavior (behavior (first exps) var val)))
1628 (if (or (equal first-behavior 0)
1629 (not (every #'(lambda (exp) (equal (behavior exp var val) first-behavior))
1630 (rest exps))))
1632 first-behavior)))
1634 (defun behavior-expt (bas expo)
1635 (let ((behavior (behavior bas var val)))
1636 (cond ((= behavior 1) 1)
1637 ((= behavior 0) 0)
1638 ((eq (ask-integer expo '$integer) '$yes)
1639 (cond ((eq (ask-integer expo '$even) '$yes) 1)
1640 (t behavior)))
1641 ((ratnump expo)
1642 (cond ((evenp (cadr expo)) 1)
1643 ((oddp (caddr expo)) behavior)
1644 (t 0)))
1645 (t 0))))
1647 (defun behavior-by-diff (exp var val)
1648 (do ((ct 0 (1+ ct))
1649 (exp (sratsimp (sdiff exp var)) (sratsimp (sdiff exp var)))
1650 (n () (not n))
1651 (ans ())) ; This do wins by a return.
1652 ((> ct 1) 0) ; This loop used to run up to 5 times,
1653 ;; but the size of some expressions would blow up.
1654 (setq ans (no-err-sub 0 exp)) ;Why not do an EVENFN and ODDFN
1655 ;test here.
1656 (cond ((eq ans t)
1657 (return 0))
1658 ((=0 ans) ()) ;Do it again.
1659 (t (setq ans (getsignl ans))
1660 (cond (n (return ans))
1661 ((equal ans 1)
1662 (return (if (eq val '$zeroa) 1 -1)))
1663 ((equal ans -1)
1664 (return (if (eq val '$zeroa) -1 1)))
1665 (t (return 0)))))))
1667 (defun try-lhospital (n d ind)
1668 ;;Make one catch for the whole bunch of lhospital trials.
1669 (let ((ans (lhospital-catch n d ind)))
1670 (cond ((null ans) ())
1671 ((not (free-infp ans)) (simpinf ans))
1672 ((not (free-epsilonp ans)) (simpab ans))
1673 (t ans))))
1675 (defun try-lhospital-quit (n d ind)
1676 (let ((ans (or (lhospital-catch n d ind)
1677 (lhospital-catch (m^ d -1) (m^ n -1) ind))))
1678 (cond ((null ans) (throw 'limit t))
1679 ((not (free-infp ans)) (simpinf ans))
1680 ((not (free-epsilonp ans)) (simpab ans))
1681 (t ans))))
1683 (defun lhospital-catch (n d ind)
1684 (cond ((> 0 lhcount)
1685 (setq lhcount $lhospitallim)
1686 (throw 'lhospital nil))
1687 ((equal lhcount $lhospitallim)
1688 (let ((lhcount (m+ lhcount -1)))
1689 (catch 'lhospital (lhospital n d ind))))
1690 (t (setq lhcount (m+ lhcount -1))
1691 (prog1 (lhospital n d ind)
1692 (setq lhcount (m+ lhcount 1))))))
1693 ;;If this succeeds then raise LHCOUNT.
1696 (defun lhospital (n d ind)
1697 (declare (special val lhp?))
1698 (when (mtimesp n)
1699 (setq n (m*l (mapcar #'(lambda (term) (lhsimp term var val)) (cdr n)))))
1700 (when (mtimesp d)
1701 (setq d (m*l (mapcar #'(lambda (term) (lhsimp term var val)) (cdr d)))))
1702 (multiple-value-bind (n d)
1703 (lhop-numden n d)
1704 (let (const nconst dconst)
1705 (setq lhp? (and (null ind) (cons n d)))
1706 (multiple-value-setq (nconst n) (var-or-const n))
1707 (multiple-value-setq (dconst d) (var-or-const d))
1709 (setq n (stirling0 n)) ;; replace factorial and %gamma
1710 (setq d (stirling0 d)) ;; with approximations
1712 (setq n (sdiff n var) ;; take derivatives for l'hospital
1713 d (sdiff d var))
1715 (if (or (not (free n '%derivative)) (not (free d '%derivative)))
1716 (throw 'lhospital ()))
1717 (let (($trigexpandtimes nil)) ;see #895 limit x->inf sin(100/x)*x very slow
1718 (setq n (expand-trigs (tansc n) var))
1719 (setq d (expand-trigs (tansc d) var)))
1721 (multiple-value-setq (const n d) (remove-singularities n d))
1722 (setq const (m* const (m// nconst dconst)))
1723 (simpinf (let ((ans (if ind
1724 (limit2 n d var val)
1725 (limit-numden n d val))))
1726 ;; When the limit function returns, it's possible that it will return NIL
1727 ;; (gave up without finding a limit). It's also possible that it will
1728 ;; return something containing UND. We treat that as a failure too.
1729 (when (and ans (freeof '$und ans))
1730 (sratsimp (m* const ans))))))))
1732 ;; Try to compute the limit of a quotient NUM/DEN, trying to massage the input
1733 ;; into a convenient form for LIMIT on the way.
1734 (defun limit-numden (n d val)
1735 (let ((expr (cond
1736 ;; For general arguments, the best approach seems to be to use
1737 ;; sratsimp to simplify the quotient as much as we can, then
1738 ;; $multthru, which splits it up into a sum (presumably useful
1739 ;; because limit(a+b) = limit(a) + limit(b) if the limits exist, and
1740 ;; the right hand side might be easier to calculate)
1741 ((not (mplusp n))
1742 ($multthru (sratsimp (m// n d))))
1744 ;; If we've already got a sum in the numerator, it seems to be
1745 ;; better not to recombine it. Call LIMIT on the whole lot, though,
1746 ;; because terms with infinite limits might cancel to give a finite
1747 ;; result.
1749 (m+l (mapcar #'(lambda (x)
1750 (sratsimp (m// x d)))
1751 (cdr n)))))))
1753 (limit expr var val 'think)))
1755 ;; Heuristics for picking the right way to express a LHOSPITAL problem.
1756 (defun lhop-numden (num denom)
1757 (declare (special var))
1758 (cond ((let ((log-num (involve num '(%log))))
1759 (cond ((null log-num) ())
1760 ((lessthan (num-of-logs (factor (sratsimp (sdiff (m^ num -1) var))))
1761 (num-of-logs (factor (sratsimp (sdiff num var)))))
1762 (psetq num (m^ denom -1) denom (m^ num -1))
1764 (t t))))
1765 ((let ((log-denom (involve denom '(%log))))
1766 (cond ((null log-denom) ())
1767 ((lessthan (num-of-logs (sratsimp (sdiff (m^ denom -1) var)))
1768 (num-of-logs (sratsimp (sdiff denom var))))
1769 (psetq denom (m^ num -1) num (m^ denom -1))
1771 (t t))))
1772 ((let ((exp-num (%einvolve num)))
1773 (cond (exp-num
1774 (cond ((%e-right-placep exp-num)
1776 (t (psetq num (m^ denom -1)
1777 denom (m^ num -1)) t)))
1778 (t ()))))
1779 ((let ((exp-den (%einvolve denom)))
1780 (cond (exp-den
1781 (cond ((%e-right-placep exp-den)
1783 (t (psetq num (m^ denom -1)
1784 denom (m^ num -1)) t)))
1785 (t ()))))
1786 ((let ((scnum (involve num '(%sin))))
1787 (cond (scnum (cond ((trig-right-placep '%sin scnum) t)
1788 (t (psetq num (m^ denom -1)
1789 denom (m^ num -1)) t)))
1790 (t ()))))
1791 ((let ((scden (involve denom '(%sin))))
1792 (cond (scden (cond ((trig-right-placep '%sin scden) t)
1793 (t (psetq num (m^ denom -1)
1794 denom (m^ num -1)) t)))
1795 (t ()))))
1796 ((let ((scnum (involve num '(%asin %acos %atan))))
1797 ;; If the numerator contains an inverse trig and the
1798 ;; denominator or reciprocal of denominator is polynomial,
1799 ;; leave everything as is. If the inverse trig is moved to
1800 ;; the denominator, things get messy, even if the numerator
1801 ;; becomes a polynomial. This is not perfect.
1802 (cond ((and scnum (or (polyinx denom var ())
1803 (polyinx (m^ denom -1) var ())))
1805 (t nil))))
1806 ((or (oscip num) (oscip denom)))
1807 ((frac num)
1808 (psetq num (m^ denom -1) denom (m^ num -1))))
1809 (values num denom))
1811 ;;i don't know what to do here for some cases, may have to be refined.
1812 (defun num-of-logs (exp)
1813 (cond ((mapatom exp) 0)
1814 ((equal (caar exp) '%log)
1815 (m+ 1 (num-of-log-l (cdr exp))))
1816 ((and (mexptp exp) (mnump (caddr exp)))
1817 (m* (simplify `((mabs) ,(caddr exp)))
1818 (num-of-logs (cadr exp))))
1819 (t (num-of-log-l (cdr exp)))))
1821 (defun num-of-log-l (llist)
1822 (do ((temp llist (cdr temp)) (ans 0))
1823 ((null temp) ans)
1824 (setq ans (m+ ans (num-of-logs (car temp))))))
1826 (defun %e-right-placep (%e-arg)
1827 (let ((%e-arg-diff (sdiff %e-arg var)))
1828 (cond
1829 ((free %e-arg-diff var)) ;simple cases
1830 ((or (and (mexptp denom)
1831 (equal (cadr denom) -1))
1832 (polyinx (m^ denom -1) var ())) ())
1833 ((let ((%e-arg-diff-lim (ridofab (limit %e-arg-diff var val 'think)))
1834 (%e-arg-exp-lim (ridofab (limit (m^ '$%e %e-arg) var val 'think))))
1835 #+nil
1836 (progn
1837 (format t "%e-arg-dif-lim = ~A~%" %e-arg-diff-lim)
1838 (format t "%e-arg-exp-lim = ~A~%" %e-arg-exp-lim))
1839 (cond ((equal %e-arg-diff-lim %e-arg-exp-lim)
1841 ((and (mnump %e-arg-diff-lim) (mnump %e-arg-exp-lim))
1843 ((and (mnump %e-arg-diff-lim) (infinityp %e-arg-exp-lim))
1844 ;; This is meant to make maxima handle bug 1469411
1845 ;; correctly. Undoubtedly, this needs work.
1847 (t ())))))))
1849 (defun trig-right-placep (trig-type arg)
1850 (let ((arglim (ridofab (limit arg var val 'think)))
1851 (triglim (ridofab (limit `((,trig-type) ,arg) var val 'think))))
1852 (cond ((and (equal arglim 0) (equal triglim 0)) t)
1853 ((and (infinityp arglim) (infinityp triglim)) t)
1854 (t ()))))
1856 ;;Takes a numerator and a denominator. If they tries all combinations of
1857 ;;products to try and make a simpler set of subproblems for LHOSPITAL.
1858 (defun remove-singularities (numer denom)
1859 (cond ((or (null numer) (null denom)
1860 (atom numer) (atom denom)
1861 (not (mtimesp numer)) ;Leave this here for a while.
1862 (not (mtimesp denom)))
1863 (values 1 numer denom))
1865 (let ((const 1))
1866 (multiple-value-bind (num-consts num-vars)
1867 (var-or-const numer)
1868 (multiple-value-bind (denom-consts denom-vars)
1869 (var-or-const denom)
1870 (if (not (mtimesp num-vars))
1871 (setq num-vars (list num-vars))
1872 (setq num-vars (cdr num-vars)))
1873 (if (not (mtimesp denom-vars))
1874 (setq denom-vars (list denom-vars))
1875 (setq denom-vars (cdr denom-vars)))
1876 (do ((nl num-vars (cdr nl))
1877 (num-list (copy-list num-vars ))
1878 (den-list denom-vars den-list-temp)
1879 (den-list-temp (copy-list denom-vars)))
1880 ((null nl) (values (m* const (m// num-consts denom-consts))
1881 (m*l num-list)
1882 (m*l den-list-temp)))
1883 (do ((dl den-list (cdr dl)))
1884 ((null dl) t)
1885 (if (or (%einvolve (car nl)) (%einvolve (car nl)))
1887 (let ((lim (catch 'limit (simpinf (simpab (limit (m// (car nl) (car dl))
1888 var val 'think))))))
1889 (cond ((or (eq lim t)
1890 (eq lim ())
1891 (equal (ridofab lim) 0)
1892 (infinityp lim)
1893 (not (free lim '$inf))
1894 (not (free lim '$minf))
1895 (not (free lim '$infinity))
1896 (not (free lim '$ind))
1897 (not (free lim '$und)))
1900 (setq const (m* lim const))
1901 (setq num-list (delete (car nl) num-list :count 1 :test #'equal))
1902 (setq den-list-temp (delete (car dl) den-list-temp :count 1 :test #'equal))
1903 (return t)))))))))))))
1905 ;; separate terms that contain var from constant terms
1906 ;; returns (const-terms . var-terms)
1907 (defun var-or-const (expr)
1908 (setq expr ($factor expr))
1909 (cond ((atom expr)
1910 (if (eq expr var)
1911 (values 1 expr)
1912 (values expr 1)))
1913 ((free expr var)
1914 (values expr 1))
1915 ((mtimesp expr)
1916 (do ((l (cdr expr) (cdr l))
1917 (const 1)
1918 (varl 1))
1919 ((null l) (values const varl))
1920 (if (free (car l) var)
1921 (setq const (m* (car l) const))
1922 (setq varl (m* (car l) varl)))))
1924 (values 1 expr))))
1926 ;; if term goes to non-zero constant, replace with constant
1927 (defun lhsimp (term var val)
1928 (cond (($mapatom term) term)
1930 (let ((term-value (ridofab (limit term var val 'think))))
1931 (if (and (not (member term-value '($inf $minf $und $ind $infinity)))
1932 (eq t (mnqp term-value 0))) term-value term)))))
1934 (defun bylog (expo bas)
1935 (simplimexpt '$%e
1936 (setq bas
1937 (try-lhospital-quit (simplify `((%log) ,(tansc bas)))
1938 (m^ expo -1)
1939 nil))
1940 '$%e bas))
1942 (defun simplimexpt (bas expo bl el)
1943 (cond ((or (eq bl '$und) (eq el '$und)) '$und)
1944 ((zerop2 bl)
1945 (cond ((eq el '$inf) (if (eq bl '$zeroa) bl 0))
1946 ((eq el '$minf) (if (eq bl '$zeroa) '$inf '$infinity))
1947 ((eq el '$ind) '$ind)
1948 ((eq el '$infinity) '$und)
1949 ((zerop2 el) (bylog expo bas))
1950 (t (cond ((equal (getsignl el) -1)
1951 (cond ((eq bl '$zeroa) '$inf)
1952 ((eq bl '$zerob)
1953 (cond ((even1 el) '$inf)
1954 ((eq (ask-integer el '$integer) '$yes)
1955 (if (eq (ask-integer el '$even) '$yes)
1956 '$inf
1957 '$minf)))) ;Gotta be ODD.
1958 (t (setq bas (behavior bas var val))
1959 (cond ((equal bas 1) '$inf)
1960 ((equal bas -1) '$minf)
1961 (t (throw 'limit t))))))
1962 ((and (mnump el)
1963 (member bl '($zeroa $zerob) :test #'eq))
1964 (cond ((even1 el) '$zeroa)
1965 ((and (eq bl '$zerob)
1966 (ratnump el)
1967 (evenp (caddr el))) 0)
1968 (t bl)))
1969 ((equal (getsignl el) 1)
1970 (if (eq bl '$zeroa) bl 0))
1971 ((equal (getsignl el) 0)
1973 (t (throw 'limit t))))))
1974 ((eq bl '$infinity)
1975 (cond ((zerop2 el) (bylog expo bas))
1976 ((eq el '$minf) 0)
1977 ((eq el '$inf) '$infinity)
1978 ((member el '($infinity $ind) :test #'eq) '$und)
1979 ((equal (setq el (getsignl el)) 1) '$infinity)
1980 ((equal el 0) 1)
1981 ((equal el -1) 0)
1982 (t (throw 'limit t))))
1983 ((eq bl '$inf)
1984 (cond ((eq el '$inf) '$inf)
1985 ((equal el '$minf) 0)
1986 ((zerop2 el) (bylog expo bas))
1987 ((member el '($infinity $ind) :test #'eq) '$und)
1988 (t (cond ((eql 0 (getsignl el)) 1)
1989 ((ratgreaterp 0 el) '$zeroa)
1990 ((ratgreaterp el 0) '$inf)
1991 (t (throw 'limit t))))))
1992 ((eq bl '$minf)
1993 (cond ((zerop2 el) (bylog expo bas))
1994 ((eq el '$inf) '$und)
1995 ((equal el '$minf) 0)
1996 ;;;Why not generalize this. We can ask about the number. -Jim 2/23/81
1997 ((mnump el) (cond ((mnegp el)
1998 (if (even1 el)
1999 '$zeroa
2000 (if (eq (ask-integer el '$integer) '$yes)
2001 (if (eq (ask-integer el '$even) '$yes)
2002 '$zeroa
2003 '$zerob)
2004 0)))
2005 (t (cond ((even1 el) '$inf)
2006 ((eq (ask-integer el '$integer) '$yes)
2007 (if (eq (ask-integer el '$even) '$yes)
2008 '$inf
2009 '$minf))
2010 (t '$infinity)))))
2011 (loginprod? (throw 'lip? 'lip!))
2012 (t '$und)))
2013 ((equal (simplify (ratdisrep (ridofab bl))) 1)
2014 (if (infinityp el) (bylog expo bas) 1))
2015 ((and (equal (ridofab bl) -1)
2016 (infinityp el)) '$ind) ;LB
2017 ((eq bl '$ind) (cond ((or (zerop2 el) (infinityp el)) '$und)
2018 ((not (equal (getsignl el) -1)) '$ind)
2019 (t '$und)))
2020 ((eq el '$inf) (cond ((abeq1 bl)
2021 (if (equal (getsignl bl) 1) 1 '$ind))
2022 ((abless1 bl)
2023 (if (equal (getsignl bl) 1) '$zeroa 0))
2024 ((equal (getsignl (m1- bl)) 1) '$inf)
2025 ((equal (getsignl (m1- `((mabs) ,bl))) 1) '$infinity)
2026 (t (throw 'limit t))))
2027 ((eq el '$minf) (cond ((abeq1 bl)
2028 (if (equal (getsignl bl) 1) 1 '$ind))
2029 ((not (abless1 bl))
2030 (if (equal (getsignl bl) 1) '$zeroa 0))
2031 ((ratgreaterp 0 bl) '$infinity)
2032 (t '$inf)))
2033 ((eq el '$infinity)
2034 (if (equal val '$infinity)
2035 '$und ;Not enough info to do anything.
2036 (destructuring-bind (real-el . imag-el)
2037 (trisplit expo)
2038 (setq real-el (limit real-el var origval nil))
2039 (cond ((eq real-el '$minf)
2041 ((and (eq real-el '$inf)
2042 (not (equal (ridofab (limit imag-el var origval nil)) 0)))
2043 '$infinity)
2044 ((eq real-el '$infinity)
2045 (throw 'limit t)) ;; don't really know real component
2047 '$ind)))))
2049 ((eq el '$ind) '$ind)
2050 ((zerop2 el) 1)
2051 ((zerop2 el) 1)
2052 ;; When bl is off the negative real axis, use direct substitution
2053 ((off-negative-real-axisp bl) (ftake 'mexpt bl el))
2055 ;; We're looking at (neg + {zerob, 0 zeroa} %i)^el. We need to
2056 ;; do a rectform on bas and decide if the imaginary part is
2057 ;; zerob, 0, or zeroa.
2058 (let ((x) (y) (xlim) (ylim) (preserve-direction t))
2059 (setq bas (risplit bas))
2060 (setq x (car bas)
2061 y (cdr bas))
2062 (setq xlim (limit x var val 'think))
2063 (setq ylim (limit y var val 'think))
2064 (cond ((eql 0 y) (ftake 'mexpt bl el))
2065 ((eq ylim '$zeroa)
2066 (mul (ftake 'mexpt (mul -1 xlim) el)
2067 (ftake 'mexpt '$%e (mul '$%i '$%pi el))))
2068 ((eq ylim '$zerob)
2069 (mul (ftake 'mexpt (mul -1 xlim) el)
2070 (ftake 'mexpt '$%e (mul -1 '$%i '$%pi el))))
2071 (t (throw 'limit nil)))))))
2073 (defun even1 (x)
2074 (cond ((numberp x) (and (integerp x) (evenp x)))
2075 ((and (mnump x) (evenp (cadr x))))))
2077 ;; is absolute value less than one?
2078 (defun abless1 (bl)
2079 (setq bl (nmr bl))
2080 (cond ((mnump bl)
2081 (and (ratgreaterp 1. bl) (ratgreaterp bl -1.)))
2082 (t (equal (getsignl (m1- `((mabs) ,bl))) -1.))))
2084 ;; is absolute value equal to one?
2085 (defun abeq1 (bl)
2086 (setq bl (nmr bl))
2087 (cond ((mnump bl)
2088 (or (equal 1. bl) (equal bl -1.)))
2089 (t (equal (getsignl (m1- `((mabs) ,bl))) 0))))
2091 (defun simplimit (exp var val &aux op)
2092 (cond
2093 ((eq var exp) val)
2094 ((or (atom exp) (mnump exp)) exp)
2095 ;; Lookup and dispatch a simplim%function from the property list
2096 ((setq op (safe-get (mop exp) 'simplim%function))
2097 (funcall op exp var val))
2099 ;; And do the same for subscripted:
2100 ((and (consp exp) (consp (car exp)) (eq (caar exp) 'mqapply)
2101 (setq op (safe-get (subfunname exp) 'simplim%function)))
2102 (funcall op exp var val))
2104 ;; Without the call to rootscontract,
2105 ;; limit(((-4)*x^2-10*x+24)/((4*x+8)^(1/3)+2),x,-4)
2106 ;; returns zero (should be 66). This bug is due to the fact that
2107 ;; 4^(1/3)*2^(1/3)-2 does not simplify to zero. Although the call
2108 ;; to rootscontract takes care of this case, almost surely there are
2109 ;; many other limit problems that need more than rootscontract.
2110 ((mplusp exp) (let (($rootsconmode nil)) ($rootscontract (simplimplus exp))))
2111 ((mtimesp exp) (simplimtimes (cdr exp)))
2112 ((mexptp exp) (simplimexpt (cadr exp) (caddr exp)
2113 (limit (cadr exp) var val 'think)
2114 (limit (caddr exp) var val 'think)))
2115 ((member (caar exp) '(%sin %cos) :test #'eq)
2116 (simplimsc exp (caar exp) (limit (cadr exp) var val 'think)))
2117 ((eq (caar exp) '%tan) (simplim%tan (cadr exp)))
2118 ((member (caar exp) '(%sinh %cosh) :test #'eq)
2119 (simplimsch (caar exp) (limit (cadr exp) var val 'think)))
2120 ((member (caar exp) '(%erf %tanh) :test #'eq)
2121 (simplim%erf-%tanh (caar exp) (cadr exp)))
2122 ((eq (caar exp) '%atanh)
2123 (simplim%atanh (limit (cadr exp) var val 'think) val))
2124 ((eq (caar exp) '%acosh)
2125 (simplim%acosh (limit (cadr exp) var val 'think)))
2126 ((eq (caar exp) '%asinh)
2127 (simplim%asinh (limit (cadr exp) var val 'think)))
2128 ((eq (caar exp) '%inverse_jacobi_ns)
2129 (simplim%inverse_jacobi_ns (limit (cadr exp) var val 'think) (third exp)))
2130 ((eq (caar exp) '%inverse_jacobi_nc)
2131 (simplim%inverse_jacobi_nc (limit (cadr exp) var val 'think) (third exp)))
2132 ((eq (caar exp) '%inverse_jacobi_sc)
2133 (simplim%inverse_jacobi_sc (limit (cadr exp) var val 'think) (third exp)))
2134 ((eq (caar exp) '%inverse_jacobi_cs)
2135 (simplim%inverse_jacobi_cs (limit (cadr exp) var val 'think) (third exp)))
2136 ((eq (caar exp) '%inverse_jacobi_dc)
2137 (simplim%inverse_jacobi_dc (limit (cadr exp) var val 'think) (third exp)))
2138 ((eq (caar exp) '%inverse_jacobi_ds)
2139 (simplim%inverse_jacobi_ds (limit (cadr exp) var val 'think) (third exp)))
2140 ((and (eq (caar exp) 'mqapply)
2141 (eq (subfunname exp) '$psi))
2142 (simplim$psi (subfunsubs exp) (subfunargs exp) val))
2143 ((and (eq (caar exp) var)
2144 (member 'array (car exp) :test #'eq)
2145 (every #'(lambda (sub-exp)
2146 (free sub-exp var))
2147 (cdr exp)))
2148 exp) ;LIMIT(B[I],B,INF); -> B[I]
2149 ;; When limsubst is true, limit(f(n+1)/f(n),n,inf) = 1. The user documentation
2150 ;; warns against setting limsubst to true.
2151 (t (if $limsubst
2152 (simplify (cons (operator-with-array-flag exp)
2153 (mapcar #'(lambda (a)
2154 (limit a var val 'think))
2155 (cdr exp))))
2156 (throw 'limit t)))))
2158 (defun liminv (e)
2159 (setq e (resimplify (subst (m// 1 var) var e)))
2160 (let ((new-val (cond ((eq val '$zeroa) '$inf)
2161 ((eq val '$zerob) '$minf))))
2162 (if new-val (let ((preserve-direction t))
2163 (toplevel-$limit e var new-val)) (throw 'limit t))))
2165 (defun simplimtimes (exp)
2166 ;; The following test
2167 ;; handles (-1)^x * 2^x => (-2)^x => $infinity
2168 ;; wants to avoid (-1)^x * 2^x => $ind * $inf => $und
2169 (let ((try
2170 (and (expfactorp (cons '(mtimes) exp) 1)
2171 (expfactor (cons '(mtimes) exp) 1 var))))
2172 (when try (return-from simplimtimes try)))
2174 (let ((prod 1) (num 1) (denom 1)
2175 (zf nil) (ind-flag nil) (inf-type nil)
2176 (constant-zero nil) (constant-infty nil))
2177 (dolist (term exp)
2178 (let* ((loginprod? (involve term '(%log)))
2179 (y (catch 'lip? (limit term var val 'think))))
2180 (cond
2181 ;; limit failed due to log in product
2182 ((eq y 'lip!)
2183 (return-from simplimtimes (liminv (cons '(mtimes simp) exp))))
2185 ;; If the limit is infinitesimal or zero
2186 ((zerop2 y)
2187 (setf num (m* num term)
2188 constant-zero (or constant-zero (not (among var term))))
2189 (case y
2190 ($zeroa
2191 (unless zf (setf zf 1)))
2192 ($zerob
2193 (setf zf (* -1 (or zf 1))))))
2195 ;; If the limit is not some form of infinity or
2196 ;; undefined/indeterminate.
2197 ((not (member y '($inf $minf $infinity $ind $und) :test #'eq))
2198 (setq prod (m* prod y)))
2200 ((eq y '$und) (return-from simplimtimes '$und))
2201 ((eq y '$ind) (setq ind-flag t))
2203 ;; Some form of infinity
2205 (setf denom (m* denom term)
2206 constant-infty (or constant-infty (not (among var term))))
2207 (unless (eq inf-type '$infinity)
2208 (cond
2209 ((eq y '$infinity) (setq inf-type '$infinity))
2210 ((null inf-type) (setf inf-type y))
2211 ;; minf * minf or inf * inf
2212 ((eq y inf-type) (setf inf-type '$inf))
2213 ;; minf * inf
2214 (t (setf inf-type '$minf))))))))
2216 (cond
2217 ;; If there are zeros and infinities among the terms that are free of
2218 ;; VAR, then we have an expression like "inf * zeroa * f(x)" or
2219 ;; similar. That gives an undefined result. Note that we don't
2220 ;; necessarily have something undefined if only the zeros have a term
2221 ;; free of VAR. For example "zeroa * exp(-1/x) * 1/x" as x -> 0. And
2222 ;; similarly for the infinities.
2223 ((and constant-zero constant-infty) '$und)
2225 ;; If num=denom=1, we didn't find any explicit infinities or zeros, so we
2226 ;; either return the simplified product or ind
2227 ((and (eql num 1) (eql denom 1))
2228 (if ind-flag '$ind prod))
2229 ;; If denom=1 (and so num != 1), we have some form of zero
2230 ((equal denom 1)
2231 (if (null zf)
2233 (let ((sign (getsignl prod)))
2234 (if (or (not sign) (eq sign 'complex))
2236 (ecase (* zf sign)
2237 (0 0)
2238 (1 '$zeroa)
2239 (-1 '$zerob))))))
2240 ;; If num=1 (and so denom != 1), we have some form of infinity
2241 ((equal num 1)
2242 (let ((sign ($csign prod)))
2243 (cond
2244 (ind-flag '$und)
2245 ((eq sign '$pos) inf-type)
2246 ((eq sign '$neg) (case inf-type
2247 ($inf '$minf)
2248 ($minf '$inf)
2249 (t '$infinity)))
2250 ((member sign '($complex $imaginary)) '$infinity)
2251 ; sign is '$zero, $pnz, $pz, etc
2252 (t (throw 'limit t)))))
2253 ;; Both zeros and infinities
2255 ;; All bets off if there are some infinities or some zeros, but it
2256 ;; needn't be undefined (see above)
2257 (when (or constant-zero constant-infty) (throw 'limit t))
2259 (let ((ans (limit2 num (m^ denom -1) var val)))
2260 (if ans
2261 (simplimtimes (list prod ans))
2262 (throw 'limit t)))))))
2264 ;;;PUT CODE HERE TO ELIMINATE FAKE SINGULARITIES??
2266 ;; At one time when simplimplus1 failed to find a limit, this function
2267 ;; applied ratsimp and tried again. This scheme didn't fix any testsuite
2268 ;; bugs and it slowed the code, so I removed it (Barton Willis, July 2023).
2269 (defun simplimplus (exp)
2270 (cond ((memalike exp simplimplus-problems) (throw 'limit t))
2271 (t (unwind-protect
2272 (progn (push exp simplimplus-problems)
2273 (let ((ans (catch 'limit (simplimplus1 exp))))
2274 (if (or (eq ans nil) (eq ans t) (among '%limit ans))
2275 (throw 'limit t) (resimp-extra-simp ans))))
2276 (pop simplimplus-problems)))))
2278 (defun simplimplus1 (exp)
2279 (prog (sum y infl infinityl minfl indl undl zerobl zeroal ans r)
2280 (do ((exp (cdr exp) (cdr exp)) (f))
2281 ((null exp) nil)
2282 (setq f (limit (car exp) var val 'think))
2283 (cond ((null f) (throw 'limit t))
2284 ((eq f '$und) (push (car exp) undl))
2285 ((eq f '$zerob) (push (car exp) zerobl))
2286 ((eq f '$zeroa) (push (car exp) zeroal))
2287 ((eq f '$ind) (push (car exp) indl))
2288 ((eq f '$inf) (push (car exp) infl))
2289 ((eq f '$minf) (push (car exp) minfl))
2290 ((eq f '$infinity) (push (car exp) infinityl))
2291 (t (push f sum))))
2293 ;; When there are two or more infinity terms, we dispatch gruntz1 on
2294 ;; the rectangular form of their sum. When gruntz1 is able to find the
2295 ;; limit, we modify the lists infinityl, minfl, ... accordingly.
2296 (when (and infinityl (cdr infinityl) (not (among '$li (cons '(mlist) infinityl))))
2297 (setq ans (risplit (fapply 'mplus infinityl)))
2299 (let ((re (car ans)) (im (cdr ans)))
2300 (setq re (car (errcatch (gruntz1 re var val))))
2301 (setq im (car (errcatch (gruntz1 im var val))))
2302 (setq r
2303 (cond ((or (null re) (null im)) nil)
2304 ((infinityp im) '$infinity)
2305 ((infinityp re) re)
2306 (t (add re (mul '$%i im))))))
2307 (cond ((eq r '$infinity) (list (fapply 'mplus infinityl)))
2308 ((eq r nil) (throw 'limit t))
2310 (setq infinityl nil)
2311 (cond ((eq r '$zerob) (push ans zerobl))
2312 ((eq r '$zeroa) (push ans zeroal))
2313 ((eq r '$ind) (push ans indl))
2314 ((eq r '$und) (push ans undl))
2315 ((eq r '$minf) (push ans minfl))
2316 ((eq r '$inf) (push ans infl))
2317 (t (push r sum))))))
2319 ;; Unfortunately, this code does not handle the case of one or more
2320 ;; infinity terms and either a minf or inf term. So we throw an error.
2321 (when (and infinityl (or minfl infl))
2322 (throw 'limit t))
2324 ;; Blend the zerob, zeroa, and sum terms. When there are both zerob
2325 ;; and zeroa terms, ignore them. When preserve-direction is true and
2326 ;; there are zerob terms, push zerob into the sum terms. And do the same
2327 ;; for zeroa. After that, add the terms in the list sum.
2328 (when (and preserve-direction zerobl (null zeroal))
2329 (push '$zerob sum))
2330 (when (and preserve-direction zeroal (null zerobl))
2331 (push '$zeroa sum))
2333 ;; When indl has two or more members, we attempt to condense the
2334 ;; ind terms into a single term.
2335 (when (and indl (cdr indl))
2336 ;; Use factor to attempt to condense the ind terms
2337 ;; into a finite term. This is needed for cases such as
2338 ;; limit(cos(1/x)*sin(x)-sin(x),x,inf). When there is only
2339 ;; one ind term, set ans to ind.
2340 (setq ans ($factor (fapply 'mplus indl)))
2341 (setq r (if (mplusp ans) nil (limit ans var val 'think)))
2342 (cond ((eq r '$zerob)
2343 (push ans zerobl)
2344 (setq indl nil))
2345 ((eq r '$zeroa)
2346 (push ans zeroal)
2347 (setq indl nil))
2348 ((eq r '$ind) (setq indl (list ans)))
2349 ((eq r '$und)
2350 (setq indl nil)
2351 (push ans undl))
2352 ((or (eq r '$minf) (eq r '$inf) (eq r '$infinity))
2353 (throw 'limit t))
2354 ((eq r nil))
2355 (t (push r sum))))
2356 ;; Add the members of the list sum.
2357 (setq sum (fapply 'mplus sum))
2359 (cond (undl
2360 (if (or infl minfl indl infinityl)
2361 (setq infinityl (append undl infinityl)); x^2 + x*sin(x)
2362 (return '$und))) ; 1 + x*sin(x)
2363 ((not (or infl minfl indl infinityl))
2364 (return (cond ((atom sum) sum)
2365 ((or (not (free sum '$zeroa))
2366 (not (free sum '$zerob)))
2367 (simpab sum))
2368 (t sum))))
2369 (t (cond ((null infinityl)
2370 (cond (infl (cond ((null minfl) (return '$inf))
2371 (t (go oon))))
2372 (minfl (return '$minf))
2373 (indl (return '$ind))))
2374 (t (setq infl (append infl infinityl))))))
2376 oon (setq y (m+l (append minfl infl)))
2377 (cond ((alike1 exp (setq y (sratsimp (hyperex y))))
2378 (cond ((not (infinityp val))
2379 (setq infl (cnv infl val)) ;THIS IS HORRIBLE!!!!
2380 (setq minfl (cnv minfl val))))
2381 (let ((val '$inf))
2382 (cond ((every #'(lambda (j) (radicalp j var))
2383 (append infl minfl))
2384 (setq y (rheur infl minfl)))
2385 (t (setq y (sheur infl minfl))))))
2386 (t (setq y (limit y var val 'think))))
2387 (cond ((or (eq y ())
2388 (eq y t)) (return ()))
2389 ((infinityp y) (return y))
2390 (indl (return '$ind))
2391 (t (return (m+ sum y))))))
2393 ;; Limit n/d, using heuristics on the order of growth.
2394 (defun sheur0 (n d)
2395 (let ((orig-n n))
2396 (cond ((and (free n var)
2397 (free d var))
2398 (m// n d))
2399 (t (setq n (cpa n d nil))
2400 (cond ((equal n 1)
2401 (cond ((oscip orig-n) '$und)
2402 (t '$inf)))
2403 ((equal n -1) '$zeroa)
2404 ((equal n 0) (m// orig-n d)))))))
2407 ;;;L1 is a list of INF's and L2 is a list of MINF's. Added together
2408 ;;;it is indeterminate.
2409 (defun sheur (l1 l2)
2410 (let ((term (sheur1 l1 l2)))
2411 (cond ((equal term '$inf) '$inf)
2412 ((equal term '$minf) '$minf)
2413 (t (let ((new-num (m+l (mapcar #'(lambda (num-term)
2414 (m// num-term (car l1)))
2415 (append l1 l2)))))
2416 (cond ((limit2 new-num (m// 1 (car l1)) var val))))))))
2418 (defun frac (exp)
2419 (cond ((atom exp) nil)
2420 (t (setq exp (nformat exp))
2421 (cond ((and (eq (caar exp) 'mquotient)
2422 (among var (caddr exp)))
2423 t)))))
2425 (defun zerop2 (z) (=0 (ridofab z)))
2427 (defun raise (a) (m+ a '$zeroa))
2429 (defun lower (a) (m+ a '$zerob))
2431 (defun sincoshk (exp1 l sc)
2432 (cond ((equal l 1) (lower l))
2433 ((equal l -1) (raise l))
2434 ((among sc l) l)
2435 ((member val '($zeroa $zerob) :test #'eq) (spangside exp1 l))
2436 (t l)))
2438 (defun spangside (e l)
2439 (setq e (behavior e var val))
2440 (cond ((equal e 1) (raise l))
2441 ((equal e -1) (lower l))
2442 (t l)))
2444 ;; get rid of zeroa and zerob
2445 (defun ridofab (e)
2446 (if (among '$zeroa e) (setq e (maxima-substitute 0 '$zeroa e)))
2447 (if (among '$zerob e) (setq e (maxima-substitute 0 '$zerob e)))
2450 ;; simple radical
2451 ;; returns true if exp is a polynomial raised to a numeric power
2452 (defun simplerd (exp)
2453 (and (mexptp exp)
2454 (mnump (caddr exp)) ;; exponent must be a number - no variables
2455 (polyp (cadr exp))))
2457 (defun branch1 (exp val)
2458 (cond ((polyp exp) nil)
2459 ((simplerd exp) (zerop2 (subin val (cadr exp))))
2461 (loop for v on (cdr exp)
2462 when (branch1 (car v) val)
2463 do (return v)))))
2465 (defun branch (exp val)
2466 (cond ((polyp exp) nil)
2467 ((or (simplerd exp) (mtimesp exp))
2468 (branch1 exp val))
2469 ((mplusp exp)
2470 (every #'(lambda (j) (branch j val)) (the list (cdr exp))))))
2472 (defun ser0 (e n d val)
2473 (cond ((and (branch n val) (branch d val))
2474 (setq nn* nil)
2475 (setq n (ser1 n))
2476 (setq d (ser1 d))
2477 ;;;NN* gets set by POFX, called by SER1, to get a list of exponents.
2478 (setq nn* (ratmin nn*))
2479 (setq n (sratsimp (m^ n (m^ var nn*))))
2480 (setq d (sratsimp (m^ d (m^ var nn*))))
2481 (cond ((member val '($zeroa $zerob) :test #'eq) nil)
2482 (t (setq val 0.)))
2483 (radlim e n d))
2484 (t (try-lhospital-quit n d nil))))
2486 (defun rheur (l1 l2)
2487 (prog (ans m1 m2)
2488 (setq m1 (mapcar (function asymredu) l1))
2489 (setq m2 (mapcar (function asymredu) l2))
2490 (setq ans (m+l (append m1 m2)))
2491 (cond ((rptrouble (m+l (append l1 l2)))
2492 (return (limit (simplify (rdsget (m+l (append l1 l2))))
2495 nil)))
2496 ((mplusp ans) (return (sheur m1 m2)))
2497 (t (return (limit ans var val t))))))
2499 (defun rptrouble (rp)
2500 (not (equal (rddeg rp nil) (rddeg (asymredu rp) nil))))
2502 (defun radicalp (exp var)
2503 (cond ((polyinx exp var ()))
2504 ((mexptp exp) (cond ((equal (caddr exp) -1.)
2505 (radicalp (cadr exp) var))
2506 ((simplerd exp))))
2507 ((member (caar exp) '(mplus mtimes) :test #'eq)
2508 (every #'(lambda (j) (radicalp j var))
2509 (cdr exp)))))
2511 (defun involve (e nn*)
2512 (declare (special var))
2513 (cond ((atom e) nil)
2514 ((mnump e) nil)
2515 ((and (member (caar e) nn* :test #'eq) (among var (cdr e))) (cadr e))
2516 (t (some #'(lambda (j) (involve j nn*)) (cdr e)))))
2518 ;; Just like INVOLVE, except the dependency on VAR is explicit (second
2519 ;; arg here). Use this instead.
2520 (defun involve-var (e var1 nn*)
2521 (cond ((atom e) nil)
2522 ((mnump e) nil)
2523 ((and (member (caar e) nn* :test #'eq)
2524 (among var1 (cdr e)))
2525 (cadr e))
2527 (some #'(lambda (j)
2528 (involve-var j var1 nn*))
2529 (cdr e)))))
2531 ;; Why not implement this as (NOT (INVOLVE EXP NN*))?
2532 (defun notinvolve (exp nn*)
2533 (cond ((atom exp) t)
2534 ((mnump exp) t)
2535 ((member (caar exp) nn* :test #'eq) (not (among var (cdr exp))))
2536 ((every #'(lambda (j) (notinvolve j nn*))
2537 (cdr exp)))))
2539 ;; Just like NOTINVOLVE, except the dependency on VAR is explicit
2540 ;; (second arg here). Use this instead.
2541 (Defun notinvolve-var (exp var1 nn*)
2542 (cond ((atom exp)
2544 ((mnump exp)
2546 ((member (caar exp) nn* :test #'eq)
2547 (not (among var1 (cdr exp))))
2548 ((every #'(lambda (j)
2549 (notinvolve-var j var1 nn*))
2550 (cdr exp)))))
2552 (defun sheur1 (l1 l2)
2553 (prog (ans)
2554 (setq l1 (mapcar #'stirling0 l1))
2555 (setq l2 (mapcar #'stirling0 l2))
2556 (setq l1 (m+l (maxi l1)))
2557 (setq l2 (m+l (maxi l2)))
2558 (setq ans (cpa l1 l2 t))
2559 (return (cond ((=0 ans) (m+ l1 l2))
2560 ((equal ans 1.) '$inf)
2561 (t '$minf)))))
2563 (defun zero-lim (cpa-list)
2564 (do ((l cpa-list (cdr l)))
2565 ((null l) ())
2566 (and (eq (caar l) 'gen)
2567 (zerop2 (limit (cadar l) var val 'think))
2568 (return t))))
2570 ;; Compare order of growth for R1 and R2. The result is 0, -1, +1
2571 ;; depending on the relative order of growth. 0 is returned if R1 and
2572 ;; R2 have the same growth; -1 if R1 grows much more slowly than R2;
2573 ;; +1 if R1 grows much more quickly than R2.
2574 (defun cpa (r1 r2 flag)
2575 (let ((t1 r1)
2576 (t2 r2))
2577 (cond ((alike1 t1 t2) 0.)
2578 ((free t1 var)
2579 (cond ((free t2 var) 0.)
2580 (t (let ((lim-ans (limit1 t2 var val)))
2581 (cond ((not (member lim-ans '($inf $minf $und $ind) :test #'eq)) 0.)
2582 (t -1.))))))
2583 ((free t2 var)
2584 (let ((lim-ans (limit1 t1 var val)))
2585 (cond ((not (member lim-ans '($inf $minf $und $ind) :test #'eq)) 0.)
2586 (t 1.))))
2588 ;; Make T1 and T2 be a list of terms that are multiplied
2589 ;; together.
2590 (cond ((mtimesp t1) (setq t1 (cdr t1)))
2591 (t (setq t1 (list t1))))
2592 (cond ((mtimesp t2) (setq t2 (cdr t2)))
2593 (t (setq t2 (list t2))))
2594 ;; Find the strengths of each term of T1 and T2
2595 (setq t1 (mapcar (function istrength) t1))
2596 (setq t2 (mapcar (function istrength) t2))
2597 ;; Compute the max of the strengths of the terms.
2598 (let ((ans (ismax t1))
2599 (d (ismax t2)))
2600 (cond ((or (null ans) (null d))
2601 ;;(eq (car ans) 'gen) (eq (car d) 'gen))
2602 ;; ismax couldn't find highest term; give up
2605 (if (eq (car ans) 'var) (setq ans (add-up-deg t1)))
2606 (if (eq (car d) 'var) (setq d (add-up-deg t2)))
2607 ;; Can't just just compare dominating terms if there are
2608 ;; indeterm-inates present; e.g. X-X^2*LOG(1+1/X). So
2609 ;; check for this.
2610 (cond ((or (zero-lim t1)
2611 (zero-lim t2))
2612 (cpa-indeterm ans d t1 t2 flag))
2613 ((isgreaterp ans d) 1.)
2614 ((isgreaterp d ans) -1.)
2615 (t 0)))))))))
2617 (defun cpa-indeterm (ans d t1 t2 flag)
2618 (cond ((not (eq (car ans) 'var))
2619 (setq ans (gather ans t1) d (gather d t2))))
2620 (let ((*indicator (and (eq (car ans) 'exp)
2621 flag))
2622 (test ()))
2623 (setq test (cpa1 ans d))
2624 (cond ((and (zerop1 test)
2625 (or (equal ($radcan (m// (cadr ans) (cadr d))) 1.)
2626 (and (polyp (cadr ans))
2627 (polyp (cadr d))
2628 (equal (limit (m// (cadr ans) (cadr d)) var val 'think)
2629 1.))))
2630 (let ((new-term1 (m// t1 (cadr ans)))
2631 (new-term2 (m// t2 (cadr d))))
2632 (cpa new-term1 new-term2 flag)))
2633 (t 0))))
2635 (defun add-up-deg (strengthl)
2636 (do ((stl strengthl (cdr stl))
2637 (poxl)
2638 (degl))
2639 ((null stl) (list 'var (m*l poxl) (m+l degl)))
2640 (cond ((eq (caar stl) 'var)
2641 (push (cadar stl) poxl)
2642 (push (caddar stl) degl)))))
2644 (defun cpa1 (p1 p2)
2645 (prog (flag s1 s2)
2646 (cond ((eq (car p1) 'gen) (return 0.)))
2647 (setq flag (car p1))
2648 (setq p1 (cadr p1))
2649 (setq p2 (cadr p2))
2650 (cond
2651 ((eq flag 'var)
2652 (setq s1 (istrength p1))
2653 (setq s2 (istrength p2))
2654 (return
2655 (cond
2656 ((isgreaterp s1 s2) 1.)
2657 ((isgreaterp s2 s1) -1.)
2658 (*indicator
2659 (setq *indicator nil)
2660 (cond
2661 ((and (poly? p1 var) (poly? p2 var))
2662 (setq p1 (m- p1 p2))
2663 (cond ((zerop1 p1) 0.)
2664 (t (getsignl (hot-coef p1)))))
2666 (setq s1
2667 (rheur (list p1)
2668 (list (m*t -1 p2))))
2669 (cond ((zerop2 s1) 0.)
2670 ((ratgreaterp s1 0.) 1.)
2671 (t -1.)))))
2672 (t 0.))))
2673 ((eq flag 'exp)
2674 (setq p1 (caddr p1))
2675 (setq p2 (caddr p2))
2676 (cond ((and (poly? p1 var) (poly? p2 var))
2677 (setq p1 (m- p1 p2))
2678 (return (cond ((or (zerop1 p1)
2679 (not (among var p1)))
2681 (t (getsignl (hot-coef p1))))))
2682 ((and (radicalp p1 var) (radicalp p2 var))
2683 (setq s1
2684 (rheur (list p1)
2685 (list (m*t -1 p2))))
2686 (return (cond ((eq s1 '$inf) 1.)
2687 ((eq s1 '$minf) -1.)
2688 ((mnump s1)
2689 (cond ((ratgreaterp s1 0.) 1.)
2690 ((ratgreaterp 0. s1) -1.)
2691 (t 0.)))
2692 (t 0.))))
2693 (t (return (cpa p1 p2 t)))))
2694 ((eq flag 'log)
2695 (setq p1 (try-lhospital (asymredu p1) (asymredu p2) nil))
2696 (return (cond ((zerop2 p1) -1.)
2697 ((real-infinityp p1) 1.)
2698 (t 0.)))))))
2700 ;;;EXPRESSIONS TO ISGREATERP ARE OF THE FOLLOWING FORMS
2701 ;;; ("VAR" POLY DEG)
2702 ;;; ("EXP" %E^EXP)
2703 ;;; ("LOG" LOG(EXP))
2704 ;;; ("FACT" <A FACTORIAL EXPRESSION>)
2705 ;;; ("GEN" <ANY OTHER TYPE OF EXPRESSION>)
2707 (defun isgreaterp (a b)
2708 (let ((ta (car a))
2709 (tb (car b)))
2710 (cond ((or (eq ta 'gen)
2711 (eq tb 'gen)) ())
2712 ((and (eq ta tb) (eq ta 'var))
2713 (ratgreaterp (caddr a) (caddr b)))
2714 ((and (eq ta tb) (eq ta 'exp))
2715 ;; Both are exponential order of infinity. Check the
2716 ;; exponents to determine which exponent is bigger.
2717 (eq (limit (m- `((%log) ,(second a)) `((%log) ,(second b)))
2718 var val 'think)
2719 '$inf))
2720 ((member ta (cdr (member tb '(num log var exp fact gen) :test #'eq)) :test #'eq)))))
2722 (defun ismax (l)
2723 ;; Preprocess the list of products. Separate the terms that
2724 ;; exponentials and those that don't. Actually multiply the
2725 ;; exponential terms together to form a single term. Pass this and
2726 ;; the rest to ismax-core to find the max.
2727 (let (exp-terms non-exp-terms)
2728 (dolist (term l)
2729 (if (eq 'exp (car term))
2730 (push term exp-terms)
2731 (push term non-exp-terms)))
2732 ;; Multiply the exp-terms together
2733 (if exp-terms
2734 (let ((product 1))
2735 ;;(format t "exp-terms = ~A~%" exp-terms)
2736 (dolist (term exp-terms)
2737 (setf product (simplify (mul product (second term)))))
2738 ;;(format t "product = ~A~%" product)
2739 (setf product `(exp ,($logcontract product)))
2740 ;;(format t "product = ~A~%" product)
2741 (ismax-core (cons product non-exp-terms)))
2742 (ismax-core l))))
2744 (defun ismax-core (l)
2745 (cond ((null l) ())
2746 ((atom l) ())
2747 ((= (length l) 1) (car l)) ;If there is only 1 thing give it back.
2748 ((every #'(lambda (x)
2749 (not (eq (car x) 'gen))) l)
2751 (do ((l1 (cdr l) (cdr l1))
2752 (temp-ans (car l))
2753 (ans ()))
2754 ((null l1) ans)
2755 (cond ((isgreaterp temp-ans (car l1))
2756 (setq ans temp-ans))
2757 ((isgreaterp (car l1) temp-ans)
2758 (setq temp-ans (car l1))
2759 (setq ans temp-ans))
2760 (t (setq ans ())))))
2761 (t ())))
2763 ;RETURNS LIST OF HIGH TERMS
2764 (defun maxi (all)
2765 (cond ((atom all) nil)
2766 (t (do ((l (cdr all) (cdr l))
2767 (hi-term (car all))
2768 (total 1) ; running total constant factor of hi-term
2769 (hi-terms (ncons (car all)))
2770 (compare nil))
2771 ((null l) (if (zerop2 total) ; if high-order terms cancel each other
2772 all ; keep everything
2773 hi-terms)) ; otherwise return list of high terms
2774 (setq compare (limit (m// (car l) hi-term) var val 'think))
2775 (cond
2776 ((or (infinityp compare)
2777 (and (eq compare '$und)
2778 (zerop2 (limit (m// hi-term (car l)) var val 'think))))
2779 (setq total 1) ; have found new high term
2780 (setq hi-terms (ncons (setq hi-term (car l)))))
2781 ((zerop2 compare) nil)
2782 ;; COMPARE IS IND, FINITE-VALUED, or und in both directions
2783 (t ; add to list of high terms
2784 (setq total (m+ total compare))
2785 (setq hi-terms (append hi-terms (ncons (car l))))))))))
2787 (defun ratmax (l)
2788 (prog (ans)
2789 (cond ((atom l) (return nil)))
2790 l1 (setq ans (car l))
2791 l2 (setq l (cdr l))
2792 (cond ((null l) (return ans))
2793 ((ratgreaterp ans (car l)) (go l2))
2794 (t (go l1)))))
2796 (defun ratmin (l)
2797 (prog (ans)
2798 (cond ((atom l) (return nil)))
2799 l1 (setq ans (car l))
2800 l2 (setq l (cdr l))
2801 (cond ((null l) (return ans))
2802 ((ratgreaterp (car l) ans) (go l2))
2803 (t (go l1)))))
2805 (defun pofx (e)
2806 (cond ((atom e)
2807 (cond ((eq e var)
2808 (push 1 nn*))
2809 (t ())))
2810 ((or (mnump e) (not (among var e))) nil)
2811 ((and (mexptp e) (eq (cadr e) var))
2812 (push (caddr e) nn*))
2813 ((simplerd e) nil)
2814 (t (mapc #'pofx (cdr e)))))
2816 (defun ser1 (e)
2817 (cond ((member val '($zeroa $zerob) :test #'eq) nil)
2818 (t (setq e (subin (m+ var val) e))))
2819 (setq e (rdfact e))
2820 (cond ((pofx e) e)))
2822 (defun gather (ind l)
2823 (prog (ans)
2824 (setq ind (car ind))
2825 loop (cond ((null l)
2826 (return (list ind (m*l ans))))
2827 ((equal (caar l) ind)
2828 (push (cadar l) ans)))
2829 (setq l (cdr l))
2830 (go loop)))
2832 ; returns rough class-of-growth of term
2833 (defun istrength (term)
2834 (cond ((mnump term) (list 'num term))
2835 ((atom term) (cond ((eq term var)
2836 (list 'var var 1.))
2837 (t (list 'num term))))
2838 ((not (among var term)) (list 'num term))
2839 ((mplusp term)
2840 (let ((temp (ismax-core (mapcar #'istrength (cdr term)))))
2841 (cond ((not (null temp)) temp)
2842 (t `(gen ,term)))))
2843 ((mtimesp term)
2844 (let ((temp (mapcar #'istrength (cdr term)))
2845 (temp1 ()))
2846 (setq temp1 (ismax temp))
2847 (cond ((null temp1) `(gen ,term))
2848 ((eq (car temp1) 'log) `(log ,temp))
2849 ((eq (car temp1) 'var) (add-up-deg temp))
2850 (t `(gen ,temp)))))
2851 ((and (mexptp term)
2852 (real-infinityp (limit term var val t)))
2853 (let ((logterm (logred term)))
2854 (cond ((and (among var (caddr term))
2855 (member (car (istrength logterm))
2856 '(var exp fact) :test #'eq)
2857 (real-infinityp (limit logterm var val t)))
2858 (list 'exp (m^ '$%e logterm)))
2859 ((not (among var (caddr term)))
2860 (let ((temp (istrength (cadr term))))
2861 (cond ((not (alike1 temp term))
2862 (rplaca (cdr temp) term)
2863 (and (eq (car temp) 'var)
2864 (rplaca (cddr temp)
2865 (m* (caddr temp) (caddr term))))
2866 temp)
2867 (t `(gen ,term)))))
2868 (t `(gen ,term)))))
2869 ((and (eq (caar term) '%log)
2870 (real-infinityp (limit term var val t)))
2871 (let ((stren (istrength (cadr term))))
2872 (cond ((member (car stren) '(log var) :test #'eq)
2873 `(log ,term))
2874 ((and (eq (car stren) 'exp)
2875 (eq (caar (second stren)) 'mexpt))
2876 (istrength (logred (second stren))))
2877 (t `(gen ,term)))))
2878 ((eq (caar term) 'mfactorial)
2879 (list 'fact term))
2880 ((let ((temp (hyperex term)))
2881 (and (not (alike1 term temp))
2882 (istrength temp))))
2883 (t (list 'gen term))))
2885 ;; log reduce - returns log of s1
2886 ;; When s1 is not of the form a^b, this code doesn't return log(s1).
2887 ;; Running the testsuite does send non exptp expressions to this function.
2888 (defun logred (s1)
2889 (or (and (eq (cadr s1) '$%e) (caddr s1))
2890 (m* (caddr s1) `((%log) ,(cadr s1)))))
2892 (defun asymredu (rd)
2893 (cond ((atom rd) rd)
2894 ((mnump rd) rd)
2895 ((not (among var rd)) rd)
2896 ((polyinx rd var t))
2897 ((simplerd rd)
2898 (cond ((eq (cadr rd) var) rd)
2899 (t (mabs-subst
2900 (factor ($expand (m^ (polyinx (cadr rd) var t)
2901 (caddr rd))))
2903 val))))
2904 (t (simplify (cons (list (caar rd))
2905 (mapcar #'asymredu (cdr rd)))))))
2907 (defun rdfact (rd)
2908 (let ((dn** ()) (nn** ()))
2909 (cond ((atom rd) rd)
2910 ((mnump rd) rd)
2911 ((not (among var rd)) rd)
2912 ((polyp rd)
2913 (factor rd))
2914 ((simplerd rd)
2915 (cond ((eq (cadr rd) var) rd)
2916 (t (setq dn** (caddr rd))
2917 (setq nn** (factor (cadr rd)))
2918 (cond ((mtimesp nn**)
2919 (m*l (mapcar #'(lambda (j) (m^ j dn**))
2920 (cdr nn**))))
2921 (t rd)))))
2922 (t (simplify (cons (ncons (caar rd))
2923 (mapcar #'rdfact (cdr rd))))))))
2925 (defun cnv (expl val)
2926 (mapcar #'(lambda (e)
2927 (maxima-substitute (cond ((eq val '$zerob)
2928 (m* -1 (m^ var -1)))
2929 ((eq val '$zeroa)
2930 (m^ var -1))
2931 ((eq val '$minf)
2932 (m* -1 var))
2933 (t (m^ (m+ var (m* -1 val)) -1.)))
2936 expl))
2938 ;; We could replace pwtaylor with a call to (tlimit-taylor exp var l terms).
2939 ;; Other than eliminating clutter, I know of no advantages to doing so.
2940 (defun pwtaylor (exp var l terms)
2941 (prog (coef ans c mc)
2942 (cond ((=0 terms) (return nil)) ((=0 l) (setq mc t)))
2943 (setq c 0.)
2944 (go tag1)
2945 loop (setq c (1+ c))
2946 (cond ((or (> c 10.) (equal c terms))
2947 (return (m+l ans)))
2948 (t (setq exp (sdiff exp var))))
2949 tag1 (setq coef ($radcan (subin l exp)))
2950 (cond ((=0 coef) (setq terms (1+ terms)) (go loop)))
2951 (setq
2953 (append
2955 (list
2956 (m* coef
2957 (m^ `((mfactorial) ,c) -1)
2958 (m^ (if mc var (m+t (m*t -1 l) var)) c)))))
2959 (go loop)))
2961 (defun rdsget (e)
2962 (cond ((polyp e) e)
2963 ((simplerd e) (rdtay e))
2964 (t (cons (list (caar e))
2965 (mapcar #'rdsget (cdr e))))))
2967 (defun rdtay (rd)
2968 (cond (limit-using-taylor ($ratdisrep ($taylor rd var val 1.)))
2969 (t (lrdtay rd))))
2971 (defun lrdtay (rd)
2972 (prog (varlist p c e d $ratfac)
2973 (setq varlist (ncons var))
2974 (setq p (ratnumerator (cdr (ratrep* (cadr rd)))))
2975 (cond ((< (length p) 3.) (return rd)))
2976 (setq e (caddr rd))
2977 (setq d (pdegr p))
2978 (setq c (m^ var (m* d e)))
2979 (setq d ($ratsimp (varinvert (m* (pdis p) (m^ var (m- d)))
2980 var)))
2981 (setq d (pwtaylor (m^ d e) var 0. 3.))
2982 (return (m* c (varinvert d var)))))
2984 (defun varinvert (e var) (subin (m^t var -1.) e))
2986 (defun deg (p)
2987 (prog ((varlist (list var)))
2988 (return (let (($ratfac nil))
2989 (newvar p)
2990 (pdegr (cadr (ratrep* p)))))))
2992 ;; Like DEG, but dependency on VAR is explicit. Use this instead when
2993 ;; possible.
2994 (defun deg-var (p var1)
2995 (prog ((varlist (list var1)))
2996 (flet ((pdegr-var (pf)
2997 (cond ((or (atom pf)
2998 (not (eq (caadr (ratf var1))
2999 (car pf))))
3001 (low*
3002 (cadr (reverse pf)))
3004 (cadr pf)))))
3005 (return (let (($ratfac nil))
3006 (newvar p)
3007 (pdegr-var (cadr (ratrep* p))))))))
3009 (defun rat-no-ratfac (e)
3010 (let (($ratfac nil))
3011 (newvar e)
3012 (ratrep* e)))
3013 (setq low* nil)
3015 (defun rddeg (rd low*)
3016 (cond ((or (mnump rd)
3017 (not (among var rd)))
3019 ((polyp rd)
3020 (deg rd))
3021 ((simplerd rd)
3022 (m* (deg (cadr rd)) (caddr rd)))
3023 ((mtimesp rd)
3024 (addn (mapcar #'(lambda (j)
3025 (rddeg j low*))
3026 (cdr rd)) nil))
3027 ((and (mplusp rd)
3028 (setq rd (andmapcar #'(lambda (j) (rddeg j low*))
3029 (cdr rd))))
3030 (cond (low* (ratmin rd))
3031 (t (ratmax rd))))))
3033 (defun pdegr (pf)
3034 (cond ((or (atom pf) (not (eq (caadr (ratf var)) (car pf))))
3036 (low* (cadr (reverse pf)))
3037 (t (cadr pf))))
3038 ;;There is some confusion here. We need to be aware of Branch cuts etc....
3039 ;;when doing this section of code. It is not very carefully done so there
3040 ;;are bugs still lurking. Another misfortune is that LIMIT or its inferiors
3041 ;;sometimes decides to change the limit VAL in midstream. This must be corrected
3042 ;;since LIMIT's interaction with the data base environment must be maintained.
3043 ;;I'm not sure that this code can ever be called with VAL other than $INF but
3044 ;;there is a hook in the first important cond clause to cathc them anyway.
3046 (defun asy (n d)
3047 (let ((num-power (rddeg n nil))
3048 (den-power (rddeg d nil))
3049 (coef ()) (coef-sign ()) (power ()))
3050 (setq coef (m// ($ratcoef ($expand n) var num-power)
3051 ($ratcoef ($expand d) var den-power)))
3052 (setq coef-sign (getsignl coef))
3053 (setq power (m// num-power den-power))
3054 (cond ((eq (ask-integer power '$integer) '$integer)
3055 (cond ((eq (ask-integer power '$even) '$even) '$even)
3056 (t '$odd)))) ;Can be extended from here.
3057 (cond ((or (eq val '$minf)
3058 (eq val '$zerob)
3059 (eq val '$zeroa)
3060 (equal val 0)) ()) ;Can be extended to cover some these.
3061 ((ratgreaterp den-power num-power)
3062 (cond ((equal coef-sign 1.) '$zeroa)
3063 ((equal coef-sign -1) '$zerob)
3064 ((equal coef-sign 0) 0)
3065 (t 0)))
3066 ((ratgreaterp num-power den-power)
3067 (cond ((equal coef-sign 1.) '$inf)
3068 ((equal coef-sign -1) '$minf)
3069 ((equal coef-sign 0) nil) ; should never be zero
3070 ((null coef-sign) '$infinity)))
3071 (t coef))))
3073 (defun radlim (e n d)
3074 (prog (nl dl)
3075 (cond ((eq val '$infinity) (throw 'limit nil))
3076 ((eq val '$minf)
3077 (setq nl (m* var -1))
3078 (setq n (subin nl n))
3079 (setq d (subin nl d))
3080 (setq val '$inf))) ;This is the Culprit. Doesn't tell the DATABASE.
3081 (cond ((eq val '$inf)
3082 (setq nl (asymredu n))
3083 (setq dl (asymredu d))
3084 (cond
3085 ((or (rptrouble n) (rptrouble d))
3086 (return (limit (m* (rdsget n) (m^ (rdsget d) -1.)) var val t)))
3087 (t (return (asy nl dl))))))
3088 (setq nl (limit n var val t))
3089 (setq dl (limit d var val t))
3090 (cond ((and (zerop2 nl) (zerop2 dl))
3091 (cond ((or (polyp n) (polyp d))
3092 (return (try-lhospital-quit n d t)))
3093 (t (return (ser0 e n d val)))))
3094 (t (return ($radcan (ratrad (m// n d) n d nl dl)))))))
3096 (defun ratrad (e n d nl dl)
3097 (prog (n1 d1)
3098 (cond ((equal nl 0) (return 0))
3099 ((zerop2 dl)
3100 (setq n1 nl)
3101 (cond ((equal dl 0) (setq d1 '$infinity)) ;No direction Info.
3102 ((eq dl '$zeroa)
3103 (setq d1 '$inf))
3104 ((equal (setq d (behavior d var val)) 1)
3105 (setq d1 '$inf))
3106 ((equal d -1) (setq d1 '$minf))
3107 (t (throw 'limit nil))))
3108 ((zerop2 nl)
3109 (setq d1 dl)
3110 (cond ((equal (setq n (behavior n var val)) 1)
3111 (setq n1 '$zeroa))
3112 ((equal n -1) (setq n1 '$zerob))
3113 (t (setq n1 0))))
3114 (t (return ($radcan (ridofab (subin val e))))))
3115 (return (simplimtimes (list n1 d1)))))
3117 ;;; Limit(log(XXX), var, 0, val), where val is either zerob (limit from below)
3118 ;;; or zeroa (limit from above).
3119 (defun simplimln (expr var val)
3120 (let ((arglim (limit (cadr expr) var val 'think)) (dir))
3121 (cond ((eq arglim '$inf) '$inf) ;log(inf) = inf
3122 ;;log(minf,infinity,zerob) = infinity & log(0) = infinity
3123 ((or (member arglim '($minf $infinity $zerob)))
3124 '$infinity)
3125 ((eq arglim '$zeroa) '$minf) ;log(zeroa) = minf
3126 ;; log(ind) = ind when ind > 0 else und
3127 ((eq arglim '$ind)
3128 (if (eq t (mgrp (cadr expr) 0)) '$ind '$und))
3129 ;; log(und) = und
3130 ((eq arglim '$und) '$und)
3131 ((member arglim '($ind $und)) '$und)
3132 ;; log(1^(-)) = zerob, log(1^(+)) = zeroa & log(1)=0
3133 ((eql arglim 1)
3134 (if (or (eq val '$zerob) (eq var '$zeroa)) val 0))
3135 ;; Special case of arglim = 0
3136 ((eql arglim 0)
3137 (setq dir (behavior (cadr expr) var val))
3138 (cond ((eql dir -1) '$infinity)
3139 ((eql dir 0) '$infinity)
3140 ((eql dir 1) '$minf)))
3141 ;; When arglim is off the negative real axis, use direct substitution
3142 ((off-negative-real-axisp arglim)
3143 (ftake '%log arglim))
3145 ;; We know that arglim is a negative real number, say xx.
3146 ;; When the imaginary part of (cadr expr) near var is negative,
3147 ;; return log(-x) - %i*pi; when the imaginary part of (cadr expr)
3148 ;; near var is positive return log(-x) + %i*pi; and when
3149 ;; we cannot determine the behavior of the imaginary part,
3150 ;; return a nounform. The value of val (either zeroa or zerob)
3151 ;; determines what is meant by "near" (smaller than var when
3152 ;; val is zerob and larger than var when val is zeroa).
3153 (setq dir (behavior ($imagpart (cadr expr)) var val))
3154 (cond ((or (eql dir 1) (eql dir -1))
3155 (add (ftake '%log (mul -1 arglim)) (mul dir '$%i '$%pi)))
3156 (t (throw 'limit nil))))))) ;do a nounform return
3157 (setf (get '%log 'simplim%function) 'simplimln)
3158 (setf (get '%plog 'simplim%function) 'simplimln)
3160 (defun simplim%limit (e x pt)
3161 (declare (ignore e x pt))
3162 (throw 'limit t))
3163 (setf (get '%limit 'simplim%function) 'simplim%limit)
3165 (defun simplim%unit_step (e var val)
3166 (let ((lim (limit (cadr e) var val 'think)))
3167 (cond ((eq lim '$und) '$und)
3168 ((eq lim '$ind) '$ind)
3169 ((eq lim '$zerob) 0)
3170 ((eq lim '$zeroa) 1)
3171 ((not (lenient-realp lim)) (throw 'limit nil)) ;catches infinity too
3172 ;; catches minf & inf cases
3173 ((eq t (mgrp 0 lim)) 0)
3174 ((eq t (mgrp lim 0)) 1)
3175 (t '$ind))))
3176 (setf (get '$unit_step 'simplim%function) 'simplim%unit_step)
3178 (defun simplim%conjugate (e var val)
3179 (let ((lim (limit (cadr e) var val 'think)))
3180 (cond ((off-negative-real-axisp lim)
3181 (ftake '$conjugate lim))
3182 (t (throw 'limit nil)))))
3183 (setf (get '$conjugate 'simplim%function) 'simplim%conjugate)
3185 (defun simplim%imagpart (e var val)
3186 (let ((lim (limit (cadr e) var val 'think)))
3187 (cond ((eq lim '$und) '$und)
3188 ((eq lim '$ind) 0)
3189 ((eq lim '$infinity) (throw 'limit nil))
3190 (t (mfuncall '$imagpart lim)))))
3191 (setf (get '$imagpart 'simplim%function) 'simplim%imagpart)
3192 (setf (get '%imagpart 'simplim%function) 'simplim%imagpart)
3194 (defun simplim%realpart (e var val)
3195 (let ((lim (limit (cadr e) var val 'think)))
3196 (cond ((eq lim '$und) '$und)
3197 ((eq lim '$ind) '$ind)
3198 ((eq lim '$infinity) (throw 'limit nil))
3199 (t (mfuncall '$realpart lim)))))
3200 (setf (get '$realpart 'simplim%function) 'simplim%realpart)
3201 (setf (get '%realpart 'simplim%function) 'simplim%realpart)
3202 ;;; Limit of the Factorial function
3204 (defun simplimfact (expr var val)
3205 (let* ((arglim (limit (cadr expr) var val 'think)) ; Limit of the argument.
3206 (arg2 arglim))
3207 (cond ((eq arglim '$inf) '$inf)
3208 ((member arglim '($minf $infinity $und $ind) :test #'eq) '$und)
3209 ((zerop2 arglim) 1)
3210 ((and (or (maxima-integerp arglim)
3211 (setq arg2 (integer-representation-p arglim)))
3212 (eq ($sign arg2) '$neg))
3213 ;; A negative integer or float or bigfloat representation.
3214 (let ((dir (limit (add (cadr expr) (mul -1 arg2)) var val 'think))
3215 (even (mevenp arg2)))
3216 (cond ((or (and even
3217 (eq dir '$zeroa))
3218 (and (not even)
3219 (eq dir '$zerob)))
3220 '$minf)
3221 ((or (and even
3222 (eq dir '$zerob))
3223 (and (not even)
3224 (eq dir '$zeroa)))
3225 '$inf)
3226 (t (throw 'limit nil)))))
3228 ;; Call simplifier to get value at the limit of the argument.
3229 (simplify (list '(mfactorial) arglim))))))
3230 (setf (get 'mfactorial 'simplim%function) 'simplimfact)
3232 (defun simplim%erf-%tanh (fn arg)
3233 (let ((arglim (limit arg var val 'think))
3234 (ans ())
3235 (rlim ()))
3236 (cond ((eq arglim '$inf) 1)
3237 ((eq arglim '$minf) -1)
3238 ((eq arglim '$infinity)
3239 (destructuring-bind (rpart . ipart)
3240 (trisplit arg)
3241 (setq rlim (limit rpart var origval 'think))
3242 (cond ((eq fn '%tanh)
3243 (cond ((equal rlim '$inf) 1)
3244 ((equal rlim '$minf) -1)))
3245 ((eq fn '%erf)
3246 (setq ans (limit (m* rpart (m^t ipart -1)) var origval 'think))
3247 (setq ans ($asksign (m+ `((mabs) ,ans) -1)))
3248 (cond ((or (eq ans '$pos) (eq ans '$zero))
3249 (cond ((eq rlim '$inf) 1)
3250 ((eq rlim '$minf) -1)
3251 (t '$und)))
3252 (t '$und))))))
3253 ((eq arglim '$und) '$und)
3254 ((member arglim '($zeroa $zerob $ind) :test #'eq) arglim)
3255 ;;;Ignore tanh(%pi/2*%I) and multiples of the argument.
3257 ;; erf (or tanh) of a known value is just erf(arglim).
3258 (simplify (list (ncons fn) arglim))))))
3260 (defun in-domain-of-atan (z)
3261 (setq z (trisplit z)) ; split z into real and imaginary parts
3262 (let ((x (car z)) (y (cdr z))) ;z = x+%i*y
3263 (not
3264 (and
3265 (eq t (meqp x 0)) ;Re(z) = 0
3266 (or (eq t (mgqp -1 y)) ;-1 >= Im(z)
3267 (eq t (mgqp y 1))))))) ; Im(z) >= 1
3269 (defun simplim%atan (e x pt)
3270 (let ((lim (limit (cadr e) x pt 'think)))
3271 (cond ((or (eq lim '$zeroa) (eq lim '$zerob) (eq lim 0) (eq lim '$ind)) lim)
3272 ((or (eq lim '$und) (eq lim '$infinity)) (throw 'limit nil))
3273 ((eq lim '$inf) #$%pi/2$) ;atan(inf) -> %pi/2
3274 ((eq lim '$minf) #$-%pi/2$) ;atan(-inf) -> -%pi/2
3275 ((in-domain-of-atan (ridofab lim)) ; direct substitution
3276 (ftake '%atan (ridofab lim)))
3277 (t (limit ($logarc e) x pt 'think)))))
3278 (setf (get '%atan 'simplim%function) 'simplim%atan)
3280 (defmvar extended-reals
3281 (append *infinitesimals* *infinities* (list '$und '$ind)))
3283 ;; Most instances of atan2 are simplified to atan expressions, but this routine
3284 ;; handles tricky cases such as limit(atan2((x^2-2), x^3-2*x), x, sqrt(2), minus).
3285 ;; Taylor and Gruntz cannot handle the discontinuity at atan(0, -1)
3287 ;; When possible, we want to evaluate the limit of an atan2 expression using
3288 ;; direct substitution--that produces, I think, the least surprising values.
3290 ;; The general simplifier catches atan2(0,0) and it transforms atan2(minf or inf,X)
3291 ;; and atan2(X, minf or inf) into an atan expression, but it doesn't catch
3292 ;; atan2(X, zerob or zeroa) or atan2(zerob or zeroa, X). For the other extended
3293 ;; real (ind,und, or infinity) arguments, the general simplifier gives sign errors.
3295 (defun simplim%atan2 (e v pt)
3296 (let ((y (second e))
3297 (x (third e))
3298 (xlim)
3299 (ylim)
3300 (xlim-z)
3301 (ylim-z)
3302 (q))
3303 (setq xlim (limit x v pt 'think))
3304 (setq ylim (limit y v pt 'think))
3305 (setq xlim-z (ridofab xlim)
3306 ylim-z (ridofab ylim))
3307 ;; For cases for which direct substitution fails, normalize
3308 ;; x & y and try again.
3309 (setq q (cond ((eq xlim '$inf) x)
3310 ((eq xlim '$minf)
3311 (mul -1 x))
3312 ((eq ylim '$inf) y)
3313 ((eq ylim '$minf)
3314 (mul -1 y))
3315 ((and (eq xlim '$zerob) (zerop2 ylim))
3316 (mul -1 x))
3317 ((and (eq xlim '$zeroa) (zerop2 ylim))
3319 ((and (eq ylim '$zerob) (zerop2 xlim))
3320 (mul -1 y))
3321 ((and (eq ylim '$zeroa) (zerop2 xlim))
3323 (t 1)))
3325 (when (not (eql q 1))
3326 (setq x (div x q))
3327 (setq y (div y q))
3328 (setq xlim (limit x v pt 'think))
3329 (setq ylim (limit y v pt 'think))
3330 (setq xlim-z (ridofab xlim)
3331 ylim-z (ridofab ylim)))
3333 (cond
3334 ((and (eq '$zerob ylim) (eq t (mgrp 0 xlim)))
3335 (mul -1 '$%pi))
3336 ((and (eq '$zerob ylim) (eq t (mgrp xlim 0)))
3338 ((and (eq '$zeroa ylim) (eq t (mgrp 0 xlim)))
3339 '$%pi)
3340 ((and (eq '$zeroa ylim) (eq t (mgrp xlim 0)))
3342 ((and (eql xlim 1) (eql ylim '$inf))
3343 (div '$%pi 2))
3344 ((and (eql xlim -1) (eql ylim 0))
3345 '$ind)
3347 ;; Use direct substitution when ylim-z # 0 or xlim-z > 0. We need
3348 ;; to check that xlim-z & ylim-z are real too.
3349 ((and (lenient-realp xlim-z)
3350 (lenient-realp ylim-z)
3351 (or (eq t (mnqp ylim-z 0))
3352 (eq t (mgrp xlim-z 0))))
3353 (ftake '%atan2 ylim-z xlim-z))
3355 (throw 'limit nil)))))
3356 (setf (get '%atan2 'simplim%function) 'simplim%atan2)
3358 (defun simplimsch (sch arg)
3359 (cond ((real-infinityp arg)
3360 (cond ((eq sch '%sinh) arg) (t '$inf)))
3361 ((eq arg '$infinity) '$infinity)
3362 ((eq arg '$ind) '$ind)
3363 ((eq arg '$und) '$und)
3364 ((and (eq sch '%sinh)
3365 (or (eq arg '$zerob) (eq arg '$zeroa)))
3366 arg)
3367 (t (let (($exponentialize t))
3368 (resimplify (list (ncons sch) (ridofab arg)))))))
3370 ;; simple limit of sin and cos
3371 (defun simplimsc (exp fn arg)
3372 (cond ((member arg '($inf $minf $ind) :test #'eq) '$ind)
3373 ((member arg '($und $infinity) :test #'eq)
3374 (throw 'limit ()))
3375 ((member arg '($zeroa $zerob) :test #'eq)
3376 (cond ((eq fn '%sin) arg)
3377 (t (m+ 1 '$zerob))))
3378 ((sincoshk exp
3379 (simplify (list (ncons fn) (ridofab arg)))
3380 fn))))
3382 (defun simplim%tan (arg)
3383 (let ((arglim (limit arg var val 'think)))
3384 (cond
3385 ((member arglim '($inf $minf $ind) :test #'eq)
3386 '$ind)
3387 ((member arglim '($und $infinity) :test #'eq)
3388 (throw 'limit nil))
3390 ;; Write the limit of the argument as c*%pi + rest.
3391 (let*
3392 ((c (or (pip arglim) 0))
3393 (rest (sratsimp (m- arglim (m* '$%pi c))))
3394 (hit-zero))
3395 ;; Check if tan(x) has a zero or pole at x=arglim.
3396 ;; zero: tan(n*%pi + 0*)
3397 ;; pole: tan((2*n+1)*%pi/2 + 0*)
3398 ;; 0* can be $zeroa, $zerob or 0.
3399 (if (and (member rest '(0 $zeroa $zerob) :test #'equal)
3400 (or (setq hit-zero (integerp c))
3401 (and (ratnump c) (equal (caddr c) 2))))
3402 ;; This is a zero or a pole.
3403 ;; Determine on which side of the zero/pole we are.
3404 ;; If rest is $zeroa or $zerob, use that.
3405 ;; Otherwise (rest = 0), try to determine the side
3406 ;; using the behavior of the argument.
3407 (let
3408 ((side (cond ((eq rest '$zeroa) 1)
3409 ((eq rest '$zerob) -1)
3410 (t (behavior arg var val)))))
3411 (if hit-zero
3412 ;; For a zero, if we don't know the side, just return 0.
3413 (cond
3414 ((equal side 1) '$zeroa)
3415 ((equal side -1) '$zerob)
3416 (t 0))
3417 ;; For a pole, we need to know the side.
3418 ;; Otherwise, we can't determine the limit.
3419 (cond
3420 ((equal side 1) '$minf)
3421 ((equal side -1) '$inf)
3422 (t (throw 'limit t)))))
3423 ;; No zero or pole - substitute in the limit of the argument.
3424 (take '(%tan) (ridofab arglim))))))))
3426 (defun simplim%asinh (arg)
3427 (cond ((member arg '($inf $minf $zeroa $zerob $ind $und) :test #'eq)
3428 arg)
3429 ((eq arg '$infinity) '$und)
3430 (t (simplify (list '(%asinh) (ridofab arg))))))
3432 (defun simplim%acosh (arg)
3433 (cond ((equal (ridofab arg) 1) '$zeroa)
3434 ((eq arg '$inf) arg)
3435 ((eq arg '$minf) '$infinity)
3436 ((member arg '($und $ind $infinity) :test #'eq) '$und)
3437 (t (simplify (list '(%acosh) (ridofab arg))))))
3439 (defun simplim%atanh (arg dir)
3440 ;; Compute limit(atanh(x),x,arg). If ARG is +/-1, we need to take
3441 ;; into account which direction we're approaching ARG.
3442 (cond ((zerop2 arg) arg)
3443 ((member arg '($ind $und $infinity $minf $inf) :test #'eq)
3444 '$und)
3445 ((equal (setq arg (ridofab arg)) 1.)
3446 ;; The limit at 1 should be complex infinity because atanh(x)
3447 ;; is complex for x > 1, but inf if we're approaching 1 from
3448 ;; below.
3449 (if (eq dir '$zerob)
3450 '$inf
3451 '$infinity))
3452 ((equal arg -1.)
3453 ;; Same as above, except for the limit is at -1.
3454 (if (eq dir '$zeroa)
3455 '$minf
3456 '$infinity))
3457 (t (simplify (list '(%atanh) arg)))))
3459 (defun simplim%asin (e x pt)
3460 (let ((lim (limit (cadr e) x pt 'think)) (dir) (lim-sgn))
3461 (cond ((member lim '($zeroa $zerob)) lim) ;asin(zeoroa/b) = zeroa/b
3462 ((member lim '($minf '$inf '$infinity)) '$infinity)
3463 ((eq lim '$ind) '$ind) ;asin(ind)=ind
3464 ((eq lim '$und) '$und) ;asin(und)=und
3465 ((in-domain-of-asin lim) ;direct substitution
3466 (ftake '%asin lim))
3468 (setq e (trisplit (cadr e))) ;overwrite e!
3469 (setq dir (behavior (cdr e) x pt))
3470 (setq lim-sgn ($csign (car e))) ;lim-sgn = sign limit(Re(e))
3471 (cond
3472 ((eql dir 0)
3473 (throw 'limit t)) ;unable to find behavior of imaginary part
3475 ;; For the values of asin on the branch cuts, see DLMF 4.23.20 & 4.23.21
3476 ;; Diagram of the values of asin just above and below the branch cuts
3478 ;; asin(x) pi - asin(x)
3479 ;;................ -1 ....0.... 1 ...............
3480 ;; -pi - asin(x) asin(x)
3482 ;; Let's start in northwest and rotate counterclockwise:
3483 ((and (eq '$neg lim-sgn) (eq dir 1))
3484 (ftake '%asin lim))
3485 ((and (eq '$pos lim-sgn) (eq dir 1))
3486 (sub '$%pi (ftake '%asin lim)))
3487 ((and (eq '$pos lim-sgn) (eq dir -1))
3488 (ftake '%asin lim))
3489 ((and (eq '$neg lim-sgn) (eq dir -1))
3490 (sub (mul -1 '$%pi) (ftake '%asin lim)))
3492 ;; unable to find sign of real part of lim.
3493 (throw 'limit t)))))))
3494 (setf (get '%asin 'simplim%function) 'simplim%asin)
3496 (defun simplim%acos (e x pt)
3497 (let ((lim (limit (cadr e) x pt 'think)) (dir) (lim-sgn))
3498 (cond ((in-domain-of-asin lim) ;direct substitution
3499 (ftake '%acos lim))
3500 ((member lim '($und $ind $inf $minf $infinity)) ;boundary cases
3501 '$und)
3503 (setq e (trisplit (cadr e))) ;overwrite e!
3504 (setq dir (behavior (cdr e) x pt))
3505 (setq lim-sgn ($csign lim))
3506 (cond
3507 ((eql dir 0)
3508 (throw 'limit t)) ;unable to find behavior of imaginary part
3509 ;; for the values of acos on the branch cuts, see DLMF 4.23.24 & 4.23.25
3510 ;; http://dlmf.nist.gov/4.23.E24
3511 ((or (eq '$pos lim-sgn) (eq '$neg lim-sgn))
3512 ;; continuous from above
3513 (if (eql dir 1) (ftake '%acos lim) (sub (mul 2 '$%pi) (ftake '%acos lim))))
3515 ;; unable to find sign of real part of lim.
3516 (throw 'limit t)))))))
3517 (setf (get '%acos 'simplim%function) 'simplim%acos)
3519 ;; Limit of an %integrate expression. For a definite integral
3520 ;; integrate(ee,var,a,b), when ee is free of the limit variable
3521 (defun simplim%integrate (e x pt)
3522 (let* ((ee (second e)) ;ee = integrand
3523 (var (third e)) ;integration variable
3524 (a (fourth e)) ;lower limit or nil if indefinite
3525 (b (fifth e)) ;lower limit or nil if indefinite
3526 (alim) (blim))
3527 (cond ((and a b ($freeof x ee) ($freeof x var))
3528 (setq alim (limit a x pt 'think))
3529 (setq blim (limit b x pt 'think))
3530 (if (and (lenient-extended-realp alim)
3531 (lenient-extended-realp blim)
3532 (not (eq alim '$infinity))
3533 (not (eq blim '$infinity)))
3534 (ftake '%integrate ee var alim blim)
3535 (throw 'limit t)))
3537 (throw 'limit t)))))
3538 (setf (get '%integrate 'simplim%function) 'simplim%integrate)
3540 (defun subftake (op subarg arg)
3541 (simplifya (subfunmake op subarg arg) t))
3543 (defun off-one-to-inf (z)
3544 (setq z (trisplit z)) ; split z into x+%i*y
3546 (eq t (mnqp (cdr z) 0)) ; y # 0
3547 (eq t (mgrp 1 (car z))))) ; x < 1
3549 (defun simplim%li (expr x pt)
3550 (let ((n (car (subfunsubs expr))) (e (car (subfunargs expr))))
3551 (cond ((freeof x n)
3552 (setq e (limit e x pt 'think))
3553 (cond ((and (eq e '$minf) (integerp n) (>= n 2))
3554 '$minf)
3555 ((and (eq e '$inf) (integerp n) (>= n 2))
3556 '$infinity)
3557 ((or (eql (ridofab e) 1) (and (not (extended-real-p e)) (off-one-to-inf e)))
3558 ;; Limit of li[s](1) can be evaluated by just
3559 ;; substituting in 1.
3560 ;; Same for li[s](x) when x is < 1.
3561 (subftake '$li (list n) (list e)))
3562 (t (throw 'limit nil))))
3563 ;; Claim ignorance when order depends on limit variable.
3564 (t (throw 'limit nil)))))
3566 (setf (get '$li 'simplim%function) 'simplim%li)
3567 (setf (get '%li 'simplim%function) 'simplim%li)
3569 (defun simplim$psi (order arg val)
3570 (if (and (not (equal (length order) 1))
3571 (not (equal (length arg) 1)))
3572 (throw 'limit ())
3573 (setq order (car order)
3574 arg (car arg)))
3575 (cond ((equal order 0)
3576 (destructuring-bind (rpart . ipart)
3577 (trisplit arg)
3578 (cond ((not (equal ipart 0)) (throw 'limit ()))
3579 (t (setq rpart (limit rpart var val 'think))
3580 (cond ((eq rpart '$zeroa) '$minf)
3581 ((eq rpart '$zerob) '$inf)
3582 ((eq rpart '$inf) '$inf)
3583 ((eq rpart '$minf) '$und)
3584 ((equal (getsignl rpart) -1) (throw 'limit ()))
3585 (t (simplify (subfunmake '$psi (list order)
3586 (list rpart)))))))))
3587 ((and (integerp order) (> order 0)
3588 (equal (limit arg var val 'think) '$inf))
3589 (cond ((mevenp order) '$zerob)
3590 ((moddp order) '$zeroa)
3591 (t (throw 'limit ()))))
3592 (t (throw 'limit ()))))
3594 (defun simplim%inverse_jacobi_ns (arg m)
3595 (if (or (eq arg '$inf) (eq arg '$minf))
3597 `((%inverse_jacobi_ns) ,arg ,m)))
3599 (defun simplim%inverse_jacobi_nc (arg m)
3600 (if (or (eq arg '$inf) (eq arg '$minf))
3601 `((%elliptic_kc) ,m)
3602 `((%inverse_jacobi_nc) ,arg ,m)))
3604 (defun simplim%inverse_jacobi_sc (arg m)
3605 (if (or (eq arg '$inf) (eq arg '$minf))
3606 `((%elliptic_kc) ,m)
3607 `((%inverse_jacobi_sc) ,arg ,m)))
3609 (defun simplim%inverse_jacobi_dc (arg m)
3610 (if (or (eq arg '$inf) (eq arg '$minf))
3611 `((%elliptic_kc) ,m)
3612 `((%inverse_jacobi_dc) ,arg ,m)))
3614 (defun simplim%inverse_jacobi_cs (arg m)
3615 (if (or (eq arg '$inf) (eq arg '$minf))
3617 `((%inverse_jacobi_cs) ,arg ,m)))
3619 (defun simplim%inverse_jacobi_ds (arg m)
3620 (if (or (eq arg '$inf) (eq arg '$minf))
3622 `((%inverse_jacobi_ds) ,arg ,m)))
3624 (defun simplim%signum (e x pt)
3625 (let ((e (limit (cadr e) x pt 'think)) (sgn))
3626 (cond ((eq '$minf e) -1)
3627 ((eq '$inf e) 1)
3628 ((eq '$infinity e) '$und)
3629 ((eq '$ind e) '$ind)
3630 ((eq '$und e) e)
3631 ((eq '$zerob e) -1)
3632 ((eq '$zeroa e) 1)
3634 (setq sgn (mnqp e 0))
3635 (cond ((eq t sgn) (ftake '%signum e))
3636 (t (throw 'limit nil))))))) ; don't know
3637 (setf (get '%signum 'simplim%function) 'simplim%signum)
3639 ;; more functions for limit to handle
3641 (defun lfibtophi (e)
3642 (cond ((not (involve e '($fib))) e)
3643 ((eq (caar e) '$fib)
3644 (let ((lnorecurse t))
3645 ($fibtophi (list '($fib) (lfibtophi (cadr e))) lnorecurse)))
3646 (t (cons (car e)
3647 (mapcar #'lfibtophi (cdr e))))))
3649 ;;; FOLLOWING CODE MAKES $LDEFINT WORK
3651 (defmfun $ldefint (exp var ll ul &aux $logabs ans a1 a2)
3652 (setq $logabs t ans (sinint exp var)
3653 a1 (toplevel-$limit ans var ul '$minus)
3654 a2 (toplevel-$limit ans var ll '$plus))
3655 (and (member a1 '($inf $minf $infinity $und $ind) :test #'eq)
3656 (setq a1 (nounlimit ans var ul)))
3657 (and (member a2 '($inf $minf $infinity $und $ind) :test #'eq)
3658 (setq a2 (nounlimit ans var ll)))
3659 ($expand (m- a1 a2)))
3661 (defun nounlimit (exp var val)
3662 (setq exp (restorelim exp))
3663 (nconc (list '(%limit) exp var (ridofab val))
3664 (cond ((eq val '$zeroa) '($plus))
3665 ((eq val '$zerob) '($minus)))))
3667 ;; substitute inside noun form of %derivative
3668 ;; for cases such as limit('diff(x+2,x), x, 1)
3669 ;; -> limit('diff(xx+3), xx, 0)
3671 ;; maxima-substitute with *atp* skips over %derivative
3673 ;; substitutes diff(f(realvar), realvar, n)
3674 ;; -> diff(f(var+val), var, n)
3675 (defun derivative-subst (exp val var realvar)
3676 (cond ((atom exp) exp)
3677 ((eq '%derivative (caar exp))
3678 (cons
3679 (car exp)
3680 (cons ;; the function being differentiated
3681 (maxima-substitute (m+ val var) realvar (cadr exp))
3682 (cons ;; the var of differentiation
3683 (maxima-substitute var realvar (caddr exp))
3684 (cdddr exp))))) ;; the order of the derivative
3685 (t (cons (car exp)
3686 (mapcar (lambda (x) (derivative-subst x val var realvar))
3687 (cdr exp))))))
3689 (defun oscip (e)
3690 (or (involve e '(%sin %cos %tan))
3691 (among '$%i (%einvolve e))))
3693 ;; Like OSCIP, but the dependency on VAR is explicit (second arg).
3694 ;; Use this instead when possible.
3695 (defun oscip-var (e var1)
3696 (or (involve-var e var1 '(%sin %cos %tan))
3697 (among '$%i (%einvolve-var e var1))))
3699 (defun %einvolve (e)
3700 (when (among '$%e e) (%einvolve01 e)))
3702 (defun %einvolve01 (e)
3703 (cond ((atom e) nil)
3704 ((mnump e) nil)
3705 ((and (mexptp e)
3706 (eq (cadr e) '$%e)
3707 (among var (caddr e)))
3708 (caddr e))
3709 (t (some #'%einvolve (cdr e)))))
3711 ;; Just like %EINVOLVE, except the dependency on VAR is explicit
3712 ;; (second arg here). Use this instead when possible.
3713 (defun %einvolve-var (e var1)
3714 (flet ((%einvolve01-var (e)
3715 ;; A copy of %ENVOLVE01, but for %EINVOLVE-VAR.
3716 (cond ((atom e)
3717 nil)
3718 ((mnump e)
3719 nil)
3720 ((and (mexptp e)
3721 (eq (cadr e) '$%e)
3722 (among var1 (caddr e)))
3723 (caddr e))
3724 (t (some #'(lambda (ee)
3725 (%einvolve-var ee var1))
3726 (cdr e))))))
3727 (when (among '$%e e)
3728 (%einvolve01-var e))))
3731 (declare-top (unspecial *indicator exp var val origval taylored
3732 $tlimswitch logcombed lhp? lhcount))
3735 ;; GRUNTZ ALGORITHM
3737 ;; Dominik Gruntz
3738 ;; "On Computing Limits in a Symbolic Manipulation System"
3739 ;; PhD Dissertation ETH Zurich 1996
3741 ;; The algorithm identifies the most rapidly varying (MRV) subexpression,
3742 ;; replaces it with a new variable w, rewrites the expression in terms
3743 ;; of the new variable, and then repeats.
3745 ;; The algorithm doesn't handle oscillating functions, so it can't do things like
3746 ;; limit(sin(x)/x, x, inf).
3748 ;; To handle limits involving functions like gamma(x) and erf(x), the
3749 ;; gruntz algorithm requires them to be written in terms of asymptotic
3750 ;; expansions, which maxima cannot currently do.
3752 ;; The algorithm assumes that everything is real, so it can't
3753 ;; currently handle limit((-2)^x, x, inf).
3755 ;; This is one of the methods used by maxima's $limit.
3756 ;; It is also directly available to the user as $gruntz.
3759 ;; most rapidly varying subexpression of expression exp with respect to limit variable var.
3760 ;; returns a list of subexpressions which are in the same MRV equivalence class.
3761 (defun mrv (exp var)
3762 (cond ((freeof var exp)
3763 nil)
3764 ((eq var exp)
3765 (list var))
3766 ((mtimesp exp)
3767 (mrv-max (mrv (cadr exp) var)
3768 (mrv (m*l (cddr exp)) var)
3769 var))
3770 ((mplusp exp)
3771 (mrv-max (mrv (cadr exp) var)
3772 (mrv (m+l (cddr exp)) var)
3773 var))
3774 ((mexptp exp)
3775 (cond ((freeof var (caddr exp))
3776 (mrv (cadr exp) var))
3777 ((member (limitinf (logred exp) var) '($inf $minf) :test #'eq)
3778 (mrv-max (list exp) (mrv (caddr exp) var) var))
3779 (t (mrv-max (mrv (cadr exp) var) (mrv (caddr exp) var) var))))
3780 ((mlogp exp)
3781 (mrv (cadr exp) var))
3782 ((equal (length (cdr exp)) 1)
3783 (mrv (cadr exp) var))
3784 ((equal (length (cdr exp)) 2)
3785 (mrv-max (mrv (cadr exp) var)
3786 (mrv (caddr exp) var)
3787 var))
3788 (t (tay-error "mrv not implemented" exp))))
3790 ;; takes two lists of expressions, f and g, and limit variable var.
3791 ;; members in each list are assumed to be in same MRV equivalence
3792 ;; class. returns MRV set of the union of the inputs - either f or g
3793 ;; or the union of f and g.
3794 (defun mrv-max (f g var)
3795 (prog ()
3796 (cond ((not f)
3797 (return g))
3798 ((not g)
3799 (return f))
3800 ((intersection f g)
3801 (return (union f g))))
3802 (let ((c (mrv-compare (car f) (car g) var)))
3803 (cond ((eq c '>)
3804 (return f))
3805 ((eq c '<)
3806 (return g))
3807 ((eq c '=)
3808 (return (union f g)))
3809 (t (merror "MRV-MAX: expected '>' '<' or '='; found: ~M" c))))))
3811 (defun mrv-compare (a b var)
3812 (let ((c ($limit (div (ftake '%log a) (ftake '%log b)) var '$inf)))
3813 (cond ((eql c 0)
3815 ((member c '($inf $minf) :test #'eq)
3817 (t '=))))
3819 ;; rewrite expression exp by replacing members of MRV set omega with
3820 ;; expressions in terms of new variable wsym. return cons pair of new
3821 ;; version of exp and the log of the new variable wsym.
3822 (defun mrv-rewrite (exp omega var wsym)
3823 (setq omega (stable-sort omega (lambda (x y) (> (length (mrv x var))
3824 (length (mrv y var))))));FIXME consider a total order function with #'sort
3825 (let* ((g (car (last omega)))
3826 (logg (logred g))
3827 (sig (equal (mrv-sign logg var) 1))
3828 (w (if sig (m// 1 wsym) wsym))
3829 (logw (if sig (m* -1 logg) logg)))
3830 (mapcar (lambda (x y)
3831 ;;(mtell "y:~M x:~M exp:~M~%" y x exp)
3832 (setq exp (syntactic-substitute y x exp)))
3833 omega
3834 (mapcar (lambda (f) ;; rewrite each element of omega
3835 (let* ((logf (logred f))
3836 (c (mrv-leadterm (m// logf logg) var nil)))
3837 (cond ((not (equal (cadr c) 0))
3838 (merror "MRV-REWRITE: expected leading term to be constant in ~M" c)))
3839 ;;(mtell "logg: ~M logf: ~M~%" logg logf)
3840 (m* (m^ w (car c))
3841 (m^ '$%e (m- logf
3842 (m* (car c) logg))))))
3843 omega))
3844 (cons exp logw)))
3846 ;;; if log w(x) = h(x), rewrite all subexpressions of the form
3847 ;;; log(f(x)) as log(w^-c f(x)) + c h(x) with c the unique constant
3848 ;;; such that w^-c f(x) is strictly less rapidly varying than w.
3849 (defun mrv-rewrite-logs (exp wsym logw)
3850 (cond ((atom exp) exp)
3851 ((and (mlogp exp)
3852 (not (freeof wsym exp)))
3853 (let* ((f (cadr exp))
3854 (c ($lopow (calculate-series f wsym)
3855 wsym)))
3856 (m+ (list (car exp)
3857 (m* (m^ wsym (m- c))
3858 (mrv-rewrite-logs f wsym logw)))
3859 (m* c logw))))
3861 (cons (car exp)
3862 (mapcar (lambda (e)
3863 (mrv-rewrite-logs e wsym logw))
3864 (cdr exp))))))
3866 ;; returns list of two elements: coeff and exponent of leading term of exp,
3867 ;; after rewriting exp in term of its MRV set omega.
3868 (defun mrv-leadterm (exp var omega)
3869 (prog ((new-omega ()))
3870 (cond ((freeof var exp)
3871 (return (list exp 0))))
3872 (dolist (term omega)
3873 (cond ((subexp exp term)
3874 (push term new-omega))))
3875 (setq omega new-omega)
3876 (cond ((not omega)
3877 (setq omega (mrv exp var))))
3878 (cond ((member var omega :test #'eq)
3879 (let* ((omega-up (mrv-moveup omega var))
3880 (e-up (car (mrv-moveup (list exp) var)))
3881 (mrv-leadterm-up (mrv-leadterm e-up var omega-up)))
3882 (return (mrv-movedown mrv-leadterm-up var)))))
3883 (destructuring-let* ((wsym (gensym "w"))
3885 coef
3886 ((f . logw) (mrv-rewrite exp omega var wsym))
3887 (series (calculate-series (mrv-rewrite-logs f wsym logw)
3888 wsym)))
3889 (setq series (maxima-substitute logw `((%log) ,wsym) series))
3890 (setq lo ($lopow series wsym))
3891 (when (or (not ($constantp lo))
3892 (not (free series '%derivative)))
3893 ;; (mtell "series: ~M lo: ~M~%" series lo)
3894 (tay-error "error in series expansion" f))
3895 (setq coef ($coeff series wsym lo))
3896 (when (not (free coef wsym))
3897 (tay-error "MRV-LEADTERM: failed to extract leading coefficient; obtained" coef))
3898 ;;(mtell "exp: ~M f: ~M~%" exp f)
3899 ;;(mtell "series: ~M~%coeff: ~M~%pow: ~M~%" series coef lo)
3900 (return (list coef lo)))))
3902 (defun mrv-moveup (l var)
3903 (mapcar (lambda (exp)
3904 (simplify-log-of-exp
3905 (syntactic-substitute `((mexpt) $%e ,var) var exp)))
3908 (defun mrv-movedown (l var)
3909 (mapcar (lambda (exp) (syntactic-substitute `((%log simp) ,var) var exp))
3912 ;; test whether sub is a subexpression of exp
3913 (defun subexp (exp sub)
3914 (let ((dummy (gensym)))
3915 (putprop dummy t 'internal)
3916 (not (alike1 (maxima-substitute dummy
3918 exp)
3919 exp))))
3921 ;; Generate $lhospitallim terms of taylor expansion.
3922 ;; Ideally we would use a lazy series representation that generates
3923 ;; more terms as higher order terms cancel.
3924 (defun calculate-series (exp var)
3925 (let ((cntx ($supcontext)) ($taylor_simplifier #'extra-simp))
3926 ($activate cntx)
3927 (unwind-protect
3928 (progn
3929 (mfuncall '$assume (ftake 'mgreaterp var 0))
3930 (putprop var t 'internal); keep var from appearing in questions to user
3931 ($taylor exp var 0 $lhospitallim))
3932 (remprop var 'internal)
3933 ($killcontext cntx))))
3935 ;; Given a Maxima expression e and a variable x, mrv-sign(e,x) returns the sign
3936 ;; of e in a neighborhood of real infinity. The sign is encoded as -1 for
3937 ;; negative, 0 for zero, and 1 for positive.
3939 ;; For a sufficiently large number of compositions, log(log(...(log(x))))
3940 ;; is positive in a neighborhood of infinity, but no matter how large we assume x
3941 ;; to be, sign(log(log(... (log(x))))) = pnz. So no, the function mrv-sign cannot
3942 ;; simply call sign.
3944 ;; The Gruntz code makes an assumption that x > *large-positive-number* before
3945 ;; this code is called. This assumption is made in a new super context, so
3946 ;; it's OK for this code to make new assumptions, as the Gruntz code eventually
3947 ;; kills the super context, deleting the new assumptions.
3949 ;; The function mrv-sign-helper extends the mrv sign of an expression to
3950 ;; include the values of 2 for an expression that is not bounded above in a
3951 ;; neighborhood of infinity and -2 for one that is not bounded below. For
3952 ;; example, the extended mrv sign of x --> log(x) is 2, and the extended
3953 ;;; mrv sign of x --> -x is -2.
3955 (defun mrv-sign (e x)
3956 (let ((sgn (mrv-sign-helper e x)))
3957 (if (null sgn) (throw 'taylor-catch nil) (max -1 (min 1 sgn)))))
3959 ;; Map {$neg, $zero, $pos} --> {-1, 0, 1}. For all other inputs, throw an error
3960 ;; to taylor-catch.
3961 (defun mrv-sign-to-number (sgn)
3962 (cond ((eq sgn '$neg) -1)
3963 ((eq sgn '$zero) 0)
3964 ((eq sgn '$pos) 1)
3965 (t (throw 'taylor-catch nil)))) ; nil for pn, pz, nz, pnz, complex, or imaginary.
3967 ;; The function mrv-sign-constant returns the mrv-sign of an expression that is
3968 ;; free of the variable x. Unfortunately, the limit problem limit(ind*inf) makes
3969 ;; its way to the Gruntz code as gruntz(ind*x, x, inf). And ultimately that calls
3970 ;; mrv-sign-constant on ind. So, we trap for this case (and other extended reals)
3971 ;; and throw an error to taylor-catch for an input that is an extended real
3972 ;; (minf, zerob, zeroa, ind, und, inf, or infinity). Possibly, for the inputs
3973 ;; minf, zerob, zeroa, and inf, mrv-sign-constant shouldn't throw to taylor-catch.
3975 ;; When this code does an asksign, it would be OK to append this fact to the
3976 ;; fact database (the Gruntz code works in a new super context). Better, I think,
3977 ;; would be an option on asksign to append the fact.
3978 (defun mrv-sign-constant (e)
3979 (if (member e extended-reals)
3980 (throw 'taylor-catch nil)
3981 (mrv-sign-to-number (if *getsignl-asksign-ok*
3982 ($asksign e)
3983 ($sign e)))))
3985 ;; Return the mrv-sign of e, where e is a sum.
3986 (defun mrv-sign-sum (e x)
3987 (let ((ans) (minfterms nil) (infterms nil) (negterms nil) (posterms nil)
3988 (failedterms nil) (ee (cdr e)))
3989 ;; collect terms with the same value of mrv-sign-helper into lists
3990 (dolist (ek ee)
3991 (setq ans (mrv-sign-helper ek x))
3992 (cond ((eql -2 ans) (push ek minfterms))
3993 ((eql -1 ans) (push ek negterms))
3994 ((eql 1 ans) (push ek posterms))
3995 ((eql 2 ans) (push ek infterms))
3996 (t (push ek failedterms))))
3997 (cond
3998 ;; Unable to find the mrv sign of one or more terms; throw an error.
3999 ;; Possibly, this code could not give up so soon.
4000 (failedterms
4001 (throw 'taylor-catch nil))
4002 ;; at least one inf terms, but no minf terms, return 2
4003 ((and infterms (null minfterms)) 2)
4004 ;; at least one minf terms, but no inf terms, return -2
4005 ((and minfterms (null infterms)) -2)
4006 ;; no minf terms, no negative terms, return either 1 or 2
4007 ((and (null minfterms) (null negterms))
4008 (if infterms 2 1))
4009 ;; no inf terms, no positive terms, return either -2 or -1
4010 ((and (null infterms) (null posterms))
4011 (if minfterms -2 -1))
4012 ;; no min or inf terms, hope csign can do it
4013 ((and (null infterms) (null minfterms))
4014 (mrv-sign-to-number ($csign e)))
4015 ;; both minf terms and inf terms
4017 ;; do the inf or minf terms dominate?
4018 (setq ans ($limit (div
4019 (fapply 'mplus infterms)
4020 (mul -1 (fapply 'mplus minfterms))) x '$inf))
4021 (cond ((eq t (mgrp ans 1)) 2) ; infterms >> |minfterms|, return 2
4022 ((eql ans 0) -2) ; infterms << |minfterms|, return -2
4023 ((eql ans 1)
4024 (let ((a) (b) (qq))
4025 (setq a (fapply 'mplus (append negterms posterms infterms)))
4026 (setq b (mul -1 (fapply 'mplus minfterms)))
4027 (setq qq (tlimit-taylor (sratsimp (sub (div a b) 1)) x '$inf 0 3))
4028 (if (null qq)
4029 (throw 'taylor-catch nil))
4030 (mrv-sign ($ratdisrep qq) x)))
4032 (throw 'taylor-catch nil)))))))
4034 ;; Return the mrv-sign of the expression e, where e is a product.
4035 (defun mrv-sign-product (e x)
4036 (let ((ee (mapcar #'(lambda (q) (mrv-sign-helper q x)) (cdr e))))
4037 (cond
4038 ;; unable to find the sign of one term, dispatch csign on e.
4039 ((some #'null ee) (mrv-sign-to-number ($csign e)))
4040 (t (max -2 (min 2 (reduce '* ee)))))))
4042 ;; Return the mrv-sign of the expression e, where the operator of e is log. To
4043 ;; allow the (slow to finish) test
4044 ;; gruntz(%e^(8*%e^((54*x^(49/45))/17+(21*x^(6/11))/8+5/(2*x^(5/7))+2/x^8))/log(log(-log(4/(3*x^(5/14)))))^(7/6),x,inf);
4045 ;; to complete, we need to examine the mrv sign of both X and 1/X, where
4046 ;; the input to mrv-sign-log is log(X).
4047 (defun mrv-sign-log (e x)
4048 (let ((ee (cadr e)))
4049 (cond ((eql 2 (mrv-sign-helper ee x)) 2) ;log(inf) = inf
4050 ((eq t (mgrp ee 1)) 1) ;log(>1) = pos
4051 ((eql 2 (mrv-sign-helper (div 1 ee) x)) -2); log(zeroa) = minf
4052 ((and (eq t (mgrp ee 0)) (eq t (mgrp 1 ee))) -1) ; log(0< & < 1) = neg
4053 (t (throw 'taylor-catch nil)))))
4055 ;; Return the mrv sign of the expression e, where e = X^Y. For the mrv sign
4056 ;; of an expression to be zero, it needs to be zero in a neighborhood of infinity.
4057 ;; So if limit(X,x,inf) = 1/2 & limit(Y,x,inf) = inf, although limit(X^Y,x,inf)=0,
4058 ;; the mrv sign of X^Y is not zero.
4059 (defun mrv-sign-mexpt (e x) ; e = X^Y
4060 (let ((a (mrv-sign-helper (cadr e) x))
4061 (b (mrv-sign-helper (caddr e) x)))
4062 (cond
4063 ;; pos^minf = pos
4064 ((and (eql a 1) (eql b -2)) 1)
4065 ;; {> 1}^inf = inf
4066 ((and (eql a 1) (eql b 2) (eq t (mgrp (cadr e) 1))) 2)
4067 ;; pos^{neg, pos} = pos
4068 ((and (eql a 1) (or (eql b -1) (eql b 1) (eql b 2))) 1)
4069 ;; inf^pos = inf & inf^inf = inf
4070 ((and (eql a 2) (or (eql b 1) (eql b 2))) 2)
4071 ;; inf^{neg, zero} = pos
4072 ((and (eql a 2) (or (eql b -1) (eql b 0))) 1)
4073 ;; inf^minf = 1
4074 ((and (eql a 2) (eql b -2)) 1)
4075 ;; zero^{pos,inf} = 0. But this case isn't tested by the testsuite!
4076 ((and (eql a 0) (or (eql b 1) (eql b 2))) 0)
4077 ;; For all other cases, let's dispatch csign or asksign
4079 (mrv-sign-to-number
4080 (if *getsignl-asksign-ok* ($asksign e) ($csign e)))))))
4082 (defun atanp (e)
4083 (and (consp e) (eq '%atan (caar e))))
4085 ;; Return the mrv-sign of the expression e, where e = atan(X).
4086 (defun mrv-sign-atan (e x)
4087 (let ((sgn (mrv-sign-helper (cadr e) x)))
4088 (cond ((or (eql -2 sgn) (eql -1 sgn)) -1) ; atan(< 0) = -1
4089 ((or (eql 2 sgn) (eql 1 sgn)) 1) ; atan(> 0) = 1
4090 (t (throw 'taylor-catch nil)))))
4092 (defun sinp (e)
4093 (and (consp e) (eq '%sin (caar e))))
4095 (defun mrv-sign-sin (e x)
4096 (let ((sgn (mrv-sign-helper (div 1 (cadr e)) x)))
4097 (cond ((eql sgn 2) 1) ;sin(zeroa) = 1
4098 ((eql sgn -2) -1) ;sin(zerob) = -1
4099 (t (throw 'taylor-catch nil)))))
4101 ;; Return the extended mrv sign of an expression. To do this, the code
4102 ;; examines the operator of the expression and dispatches the appropriate function.
4103 (defun mrv-sign-helper (e x)
4104 (cond ((freeof x e) (mrv-sign-constant e))
4105 ((eq e x) 2)
4106 ((mtimesp e) (mrv-sign-product e x))
4107 ((mplusp e) (mrv-sign-sum e x))
4108 ((mexptp e) (mrv-sign-mexpt e x))
4109 ((mlogp e) (mrv-sign-log e x))
4110 ((atanp e) (mrv-sign-atan e x))
4111 ((sinp e) (mrv-sign-sin e x))
4112 ;; As needed, uncomment and define functions such as:
4113 ;; ((coshp e) (mrv-sign-cosh e x))
4114 ;; ((sinhp e) (mrv-sign-sinh e x))
4115 ;; If the expression doesn't match any of the above, throw an error.
4116 (t (throw 'taylor-catch nil))))
4118 ;; gruntz algorithm for limit of exp as var goes to positive infinity
4119 (defun limitinf (exp var)
4120 (prog (($exptsubst nil))
4121 (cond ((freeof var exp)
4122 (return exp)))
4123 (destructuring-let* ((c0-e0 (mrv-leadterm exp var nil))
4124 (c0 (car c0-e0))
4125 (e0 (cadr c0-e0))
4126 (sig (mrv-sign e0 var)))
4127 (cond ((equal sig 1)
4128 (return 0))
4129 ((equal sig -1)
4130 (cond ((equal (mrv-sign c0 var) 1)
4131 (return '$inf))
4132 ((equal (mrv-sign c0 var) -1)
4133 (return '$minf))))
4134 ((equal sig 0)
4135 (if (equal exp c0)
4136 ;; example: gruntz(n^n/(n^n+(n-1)^n), n, inf);
4137 (tay-error " infinite recursion in limitinf" exp))
4138 (return (limitinf c0 var)))))))
4140 ;; user-level function equivalent to $limit.
4141 ;; direction must be specified if limit point is not infinite
4142 ;; The arguments are checked and a failure of taylor is caught.
4144 (defmfun $gruntz (expr var val &rest rest)
4145 (let (ans dir)
4146 (when (> (length rest) 1)
4147 (merror
4148 (intl:gettext "gruntz: too many arguments; expected just 3 or 4")))
4149 (setq dir (car rest))
4150 (when (and (not (member val '($inf $minf $zeroa $zerob)))
4151 (not (member dir '($plus $minus))))
4152 (merror
4153 (intl:gettext "gruntz: direction must be 'plus' or 'minus'")))
4154 (setq ans
4155 (catch 'taylor-catch
4156 (let ((silent-taylor-flag t))
4157 (gruntz1 expr var val dir))))
4158 (if (or (null ans) (eq ans t))
4159 (if dir
4160 `(($gruntz simp) ,expr ,var, val ,dir)
4161 `(($gruntz simp) ,expr ,var ,val))
4162 ans)))
4164 ;; Additional simplifications for the limit function. Specifically:
4165 ;; (a) replace every mapatom that is declared to be zero by zero
4166 ;; (b) dispatch radcan on expressions of the form (positive integer)^XXX
4167 ;; (c) log(negative number) --> log(-negative number) + %i*%pi
4168 ;; (d) apply cos(X)^2 + sin(X)^2 --> 1, when X depends on var
4169 ;; (e) convert, gamma functions, binomial coefficients, and beta functions to
4170 ;; factorial form
4171 ;; (f) do some reciprocial function transformations; for example
4172 ;; csc(X) --> 1/sin(X)
4173 ;; (g) do transformations similar to acsc(X) --> asin(1/X).
4174 ;; (h) convert fibonacci functions to power form.
4175 ;; The mechanism (a) isn't perfect--if a+b is declared to zero, it doesn't
4176 ;; simplify a+b+c to c, for example.
4178 ;; This should be moved to the jacobi function code. And likely, we should
4179 ;; set the reciprocal property for the other jacobi functions.
4180 (mapcar #'(lambda (q) (setf (get (car q) 'recip) (cdr q)))
4181 '((%jacobi_nc . %jacobi_cn)
4182 (%jacobi_ns . %jacobi_sn)
4183 (%jacobi_cs . %jacobi_sc)
4184 (%jacobi_ds . %jacobi_sd)
4185 (%jacobi_dc . %jacobi_cd)))
4187 (defun extra-simp (e)
4188 (declare (special var))
4189 (let ((var-present (not (freeof var e))))
4190 (cond ((extended-real-p e) e) ;we don't want to call sign on ind, so catch this
4191 (($mapatom e) ;if e is declared zero, return 0; otherwise e
4192 (if (eq '$zero ($csign e)) 0 e))
4193 ;; dispatch radcan on (positive integer)^Y
4194 ((and (mexptp e) (integerp (cadr e)) (> (cadr e) 0))
4195 ($radcan (ftake 'mexpt (cadr e) (extra-simp (caddr e)))))
4196 ;; log(negative number) --> log(-negative number) + %i*%pi. This is
4197 ;; needed for a nice result for integrate(x^3/(exp(x)-1),x,0,inf), for
4198 ;; example.
4199 ((and (eq '%log (caar e)) ($numberp (cadr e)) (eq t (mgrp 0 (cadr e))))
4200 (add (ftake '%log (mul -1 (cadr e))) (mul '$%i '$%pi)))
4201 ;; When e isn't freeof var and e is a sum, map extra-simp over the
4202 ;; summands, add the results, and apply sin-sq-cos-sq-sub.
4203 ((and var-present (mplusp e))
4204 (sin-sq-cos-sq-sub (fapply 'mplus (mapcar #'extra-simp (cdr e))) var))
4205 ;; Convert gamma functions to factorials. Eventually, we should convert
4206 ;; factorials to gamma functions, I think (BW).
4207 ((and var-present (eq '%gamma (caar e)))
4208 (ftake 'mfactorial (extra-simp (sub (cadr e) 1))))
4209 ;; Exponentialize the hyperbolic functions. It might be nicer to not do
4210 ;; this, but without this we get an error for limit(diff(log(tan(%pi/2*tanh(x))),x),x,inf).
4211 ((and var-present (member (caar e) (list '%sinh '%cosh '%tanh '%sech '%csch '%coth)))
4212 (extra-simp ($exponentialize e)))
4213 ;; When X depends on var, apply reciprocal function identities such as
4214 ;; csc(X) --> 1/sin(X). Specifically, do this for operators '%sec, '%csc,
4215 ;; '%cot, '%jacobi_nc, '%jacobi_ns, %jacobi_cs, %jacobi_ds, and %jacobi_dc.
4216 ;; Since the hyperbolics are exponentialized, we don't do this for the
4217 ;; hyperbolics.
4218 ((and var-present (member (caar e)
4219 (list '%sec '%csc '%cot '%jacobi_nc '%jacobi_ns '%jacobi_cs '%jacobi_ds '%jacobi_dc)))
4220 (div 1 (fapply (get (caar e) 'recip) (mapcar #'extra-simp (cdr e)))))
4221 ;; When X or Y depends on var, convert binomial(X,Y) to factorial form.
4222 ;; Same for beta(x,y). Again, I think it would be better to convert to
4223 ;; gamma function form.
4224 ((and var-present (member (caar e) (list '%binomial '%beta)))
4225 (extra-simp ($makefact e)))
4226 ;; When X depends on var, do acsc(X) --> asin(1/X). Do the same
4227 ;; for asec, acot, acsch, asech, and acoth.
4228 ((and var-present (member (caar e) '(%acsc %asec %acot %acsch %asech %acoth)))
4229 (ftake (get (get (get (caar e) '$inverse) 'recip) '$inverse)
4230 (div 1 (extra-simp (cadr e)))))
4231 ;; When X depends on var, convert fib(X) to its power form.
4232 ((and var-present (eq '$fib (caar e)))
4233 (extra-simp ($fibtophi e)))
4234 ;; convert log_gamma(X) to log(gamma(X))
4235 ((and var-present (eq '%log_gamma (caar e)))
4236 (extra-simp (ftake '%log (ftake '%gamma (cadr e)))))
4237 (($subvarp (mop e)) ;subscripted function
4238 (subfunmake
4239 (subfunname e)
4240 (mapcar #'extra-simp (subfunsubs e))
4241 (mapcar #'extra-simp (subfunargs e))))
4242 (t (fapply (caar e) (mapcar #'extra-simp (cdr e)))))))
4244 ;; Call extra-simp followed by a call to resimplify. This is analogous to
4245 ;; sratsimp.
4246 (defun resimp-extra-simp (e) (resimplify (extra-simp e)))
4248 ;; This function is for internal use in $limit.
4250 ;; The function gruntz1 standardizes the limit point to inf and the limit variable
4251 ;; to a gensym. Since the limit point is possibly altered by this function, we
4252 ;; need to make the appropriate assumptions on the limit variable. This is done
4253 ;; in a supcontext.
4254 (defun gruntz1 (exp var val &rest rest)
4255 (cond ((> (length rest) 1)
4256 (merror (intl:gettext "gruntz: too many arguments; expected just 3 or 4"))))
4257 (let (($logexpand t) ; gruntz needs $logexpand T
4258 (newvar (gensym "w"))
4259 (dir (car rest)))
4260 (putprop newvar t 'internal); keep var from appearing in questions to user
4261 (cond ((eq val '$inf)
4262 (setq exp (maxima-substitute newvar var exp)))
4263 ((eq val '$minf)
4264 (setq exp (maxima-substitute (m* -1 newvar) var exp)))
4265 ((eq val '$zeroa)
4266 (setq exp (maxima-substitute (m// 1 newvar) var exp)))
4267 ((eq val '$zerob)
4268 (setq exp (maxima-substitute (m// -1 newvar) var exp)))
4269 ((eq dir '$plus)
4270 (setq exp (maxima-substitute (m+ val (m// 1 newvar)) var exp)))
4271 ((eq dir '$minus)
4272 (setq exp (maxima-substitute (m+ val (m// -1 newvar)) var exp)))
4273 (t (merror (intl:gettext "gruntz: direction must be 'plus' or 'minus'; found: ~M") dir)))
4274 (let ((cx ($supcontext)))
4275 (unwind-protect
4276 (progn
4277 (mfuncall '$assume (ftake 'mlessp *large-positive-number* newvar)) ; *large-positive-number* < newvar
4278 (mfuncall '$assume (ftake 'mlessp 0 'lim-epsilon)) ; 0 < lim-epsilon
4279 (mfuncall '$assume (ftake 'mlessp *large-positive-number* 'prin-inf)) ; *large-positive-number* < prin-inf
4280 (mfuncall '$activate cx) ;not sure this is needed, but OK
4281 (setq exp (resimplify exp)) ;simplify in new context
4282 (setq exp (resimp-extra-simp (sratsimp exp))) ;additional simplifications
4283 (limitinf exp newvar)) ;compute & return limit
4284 ($killcontext cx))))) ;kill context & forget all new facts.
4286 ;; substitute y for x in exp
4287 ;; similar to maxima-substitute but does not simplify result
4288 (defun syntactic-substitute (y x exp)
4289 (cond ((alike1 x exp) y)
4290 ((atom exp) exp)
4291 (t (cons (car exp)
4292 (mapcar (lambda (exp)
4293 (syntactic-substitute y x exp))
4294 (cdr exp))))))
4296 ;; log(exp(subexpr)) -> subexpr
4297 ;; without simplifying entire exp
4298 (defun simplify-log-of-exp (exp)
4299 (cond ((atom exp) exp)
4300 ((and (mlogp exp)
4301 (mexptp (cadr exp))
4302 (eq '$%e (cadadr exp)))
4303 (caddr (cadr exp)))
4304 (t (cons (car exp)
4305 (mapcar #'simplify-log-of-exp
4306 (cdr exp))))))