1;;; -*-  Mode: Lisp; Package: Maxima; Syntax: Common-Lisp; Base: 10 -*- ;;;;
2;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
3;;;     The data in this file contains enhancments.                    ;;;;;
4;;;                                                                    ;;;;;
5;;;  Copyright (c) 1984,1987 by William Schelter,University of Texas   ;;;;;
6;;;     All rights reserved                                            ;;;;;
7;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
8;;;     (c) Copyright 1982 Massachusetts Institute of Technology         ;;;
9;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
10
11(in-package :maxima)
12
13(macsyma-module matrun)
14
15;;; TRANSLATION properties for the FSUBRs in this file
16;;; can be found in MAXSRC;TRANS5 >.  Be sure to check on those
17;;; if any semantic changes are made.
18
19(declare-top (special $rules $maxapplyheight $maxapplydepth))
20
21;;  $MAXAPPLYDEPTH is the maximum depth within an expression to which
22;;  APPLYi will delve.  If $MAXAPPLYDEPTH is 0, it is applied only to
23;;  top level.
24(defmvar $maxapplydepth 10000.)
25
26;;  If $MAXAPPLYHEIGHT is 0, only atoms are affected by $APPLYB1 and
27;;  $APPLYB2.
28(defmvar $maxapplyheight 10000.)
29
30(defmvar matchreverse nil)
31
32(defmspec $disprule (l) (setq l (cdr l))
33    (if (and (eq (car l) '$all) (null (cdr l)))
34      (disprule1 (cdr $rules))
35      (disprule1 l)))
36
37(defun disprule1 (l)
38  `((mlist simp) ,@(loop for r in l collect (cadr ($ldisp (consrule r))))))
39
40(defun consrule (x)
41  (let ((rule (mget x '$rule)))
42    (if rule (list '(msetq simp) x (cons '(marrow simp) (cdr rule)))
43	(merror (intl:gettext "disprule: ~:M is not a user rule.") x))))
44
45(defmfun $remrule (op rule)
46  (prog (rules)
47     (setq op (getopr op))
48     (cond ((not (eq rule '$all))
49	    (removerule op rule) (return (getop op)))
50	   ((null (setq rules (mget op 'oldrules)))
51	    (merror (intl:gettext "remrule: no rules known for operator ~:@M") op)))
52     next (cond ((or (null rules) (null (cdr rules)))
53		 (mputprop op 1 'rulenum) (return (getop op)))
54		(t (removerule op (car rules))
55		   (setq rules (cdr rules)) (go next)))))
56
57(defun removerule (op rule)
58  (cond ((member rule *builtin-$rules* :test #'eq)
59	 (mget op 'oldrules))
60	(t
61	 (prog
62	     (oldrules old othrulename othrule)
63	    (setq oldrules (mget op 'oldrules))
64	    (cond ((or (null rule) (null (setq oldrules (member rule oldrules :test #'equal))))
65		   (merror (intl:gettext "remrule: no such rule: ~:M") rule))
66		  ((null (car (setq oldrules (cdr oldrules))))
67		   (setq oldrules (cdr oldrules))
68		   (setq othrulename nil)
69		   (setq othrule #'(lambda (a bb c) (declare (ignore bb)) (simpargs a c))))
70		  (t (setq othrulename (car oldrules))
71		     (setq othrule (cadr (getl (car oldrules) '(expr subr))))))
72	    (putprop-or-remprop rule othrule 'expr)
73	    (setq old (cdr (member rule (reverse (mget op 'oldrules)) :test #'equal)))
74	    (if old (putprop-or-remprop (car old)
75			     (subst othrulename rule (get (car old) 'expr))
76			     'expr))
77	    (if (boundp rule) (makunbound rule))
78	    (mremprop rule '$rule)
79	    (mremprop rule '$ruletype)
80	    (mremprop rule 'ruleof)
81	    (remprop rule 'expr)
82	    (setq $rules (delete rule $rules :count 1 :test #'eq))
83	    (putprop-or-remprop rule othrulename 'expr)
84	    (if (eq (get op 'operators) rule)
85		(putprop-or-remprop op othrulename 'operators))
86	    (let ((l (delete rule (mget op 'oldrules) :test #'eq)))
87		  (if (equal l '(nil)) (mremprop op 'oldrules) (mputprop op l 'oldrules))
88		  (return l))))))
89
90(defun putprop-or-remprop (x y z)
91  (if y
92    (putprop x y z)
93    (remprop x z)))
94
95(defun findbe (e)
96  (cond ((equal e 1) '(1 . 0))
97	((equal e 0) '(0 . 1))
98	((atom e) (cons e 1))
99	((eq (caar e) 'mexpt) (cons (cadr e) (caddr e)))
100	(t (cons e 1))))
101
102(defun findfun (e p c)
103  (prog ()
104     (cond ((and (null (atom e)) (eq (caar e) p)) (return e))
105	   ((or (atom e) (not (eq (caar e) c))) (matcherr))
106	   ((and (null matchreverse) (member c '(mplus mtimes) :test #'eq))
107	    (setq e (reverse (cdr e))) (go b)))
108     a    (setq e (cdr e))
109     b    (cond ((null e) (matcherr))
110		((and (not (atom (car e))) (eq (caaar e) p)) (return (car e))))
111     (go a)))
112
113(defun findexpon (e1 base* c)
114  (prog (e)
115     (setq e e1)
116     (cond ((and (mexptp e) (alike1 base* (cadr e)))
117	    (return (caddr e)))
118	   ((or (atom e) (not (eq (caar e) c))) (go c))
119	   ((and (null matchreverse) (member c '(mplus mtimes) :test #'eq))
120	    (setq e (reverse (cdr e))) (go b)))
121     a    (setq e (cdr e))
122     b    (cond ((null e) (go c))
123		((and (mexptp (car e)) (alike1 base* (cadar e)))
124		 (return (caddar e))))
125     (go a)
126     c    (cond ((or (and (not (atom e1)) (member c '(mplus mtimes) :test #'eq)
127			  (eq c (caar e1)) (memalike base* e1))
128		     (alike1 e1 base*)
129		     (and (not (atom base*)) (eq c (caar base*))))
130		 (return 1))
131		((eq c 'mexpt) (matcherr))
132		(t (return 0)))))
133
134(defun findbase (e expon c)
135  (prog ()
136     (cond ((equal expon 0)
137	    (if (and (eq c 'mexpt) (not (equal 1 e))) (matcherr))
138	    (return 1))
139	   ((equal expon 1) (return e))
140	   ((and (numberp expon) (> expon 0) (equal e 0))
141	    (return 0))
142	   ((and (mexptp e) (alike1 expon (caddr e)))
143	    (return (cadr e)))
144	   ((or (atom e) (not (eq (caar e) c))) (matcherr))
145	   ((and (null matchreverse) (member c '(mplus mtimes) :test #'eq))
146	    (setq e (reverse (cdr e))) (go b)))
147     a    (setq e (cdr e))
148     b    (cond ((null e)
149		 (return (if (and (realp expon) (minusp expon)) 1 0)))
150		((and (mexptp (car e)) (alike1 expon (caddar e)))
151		 (return (cadar e))))
152     (go a)))
153
154(defun part+ (e p preds)
155  (prog (flag saved val)
156     (if (not (mplusp e)) (matcherr))
157     (cond ((> (length p) (length preds))
158	    (setq p (reverse p))
159	    (setq p (nthkdr p (- (length p) (length preds))))
160	    (setq p (nreverse p))))
161     (setq e (copy-tree e)) ; PREVIOUSLY: (setq e ($ratexpand e))
162     (setq e (cdr e))
163     a    (cond ((null p) (cond ((null e) (return t)) (t (matcherr))))
164		((and (cdr preds) (member (car (caddar preds)) '(msetq setq) :test #'eq))
165		 (cond (flag (merror (intl:gettext "PART+: two or more pattern variables match anything.")))
166		       (t (setq flag t p (reverse p) preds (reverse preds))
167			  (go a))))
168		((not (atom (car p)))
169		 (prog (mye)
170		    (setq mye e)
171		    loop (cond ((null mye) (matcherr)))
172		    (setq val (catch 'match (mcall (car preds) (car mye))))
173		    (cond ((null val)
174			   (setq mye (cdr mye)) (go loop))
175			  (t (return (setq e (delete (car mye) e :count 1 :test #'equal))))))
176		 (go b))
177		(t (mset (car p) 0)))
178     (setq saved 0)
179     (mapc
180      #'(lambda (z)
181	  (cond ((null (setq val (catch 'match (mcall (car preds) z)))) nil)
182		(t (setq saved (add2* saved val))
183		   (setq e (delete z e :count 1 :test #'equal)))))
184      e)
185     (cond ((and (equal saved 0)
186		 (null (setq val (catch 'match (mcall (car preds) 0)))))
187	    (matcherr)))
188     (mset (car p) saved)
189     b (setq preds (cdr preds) p (cdr p))
190     (go a)))
191
192(defun part* (e p preds)
193  (prog (flag saved val)
194     (if (not (mtimesp e)) (matcherr))
195     (cond ((> (length p) (length preds))
196	    (setq p (reverse p))
197	    (setq p (nthkdr p (- (length p) (length preds))))
198	    (setq p (nreverse p))))
199     (setq e (copy-tree e)) ; PREVIOUSLY: (setq e ($factor e))
200     (setq e (cdr e))
201     a    (cond ((null p) (cond ((null e) (return t)) (t (matcherr))))
202		((and (cdr preds) (member (car (caddar preds)) '(msetq setq) :test #'eq))
203		 (cond (flag (merror (intl:gettext "PART*: two or more pattern variables match anything.")))
204		       (t (setq flag t p (reverse p) preds (reverse preds))
205			  (go a))))
206		((not (atom (car p)))
207		 (prog (mye)
208		    (setq mye e)
209		    loop (cond ((null mye) (matcherr)))
210		    (setq val (catch 'match (mcall (car preds) (car mye))))
211		    (cond ((null val)
212			   (setq mye (cdr mye)) (go loop))
213			  (t (return (setq e (delete (car mye) e :count 1 :test #'equal))))))
214		 (go b))
215		(t (mset (car p) 1)))
216     (setq saved 1)
217     (mapc
218      #'(lambda (z) (setq val (catch 'match (mcall (car preds) z)))
219		(cond ((null val) nil)
220		      (t (setq saved (mul2* saved val))
221			 (setq e (delete z e :count 1 :test #'equal)))))
222      e)
223     (cond ((and (equal saved 1)
224		 (null (setq val (catch 'match (mcall (car preds) 1)))))
225	    (matcherr)))
226     (mset (car p) saved)
227     b    (setq preds (cdr preds) p (cdr p))
228     (go a)))
229
230;;; TRANSLATE property in MAXSRC;TRANS5 >
231
232(defmspec $apply1 (l) (setq l (cdr l))
233	  (let ((expr (meval (car l))))
234	    (mapc #'(lambda (z) (setq expr (apply1 expr z 0))) (cdr l))
235	    expr))
236
237(defun apply1 (expr *rule depth)
238  (cond
239    ((> depth $maxapplydepth) expr)
240    (t
241     (prog nil
242	(*rulechk *rule)
243	(setq expr (rule-apply *rule expr))
244	b    (cond
245	       ((or (atom expr) (mnump expr)) (return expr))
246	       ((eq (caar expr) 'mrat)
247		(setq expr (ratdisrep expr)) (go b))
248	       (t
249		(return
250		  (simplifya
251		   (cons
252		    (delsimp (car expr))
253		    (mapcar #'(lambda (z) (apply1 z *rule (1+ depth)))
254			    (cdr expr)))
255		   t))))))))
256
257(defmspec $applyb1 (l)  (setq l (cdr l))
258	  (let ((expr (meval (car l))))
259	    (mapc #'(lambda (z) (setq expr (car (apply1hack expr z)))) (cdr l))
260	    expr))
261
262(defun apply1hack (expr *rule)
263  (prog (pairs max)
264     (*rulechk *rule)
265     (setq max 0)
266     b    (cond
267	    ((atom expr) (return (cons (multiple-value-bind (ans rule-hit) (mcall *rule expr) (if rule-hit ans expr)) 0)))
268	    ((specrepp expr) (setq expr (specdisrep expr)) (go b)))
269     (setq pairs (mapcar #'(lambda (z) (apply1hack z *rule))
270			 (cdr expr)))
271     (setq max 0)
272     (mapc #'(lambda (l) (setq max (max max (cdr l)))) pairs)
273     (setq expr (simplifya (cons (delsimp (car expr))
274				 (mapcar #'car pairs))
275			   t))
276     (cond ((= max $maxapplyheight) (return (cons expr max))))
277     (setq expr (rule-apply *rule expr))
278     (return (cons expr (1+ max)))))
279
280(defun *rulechk (*rule)
281  (if (and (symbolp *rule) (not (fboundp *rule)) (not (mfboundp *rule)))
282      (merror (intl:gettext "apply1: no such rule: ~:M") *rule)))
283
284(defun rule-apply (*rule expr)
285  (prog (ans rule-hit)
286   loop (multiple-value-setq (ans rule-hit) (mcall *rule expr))
287   (cond ((and rule-hit (not (alike1 ans expr)))
288	  (setq expr ans) (go loop)))
289   (return expr)))
290
291(defmspec $apply2 (l) (setq l (cdr l))
292	  (let ((rulelist (cdr l))) (apply2 rulelist (meval (car l)) 0)))
293
294(defun apply2 (rulelist expr depth)
295  (cond
296    ((> depth $maxapplydepth) expr)
297    (t
298     (prog (ans ruleptr rule-hit)
299      a    (setq ruleptr rulelist)
300      b    (cond
301	     ((null ruleptr)
302	      (cond
303		((atom expr) (return expr))
304		((eq (caar expr) 'mrat)
305		 (setq expr (ratdisrep expr)) (go b))
306		(t
307		 (return
308		   (simplifya
309		    (cons
310		     (delsimp (car expr))
311		     (mapcar #'(lambda (z) (apply2 rulelist z (1+ depth)))
312			     (cdr expr)))
313		    t))))))
314      (cond ((progn (multiple-value-setq (ans rule-hit) (mcall (car ruleptr) expr)) rule-hit)
315	     (setq expr ans)
316	     (go a))
317	    (t (setq ruleptr (cdr ruleptr)) (go b)))))))
318
319(defmspec $applyb2 (l) (setq l (cdr l))
320	  (let ((rulelist (cdr l))) (car (apply2hack rulelist (meval (car l))))))
321
322(defun apply2hack (rulelist e)
323  (prog (pairs max)
324     (setq max 0)
325     (cond ((atom e) (return (cons (apply2 rulelist e -1) 0)))
326	   ((specrepp e) (return (apply2hack rulelist (specdisrep e)))))
327     (setq pairs (mapcar #'(lambda (x) (apply2hack rulelist x)) (cdr e)))
328     (setq max 0)
329     (mapc #'(lambda (l) (setq max (max max (cdr l)))) pairs)
330     (setq e (simplifya (cons (delsimp (car e)) (mapcar #'car pairs)) t))
331     (cond ((= max $maxapplyheight) (return (cons e max)))
332	   (t (return (cons (apply2 rulelist e -1) (1+ max)))))))
333