share/tensor/itensor.lisp: make X and D shared lexical variables for the functions...
[maxima.git] / share / tensor / itensor.lisp
blobbfcea2d4b026c2a72154ac599b20217eff122f57
1 ;;; -*- Mode:LISP; Package:MACSYMA -*-
2 ;; ** (c) Copyright 1981 Massachusetts Institute of Technology **
3 ;;
4 ;; This program is free software; you can redistribute it and/or
5 ;; modify it under the terms of the GNU General Public License as
6 ;; published by the Free Software Foundation; either version 2 of
7 ;; the License, or (at your option) any later version.
8 ;;
9 ;; This program is distributed in the hope that it will be
10 ;; useful, but WITHOUT ANY WARRANTY; without even the implied
11 ;; warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
12 ;; PURPOSE. See the GNU General Public License for more details.
14 ;; Comments:
16 ;; The Itensor package was downcased, cleaned up, and moving frames
17 ;; functionality was added by Viktor Toth (https://www.vttoth.com/).
19 ;; As of November, 2004, the naming conventions in this package now
20 ;; correspond with the naming conventions in commercial MACSYMA.
23 (in-package :maxima)
25 (macsyma-module itensor) ;; added 9/24/82 at UCB
27 (cond (($get '$itensor '$version) (merror "ITENSOR already loaded"))
28 (t ($put '$itensor '$v20210714 '$version)))
30 ; Various functions in Itensor have been parceled out to separate files. A
31 ; function in one of these files will only be loaded in (automatically) if
32 ; explicitly used in the Maxima. (It is necessary to have first loaded in
33 ; ITENSOR FASL for this autoloading to take place.) The current status of
34 ; these separate files are:
36 ; Filename Macsyma Functions
37 ; -------- -----------------
38 ; CANTEN FASL CANTEN, CONCAN, IRPMON
39 ; GENER FASL IC_CONVERT, MAKEBOX, AVERAGE, CONMETDERIV, FLUSH1DERIV,
40 ; IGEODESIC_COORDS
41 ; SYMTRY FASL CANFORM, DECSYM, DISPSYM, REMSYM
43 (autof '$ic_convert '|gener|)
44 (autof '$decsym '|symtry|)
45 (autof '$canform '|symtry|)
46 (autof '$canten '|canten|)
47 (autof '$makebox '|gener|)
48 (autof '$igeodesic_coords '|gener|)
49 (autof '$conmetderiv '|gener|)
50 (autof '$name '|canten|)
52 (declare-top (special smlist $idummyx $vect_coords $imetric $icounter $dim
53 $contractions $coord $allsym $metricconvert $iframe_flag
54 $itorsion_flag $inonmet_flag))
56 (setq $idummyx '$% ;Prefix for dummy indices
57 $icounter 0. ;Dummy variable numeric index
58 smlist '(mlist simp) ;Simplified mlist header
59 $vect_coords nil ;Used when differentiating w.r.t. a number
60 $coord '((mlist simp)) ;Objects treated liked coordinates in diff
61 $allsym nil ;If T then all indexed objects symmetric
62 $metricconvert t ;Flag used by $ic_convert
63 $iframe_flag nil
64 $itorsion_flag nil)
66 (defmacro ifnot (&rest clause) `(or ,@ clause))
68 (defmacro m+or*or^p (&whole cl &rest ign)
69 (declare (ignore ign))
70 (subst (cadr cl)
72 '(member (caar x) '(mtimes mplus mexpt) :test #'eq)))
74 (defmfun $idummy () ;Sets arguments to dummy indices
75 (progn
76 (incf $icounter)
77 (intern (format nil "~a~d" $idummyx $icounter))))
79 (defprop $kdelta ((/ . / )) contractions)
81 (defun isprod (x)
82 (or (equal x '(mtimes)) (equal x '(mtimes simp))
83 (equal x '(mtimes simp ratsimp))))
85 ;; Remove occurrences of ratsimp from elements of x
86 (defun derat (x)
87 (cond
88 ((null x) nil)
89 ((atom x) x)
90 ((eq (car x) 'ratsimp) (derat (cdr x)))
91 (t (cons (derat (car x)) (derat (cdr x))))
95 (defun plusi(l)
96 (cond
97 ((null l) l)
98 ((and (numberp (car l)) (< (car l) 0)) (plusi (cdr l)))
99 ((atom (car l)) (cons (car l) (plusi (cdr l))))
100 ((and (isprod (caar l)) (eql (cadar l) -1)) (plusi (cdr l)))
101 (t (cons (car l) (plusi (cdr l))))
105 (defun minusi(l)
106 (cond
107 ((null l) l)
108 ((and (numberp (car l)) (< (car l) 0)) (cons (neg (car l)) (plusi (cdr l))))
109 ((atom (car l)) (minusi (cdr l)))
111 (and (isprod (caar l)) (eql (cadar l) -1))
112 (cons (caddar l) (minusi (cdr l)))
114 (t (minusi (cdr l)))
119 (defun covi (rp) (plusi (cdadr rp)))
120 (defun conti (rp) (append (minusi (cdadr rp)) (cdaddr rp)))
121 (defun deri (rp) (cdddr rp))
122 (defun name (rp) (caar rp))
123 (defmfun $covi (rp) (cond ((rpobj rp) (cons smlist (covi rp)))
124 (t (merror "Not an RPOBJ"))
127 (defmfun $conti (rp) (cond ((rpobj rp) (cons smlist (conti rp)))
128 (t (merror "Not an RPOBJ"))
131 (defmfun $deri (rp) (cond ((rpobj rp) (cons smlist (deri rp)))
132 (t (merror "Not an RPOBJ"))
135 (defmfun $name (rp) (cond ((rpobj rp) (caar rp)) (t (merror "Not an RPOBJ"))))
137 ;KDELTA has special contraction property because it contracts with any indexed
138 ;object.
140 (meval '(($declare) %kdelta $constant)) ;So derivative will be zero
141 (meval '(($declare) $kdelta $constant)) ;So derivative will be zero
142 (meval '(($declare) %levi_civita $constant))
143 (meval '(($declare) $levi_civita $constant))
145 (setq $dim 4. $contractions '((mlist simp)))
147 (defmfun $defcon n ;Defines contractions: A contracts with B to form C
148 ((lambda (a)
149 (add2lnc a $contractions)
150 (putprop
152 (cons (cond ((= n 1.) '(/ . / ))
153 ((= n 3.) (cons (arg 2.) (arg 3.)))
154 (t (merror "DEFCON takes 1 or 3 arguments")))
155 (zl-get a 'contractions))
156 'contractions)
157 '$done)
158 (arg 1.)))
160 (defmspec $dispcon (a) (setq a (cdr a))
161 ;;Displays contraction definitions
162 ((lambda (tmp)
163 (and (eq (car a) '$all) (setq a (cdr $contractions)))
164 (cons
165 smlist
166 (mapcar
167 #'(lambda (e)
168 (cond ((setq tmp (zl-get e 'contractions))
169 (cons smlist
170 (mapcar #'(lambda (z)
171 (cond ((eq (car z)
172 '/ )
173 (list smlist e))
174 (t (list smlist
176 (car z)
177 (cdr z)))))
178 tmp)))
179 (t '((mlist simp)))))
180 a)))
181 nil))
183 (defmspec $remcon (a) (setq a (cdr a))
184 ;;Removes contraction definitions
185 (and (eq (car a) '$all) (setq a (cdr $contractions)))
186 (cons smlist (mapc #'(lambda (e)
187 (zl-remprop e 'contractions)
188 (setq $contractions (delete e $contractions :test #'eq)))
189 a)))
191 ;; Helper to obtain contractions on both the noun and verb form of E
192 (defun getcon (e)
193 (if (and (symbolp e) (char= (get-first-char e) #\%))
194 (zl-get ($verbify e) 'contractions)
195 (zl-get e 'contractions)))
197 (defun rpobj (e) ;"True" if an indexed object and not a matrix
198 (cond ((and (not (atom e)) (eq (caar e) 'mqapply)) (rpobj (cdr e)))
200 (and (not (atom e))
201 (not (eq (caar e) '$matrix))
202 ($listp (cadr e))
203 (cond ((cddr e) ($listp (caddr e)))
204 (t (nconc e '(((mlist simp)))) t ))))))
205 ;Transforms F([...]) into F([...],[])
207 ;RPOBJ is the predicate for indexed objects. In the case of no contravariant
208 ;components, it tacks a null list on.
210 (deff $tenpr #'rpobj)
212 (defmfun $imetric (v) (setq $imetric v) ($defcon v) ($defcon v v '$kdelta))
214 (defun mysubst0 (new old) ;To reuse subparts of old expression
215 (cond ((alike1 new old) old) (t new)))
217 (defun cov (a b) ;COV gives covariant form of metric
218 (cond ((boundp '$imetric)
219 (meval (list (ncons $imetric)
220 (list smlist a b)
221 '((mlist simp)))))
222 (t (merror "Name of metric must be specified"))))
224 (defun contr (a b) ;contr gives contraviant form of metric
225 (cond ((boundp '$imetric)
226 (meval (list (ncons $imetric)
227 '((mlist simp))
228 (list smlist a b))))
229 (t (merror "Name of metric must be specified"))))
231 (defun diffcov (a b d)
232 (cond ((boundp '$imetric)
233 (meval (list (ncons $imetric)
234 (list smlist a b)
235 '((mlist simp))
240 (t (merror "Name of metric must be specified"))))
242 (defmfun $ichr1 nargs ; Christoffel-symbol of the first kind
243 (prog (a b c)
244 (cond
246 (> nargs 2) ; Derivative indices present; use idiff() to resolve
247 (return
248 (meval
249 (cons
250 '$idiff
251 (cons
252 ($ichr1 (arg 1) (arg 2))
253 (apply
254 #'append
255 (mapcar #'(lambda (e) (list e 1)) (cddr (listify nargs)))
263 (> nargs 1)
264 (and (eql 1 (length (arg 2))) (return ($ichr1 (arg 1))))
265 (merror "ichr1 cannot have contravariant indices")
267 (t ; G_abc = 1/2*(g_ba,c+g_ca,b-g_bc,a)
268 (setq a (cadddr (arg 1)) b (cadr (arg 1)) c (caddr (arg 1)))
269 (return
270 (list
271 '(mtimes)
272 '((rat simp) 1. 2.)
273 (list
274 '(mplus)
275 (diffcov b a c)
276 (diffcov c a b)
277 (list '(mtimes) -1. (diffcov b c a))
286 (defmfun $ichr2 nargs ; Christoffel-symbol of the second kind
287 (prog (a b c d)
288 (cond
290 (> nargs 2) ; Derivative indices present; use idiff() to resolve
291 (return
292 (meval
293 (cons
294 '$idiff
295 (cons
296 ($ichr2 (arg 1) (arg 2))
297 (apply
298 #'append
299 (mapcar #'(lambda (e) (list e 1)) (cddr (listify nargs)))
306 (t ; G_ab^c=g^cd*G_abd
307 (setq a (cadr (arg 1)) b (caddr (arg 1)) c (cadr (arg 2)))
308 (return
310 ((flag) (l (append (cdr (arg 1)) (cdr (arg 2)))))
311 (flag
312 (list '(mtimes) (contr c d) ($ichr1 (list smlist a b d)))
314 (setq d ($idummy))
315 (and (not (member d l :test #'eq)) (setq flag t))
323 (defmfun $icurvature (l1 l2)
324 (prog (i j k h r)
325 (setq r ($idummy) i (cadr l1) k (caddr l1) h (cadddr l1) j (cadr l2))
326 (return
327 (list
328 '(mplus)
329 (idiff (list (diffop) (list smlist i k) l2) h)
330 (list
331 '(mtimes) -1.
332 (idiff (list (diffop) (list smlist i h) (list smlist j)) k)
334 (list
335 '(mtimes)
336 (list (diffop) (list smlist i k) (list smlist r))
337 (list (diffop) (list smlist r h) l2)
339 (list
340 '(mtimes)
342 (list (diffop) (list smlist i h) (list smlist r))
343 (list (diffop) (list smlist r k) l2)
345 (cond
347 $iframe_flag
348 (list
349 '(mtimes) -1.
350 (list '($ifb) (list smlist k h) (list smlist r))
351 (list '($icc2) (list smlist r i) (list smlist j))
354 (t 0.)
361 (defun covsubst (x y rp) ;Substitutes X for Y in the covariant part of RP
362 (cons (car rp) (cons (subst x y ($covi rp)) (cons ($conti rp) (cdddr rp)))))
364 (defun consubst (x y rp) ;Substitutes X for Y in the contravariant part of RP
365 (cons (car rp)
366 (cons ($covi rp)
367 (cons (subst x y ($conti rp)) (cdddr rp)))))
369 (defun dersubst (x y rp) ;Substitutes X for Y in the derivative indices of RP
370 (nconc (list (car rp) (cadr rp) (caddr rp))
371 (subst x y (cdddr rp))))
373 ;; COVARIANT DIFFERENTIATION
374 ;; As of November, 2004, COVDIFF now takes into account the value of
375 ;; iframe_flag. If true, COVDIFF uses the coefficients icc2 in place
376 ;; of the Christoffel-symbols ichr2.
378 (defun diffop () ; ichr2 or icc2 depending on iframe_flag
379 (cond
381 (or $iframe_flag $itorsion_flag $inonmet_flag)
382 '($icc2 simp)
384 (t '($ichr2 simp))
388 (defmfun $idiff (&rest args)
389 (let (derivlist)
390 (ideriv args)))
392 (let (temp x d)
394 (defmfun $covdiff nargs
395 (prog
396 (e i)
397 (and (< nargs 2) (merror "COVDIFF must have at least 2 args"))
398 (setq temp nil d nil)
399 (setq i 2 e (arg 1))
400 again (setq x (arg i) e (covdiff e) i (1+ i))
401 (and (> i nargs) (return e))
402 (go again)
406 (defun covdiff (e) ; The covariant derivative...
407 (setq d ($idummy))
408 (cond
409 ( ; is the partial derivative for scalars (*** torsion?)
410 (or (atom e) (eq (caar e) 'rat))
411 (idiff e x)
414 (rpobj e)
415 (setq temp
416 (mapcar
417 #'(lambda (v)
418 (list '(mtimes)
419 (list (diffop) (list smlist d x) (list smlist v))
420 (consubst d v e)
423 (conti e)
426 (simplus
427 (cons
428 '(mplus)
429 (cons
430 (idiff e x)
431 (cond
433 (or (covi e) (cdddr e))
434 (cons (list '(mtimes) -1. (cons '(mplus)
435 (nconc
436 (mapcar
437 #'(lambda (v)
438 (list '(mtimes)
439 (list
440 (diffop)
441 (list smlist v x)
442 (list smlist d)
444 (covsubst d v e)
447 (covi e)
449 (mapcar
450 #'(lambda (v)
451 (list
452 '(mtimes)
453 (list
454 (diffop)
455 (list smlist v x)
456 (list smlist d)
458 (dersubst d v e)
461 (cdddr e)
466 temp
469 (t temp)
473 1. t
477 (eq (caar e) 'mtimes) ; (a*b)'
478 (simplus
479 (covdifftimes (cdr e) x)
484 (eq (caar e) 'mplus) ; (a+b)'=a'+b'
485 (simplifya
486 (cons
487 '(mplus)
488 (mapcar 'covdiff (cdr e))
494 (eq (caar e) 'mexpt) ; (a^b)'=b*a^(b-1)*a'
495 (simptimes
496 (list
497 '(mtimes)
498 (caddr e)
499 (list
500 '(mexpt)
501 (cadr e)
502 (list '(mplus) -1. (caddr e))
504 ($covdiff (cadr e) x)
506 1. nil
510 (eq (caar e) 'mequal)
511 (list (car e) (covdiff (cadr e)) (covdiff (caddr e)))
513 ((and (eq (caar e) '%determinant) (eq (cadr e) $imetric))
514 (cond ((or $iframe_flag $itorsion_flag $inonmet_flag)
515 (prog (d1 d2) (setq d1 ($idummy) d2 ($idummy))
516 (return (simptimes (list '(mtimes) e
517 (list (cons $imetric '(simp)) '((mlist simp)) (list '(mlist simp) d1 d2))
518 (cond ((position '$extdiff *mlambda-call-stack*) ; Special case, we're in extdiff()
519 ($idiff (list (cons $imetric '(simp)) (list '(mlist simp) d1 d2) '((mlist simp))) x))
520 (t ($covdiff (list (cons $imetric '(simp)) (list '(mlist simp) d1 d2) '((mlist simp))) x))
522 ) 1. t))
524 (t 0)
527 (t (merror "Not acceptable to COVDIFF: ~M" (ishow e)))
532 (defun covdifftimes (l x)
533 (prog (sp left out)
534 (setq out (ncons '(mplus)))
535 loop (setq sp (car l) l (cdr l))
536 (nconc out
537 (list
538 (simptimes
539 (cons '(mtimes) (cons ($covdiff sp x) (append left l)))
540 1. t
544 (cond ((null l) (return out)))
545 (setq left (nconc left (ncons sp)))
546 (go loop)
550 (declare-top (unspecial r))
552 (defun vecdiff (v i j d) ;Add frame bracket contribution when iframe_flag:true
553 (cond
555 $iframe_flag
556 (cons
557 '(mplus simp)
558 (list
559 (list (list v) '((mlist)) (list '(mlist) i) j)
560 (list
561 '(mtimes simp)
562 (list (list v) '((mlist)) (list '(mlist) d))
563 (list
564 '(mtimes simp)
566 (list '(%ifb) (list '(mlist) d j) (list '(mlist) i))
573 (list (list v) '((mlist)) (list '(mlist) i) j)
578 (defun liediff (v e n)
579 (cond
580 ((not (symbolp v)) (merror "~M is not a symbol" v))
582 (or (atom e) (eq (caar e) 'rat)) ; Scalar field
583 ; v([],[%1])*idiff(e,%1)
584 (let
585 ((dummy (implode (nconc (exploden $idummyx) (exploden n)))))
586 (list
587 '(mtimes) (list (list v) '((mlist)) (list '(mlist) dummy))
588 ($idiff e dummy)
593 (rpobj e) ; Tensor field
595 ; Dummy implementation for logic tests
596 ; (list '(%liediff) v e)
598 ; Shall the dummy index be in ICOUNTER sequence? Probably yes.
599 ; (let ((dummy (implode (nconc (exploden $idummyx) (exploden n)))))
600 (let
602 (dummy ($idummy))
603 (dummy2
604 (cond
605 ($iframe_flag ($idummy))
606 (t nil)
611 append
612 (list
613 '(mplus) 0
614 (list
615 '(mtimes) ; e([...],[...],%1)*v([],[%1])
616 (list (list v) '((mlist)) (list '(mlist) dummy))
617 ($idiff e dummy)
620 (maplist
621 #'(lambda (s) ; e([..%1..],[...])*v([],[%1],k)
622 (list
623 '(mtimes)
624 (cond ((atom (car s)) 1) (t -1))
625 (append
626 (list
627 (car e)
628 (cons
629 '(mlist)
630 (append
631 (subseq (cdadr e) 0 (- (length (cdadr e)) (length s)))
632 (cons
633 (cond ((atom (car s)) dummy)
634 (t (list '(mtimes simp) -1 dummy))
636 (cdr s)
640 (caddr e)
642 (cdddr e)
644 (vecdiff
646 (cond ((atom (car s)) dummy) (t (caddr (car s))))
647 (cond ((atom (car s)) (car s)) (t dummy))
648 dummy2
652 (cdadr e)
654 (maplist
655 #'(lambda (s) ; +e([...],[...],..%1..)*v([],[%1],k)
656 (list
657 '(mtimes)
658 (append
659 (list (car e) (cadr e) (caddr e))
660 (subseq (cdddr e) 0 (- (length (cdddr e)) (length s)))
661 (cons dummy (cdr s))
663 (vecdiff v dummy (car s) dummy2)
666 (cdddr e)
668 (maplist
669 #'(lambda (s) ; -e([...],[..%1..])*v([],[k],%1)
670 (list
671 '(mtimes) -1
672 (append
673 (list (car e) (cadr e)
674 (cons
675 '(mlist)
676 (append
677 (subseq (cdaddr e) 0 (- (length (cdaddr e)) (length s)))
678 (cons dummy (cdr s))
682 (cdddr e)
684 (vecdiff v (car s) dummy dummy2)
687 (cdaddr e)
693 (eq (caar e) 'mtimes) ; Leibniz rule
694 ; Lv(cadr e)*(cddr e)+(cadr e)*Lv(cddr e)
695 (list
696 '(mplus)
697 (cons '(mtimes) (cons (liediff v (cadr e) n) (cddr e)))
698 (cons
699 '(mtimes)
700 (list
701 (cadr e)
702 (liediff
704 (cond ((cdddr e) (cons '(mtimes) (cddr e))) (t (caddr e)))
712 (eq (caar e) 'mplus) ; Linearity
713 ; We prefer mapcar to iteration, but the recursive code also works
714 ; (list
715 ; '(mplus)
716 ; (liediff v (cadr e) n)
717 ; (liediff v (cond ((cdddr e) (cons '(mplus) (cddr e))) (t (caddr e))) n)
719 (cons '(mplus) (mapcar #'(lambda (u) (liediff v u n)) (cdr e)))
721 (t (merror "~M is not a tensorial expression liediff can handle" e))
725 (defmfun $liediff (v e) (liediff v e 1))
727 (defmfun $rediff (x) (meval '(($ev) x $idiff)))
729 (defmfun $undiff (x)
730 (cond
731 ((atom x) x)
733 (rpobj x)
734 (cond
736 (cdddr x)
737 (nconc
738 (list '(%idiff) (list (car x) (cadr x) (caddr x)))
739 (putinones (cdddr x))
742 (t x)
746 (mysubst0
747 (simplifya (cons (ncons (caar x)) (mapcar (symbol-function '$undiff) (cdr x))) t)
754 ;;(defmfun $evundiff (x) ($rediff ($undiff x)))
755 (defmfun $evundiff (x) (meval (list '($ev) ($undiff x) '$nouns)))
757 (defun putinones (e)
758 (cond
759 ((cdr e) (cons (car e) (cons 1. (putinones (cdr e)))))
760 (t (list (car e) 1.))
766 (defmfun $lorentz_gauge n
767 (cond ((equal n 0) (merror "LORENTZ_GAUGE requires at least one argument"))
768 ((equal n 1) (lorentz (arg 1) nil))
769 (t (lorentz (arg 1)
770 ((lambda (l) (cond ((loop for v in l
771 always (symbolp v)) l)
772 (t (merror
773 "Invalid tensor name(s) in argument to LORENTZ_GAUGE"))))
774 (listify (f- 1 n)))))))
776 ;Lorentz contraction of E: indexed objects with a derivative index matching a
777 ;contravariant index become 0. If L is NIL then do this for all indexed objects
778 ;otherwise do this only for those indexed objects whose names are members of L.
780 (defun lorentz (e l)
781 (cond ((atom e) e)
782 ((rpobj e)
783 (cond ((and (or (null l) (member (caar e) l :test #'eq))
784 (intersect (cdaddr e) (cdddr e)))
786 (t e)))
787 (t (mysubst0
788 (simplifya
789 (cons (ncons (caar e))
790 (mapcar (function (lambda (q) (lorentz q l)))
791 (cdr e)))
792 t) e))))
794 (defun less (x y) ;alphanumeric compare
795 (cond ((numberp x)
796 (cond ((numberp y) (< x y))
797 (t (alphalessp (ascii x) y))))
798 (t (cond ((numberp y) (alphalessp x (ascii y)))
799 (t (alphalessp x y))))))
801 ;; Christoffels contains all Christoffel-like symbols: i.e., symbols
802 ;; that make sense only with certain index patterns. These symbols are
803 ;; excluded from contractions, because those would produce illegal
804 ;; index combinations (e.g., ichr1([a,b],[c])). However, special rules
805 ;; exist to convert a covariant symbol into a mixed symbol and vice
806 ;; versa; for instance, g^ad*ichr1_bcd will contract to ichr2_bc^a.
807 (declare-top (special christoffels christoffels1 christoffels2))
809 (setq christoffels1 '($ichr1 %ichr1 $icc1 %icc1 $ifc1 %ifc1
810 $inmc1 %inmc1 $ikt1 %ikt1))
811 (setq christoffels2 '($ichr2 %ichr2 $icc2 %icc2 $ifc2 %ifc2
812 $inmc2 %inmc2 $ikt2 %ikt2))
813 (setq christoffels (append christoffels1 christoffels2 '(%ifb $ifb %itr $itr)))
815 ;; Main contraction function
816 (defmfun $contract (e)
817 (cond
818 ((atom e) e)
819 ((rpobj e) (contract5 e))
821 (eq (caar e) 'mtimes)
822 (mysubst0 (simplifya (cons '(mtimes) (contract4a e)) nil) e)
825 (eq (caar e) 'mplus)
826 (mysubst0 (simplus (cons '(mplus) (mapcar (symbol-function '$contract) (cdr e))) 1. t) e)
829 (mysubst0 (simplifya (cons (car e) (mapcar (symbol-function '$contract) (cdr e))) nil) e)
834 (defun contract4a (e)
835 (prog (l1 l2)
836 (setq l1 nil l2 nil)
837 (dolist (o (cdr e))
838 (cond
839 ((or (atom o) (atom (car o))) (setq l1 (cons o l1)))
841 (and (eq (caar o) 'mexpt) (eql (caddr o) -1))
842 (setq l2 (cons (cadr o) l2))
844 (t (setq l1 (cons o l1)))
847 (cond (l1 (setq l1 (contract4 (cons '(mtimes) l1)))))
848 (cond (l2 (setq l1 (cons (list '(mexpt)
849 (cons '(mtimes)
850 (contract4 (cons '(mtimes) l2))
855 ))))
856 (return l1)
860 ;; Contract a single tensor with itself
861 (defun contract5 (e)
862 (prog
863 ( ; See if e contracts with itself, find contraction symbol
864 (c (or (and (rpobj e) (getcon (caar e))) (return e)))
866 symbol
869 (c (getcon (caar e)) (cdr c))
871 ((or (eq (caar c) (caar e)) (null c)) (cond (c (cdar c)) (t nil)) )
875 (return
876 (cond
877 ((or (null symbol) (member (caar e) christoffels :test #'eq)) e)
880 (prog (cov con f sgn)
881 (setq sgn (cond ((rpobj ($canform e)) 1) (t -1))
882 cov (contractinside (derat (cadr e)))
883 con (derat (caddr e))
884 f (not (equal cov (derat (cadr e))))
886 ; Calling contract2 here won't do the trick as it messes up the
887 ; order of indices. So we remove indices that appear both in cov
888 ; and in con the hard way, with a do loop.
890 ((i cov (cdr i)))
891 ((null i))
892 (cond
893 ((not (atom (car i))))
895 (member (car i) con)
896 (setq f t con (delete (car i) con) cov (delete (car i) cov))
900 (setq c
901 (nconc
902 (list (cond (f (list symbol)) (t (car e))) cov con)
903 (cdddr e)
906 (return (cond ((and f (eql sgn -1)) (list '(mtimes) sgn c)) (t c)))
914 (defun head (x) (cond ((atom x) nil) (t (cons (car x) nil))))
916 (defun firstintersect (l1 l2) (head (intersect l1 l2)))
918 ;; Remove like members. Return (cons l1 l2) or nil if no like members found.
919 (defun contract2 (l1 l2)
921 (lambda (i) (and i (cons (setdiff l1 i) (setdiff l2 i))))
922 (firstintersect l1 l2)
926 ;; Return a list with those members of s1 that are not in s2
927 (defun setdiff (s1 s2)
929 ((j s1 (cdr j)) (a))
930 ((null j) (reverse a))
932 (and (not (numberp (car j))) (member (car j) s2 :test #'eq))
933 (setq a (cons (car j) a))
938 (defun contract3 (it lst) ;Tries to contract IT with some element of LST.
939 (prog (frst r rest) ;If none occurs then return NIL otherwise return
940 ;a list whose first member is the result of
941 ;contraction and whose cdr is a top-level copy
942 ;of LST with the element which contracted
943 ;removed.
944 loop (setq frst (car lst) lst (cdr lst))
945 ;; (and (eq (caar frst) '%kdelta) (go skip))
946 (and (setq r (contract1 it frst))
947 (return (cons r (nconc (nreverse rest) lst))))
948 ;Try contraction in reverse order since the
949 ;operation is commutative.
950 ;; skip (and (zl-get (caar frst) 'contractions)
951 skip (and (getcon (caar frst))
952 (setq r (contract1 frst it))
953 (return (cons r (nconc (nreverse rest) lst))))
954 (and (null lst) (return nil))
955 (setq rest (cons frst rest))
956 (go loop)))
958 (defun contract4 (l) ;contracts products
959 (prog (l1 l2 l3 f cl sf)
960 (setq cl (cdr l)) ;Following loop sets up 3 lists from the factors
961 ;on L: L1 - atoms or the contraction of non
962 ;indexed objects (the contraction is to handle
963 ;sub-expressions in case E is not fully expanded
964 ;as in A*B*(C*D+E*F). ), L2 - indexed objects in
965 ;L with contraction property, L3 - indexed
966 ;objects in L without contraction property
967 again(setq f (car cl) cl (cdr cl))
968 (cond ((atom f) (setq l1 (cons f l1)))
969 ((rpobj f)
970 ;;*** contract5 may return a negative result
971 (setq f (contract5 f))
972 (cond (
973 (and (or (eq (car f) '(mtimes)) (eq (car f) '(mtimes simp))) (eql (cadr f) -1))
974 (setq l1 (cons -1 l1) f (caddr f)) ))
975 (cond ((getcon (caar f))
976 (setq l2 (cons f l2)))
977 (t (setq l3 (cons f l3)))))
978 (t (setq l1 (cons ($contract f) l1))))
979 (and cl (go again))
980 (and (null l2) (return (nconc l1 l3)))
981 (and (null (cdr l2)) (setq cl l2) (go loop2+1))
982 ;If L2 is empty then no more contractions are
983 ;needed. If L2 has only 1 member then just
984 ;contract it with L3 otherwise contract the
985 ;members of L2 with themselves. The following
986 ;loop goes down L2 trying to contract members
987 ;with other members according to the following
988 ;method: moving from front to end take current
989 ;member (F) and see if it contracts with any
990 ;elements in the rest of the list (this is done
991 ;by CONTRACT3). If it doesn't then add it to CL.
992 ;If it does then take result of contraction and
993 ;add to L1, L2, or L3 as above.
994 loop1(setq f (car l2) l2 (cdr l2))
995 (cond ((null (setq sf (contract3 f l2)))
996 (setq cl (cons f cl)))
998 ;;*** contract3 may also return a negative result
999 (setq sf (mapcar #'(lambda (x)
1000 (cond ((atom x) x) (
1001 (and (or (equal (car x) '(mtimes)) (equal (car x) '(mtimes simp))) (eql (cadr x) -1))
1002 (setq l1 (cons -1 l1)) (caddr x)) (t x))
1003 ) sf ) )
1005 (setq l2 (cdr sf) sf (car sf))
1006 (cond ((atom sf) (setq l1 (cons sf l1)))
1007 ((rpobj sf)
1008 ;; (cond ((zl-get (caar sf)
1009 ;; 'contractions)
1010 (cond ((getcon (caar sf))
1011 (setq l2 (cons sf l2)))
1012 (t (setq l3 (cons sf l3)))))
1013 (t (setq l1 (cons sf l1))))))
1014 ;If L2 has at least 2 elements left then
1015 ;continue loop. If L2 has 1 element and CL
1016 ;is not empty and there were some contractions
1017 ;performed last time then add CL to L2 and try
1018 ;again. Otherwise add L2 to CL and quit.
1019 (and l2
1020 (cond ((cdr l2) (go loop1))
1021 ((and cl sf)
1022 (setq sf nil l2 (cons (car l2) cl) cl nil)
1023 (go loop1))
1024 (t (setq cl (nconc l2 cl)))))
1025 ;The following loop goes down CL trying to
1026 ;contract each member with some member in L3. If
1027 ;there is not a contraction then the element
1028 ;from CL is added onto L3 (this causes elements
1029 ;of CL to be contracted with each other). If
1030 ;there is a contraction then the result is added
1031 ;onto L3 by setting L3 to the result of
1032 ;CONTRACT3 here if CL is known not to be null.
1033 ;If L3 is empty then there is nothing left to
1034 ;contract.
1035 loop2(and (null cl) (return (nconc l1 l3)))
1036 loop2+1
1037 (and (null l3) (return (nconc l1 cl)))
1038 (setq f (car cl) cl (cdr cl))
1039 (cond ((setq sf (contract3 f l3))
1040 ;;*** contract3 may also return a negative result
1041 (setq sf (mapcar #'(lambda (x)
1042 (cond ((atom x) x) (
1043 (and (or (equal (car x) '(mtimes)) (equal (car x) '(mtimes simp))) (eql (cadr x) -1))
1044 (setq l1 (cons -1 l1)) (caddr x)) (t x))
1045 ) sf ) )
1047 (setq l3 sf))
1048 (t (setq l3 (cons f l3))))
1049 (go loop2)))
1051 ;; Create a 'normalized' (i.e., old-style) rpobj
1052 (defmfun $renorm (e &optional (force nil))
1053 (prog (c v)
1054 (and (not (rpobj e)) (merror "Not an RPOBJ: ~M" e))
1055 (and $allsym (setq force t))
1056 (setq c (cdaddr e) v nil)
1058 ((i (reverse (cdadr e)) (cdr i)))
1060 (or (null i) (and (atom (car i)) (not force))) ; Terminating condition
1061 (setq v (append (reverse i) v)) ; Remaining covariant indices
1063 (cond
1064 ((atom (car i)) (setq v (cons (car i) v)))
1065 (t (setq c (cons (caddar i) c)))
1068 (return
1069 (cons (car e) (append (list (cons smlist v) (cons smlist c)) (cdddr e)))
1074 ;; As above, but unconditionally. Not needed.
1075 ;(defun renorm (e) (append (list (car e) ($covi e) ($conti e)) (cdddr e)))
1077 ;; Add a minus sign to all elements in a list
1078 (defun neglist (l)
1079 (cond ((null l) nil)
1080 (t (cons (list '(mtimes simp) -1 (car l)) (neglist (cdr l))))
1084 ;; Create an 'abnormal' (i.e., new-style) rpobj
1085 (defun abnorm (e)
1086 (append (list (car e)
1087 (append ($covi e) (neglist (conti e)))
1088 '((mlist simp)))
1089 (cdddr e)
1093 ;; Substitute using EQUAL, to catch member lists
1094 (defun substlist (b a l)
1095 (cond ((null l) l)
1096 ((equal a (car l)) (cons b (cdr l)))
1097 (t (cons (car l) (substlist b a (cdr l))))
1101 ;; Removes items not in i from l.
1102 (defun removenotin (i l)
1103 (cond ((null l) l)
1104 ((member (car l) i :test #'eq) (cons (car l) (removenotin i (cdr l))))
1105 (t (removenotin i (cdr l)))
1109 ;; Removes items not in i from l. But the ones in l have a minus sign!
1110 (defun removenotinm (i l)
1111 (cond ((null l) l)
1112 ((atom (car l)) (cons (car l) (removenotinm i (cdr l))))
1113 ((and (isprod (caar l)) (eql (cadar l) -1)
1114 (not (member (caddar l) i :test #'eq))) (removenotinm i (cdr l)))
1115 (t (cons (car l) (removenotinm i (cdr l))))
1119 ;; Removes indices duplicated once with and once without a minus sign
1120 (defun contractinside (c)
1122 ((i (minusi c) (cdr i)))
1123 ((null i))
1124 (and (member (car i) c :test #'equal)
1125 (member (list '(mtimes simp) -1 (car i)) c :test #'equal)
1126 (setq c (delete (car i) (delete (list '(mtimes simp) -1 (car i)) c :test #'equal)))
1132 ;; This does the actual contraction of f with g. If f has any derivative
1133 ;; indices then it can't contract g. If f is Kronecker delta then see which of
1134 ;; the covariant, contravariant, or derivative indices matches those in g.
1135 (defun contract1 (f g)
1136 (prog (a b c d e cf sgn)
1137 (when (cdddr f) (return nil))
1138 (setq a (copy-tree (derat (cdadr f))) b (copy-tree (cdaddr f))
1139 c (copy-tree (derat (cadr g))) d (copy-tree (caddr g)) e (copy-tree (cdddr g))
1141 (cond ; This section is all Kronecker-delta code
1143 (or (eq (caar f) '%kdelta) (eq (caar f) '$kdelta))
1145 ; We normalize the indices first
1146 (setq b (append (minusi a) b) a (plusi a))
1148 ;We cannot contract with higher-order or malformed Kronecker deltas
1149 (and (or (/= (length a) 1) (/= (length b) 1 )) (return nil))
1151 (setq a (car a) b (car b))
1152 (return
1153 (simplifya
1154 (cond
1156 (and (cdr c) (not (numberp b)) (member b (cdr c) :test #'eq))
1157 (setq c (subst a b (cdr c)))
1158 (and
1159 (not (member (caar g) christoffels :test #'eq))
1160 (cdr d)
1161 (setq a (contract2 c (cdr d)))
1162 (setq c (car a) d (cons smlist (cdr a)))
1164 (setq c (contractinside c))
1165 (nconc (list (car g) (cons smlist c) d) e)
1168 (and e (not (numberp b)) (member b e :test #'eq))
1169 (nconc (list (car g) c d)
1170 (cond
1171 ($iframe_flag (subst a b e))
1172 (t (itensor-sort (subst a b e)))
1177 (and (cdr d) (not (numberp a)) (member a (cdr d) :test #'eq))
1178 (setq d (subst b a (cdr d)))
1179 (and
1180 (cdr c)
1181 (setq a (contract2 (cdr c) d))
1182 (setq d (cdr a) c (cons smlist (car a)))
1184 (nconc (list (car g) c (cons smlist d)) e)
1187 (and (cdr c) (not (numberp a))
1188 (member (list '(mtimes simp) -1 a) (cdr c) :test #'equal)
1190 (setq c (substlist (list '(mtimes simp) -1 b)
1191 (list '(mtimes simp) -1 a)
1192 (cdr c)
1195 (setq c (contractinside c))
1196 (nconc (list (car g) (cons smlist c) d) e)
1198 (t nil)
1206 ;No tensor can contract Kronecker-deltas, Levi-Civita symbols, or the torsion tensor.
1207 (and
1208 (or (eq (caar g) '$kdelta) (eq (caar g) '%kdelta)
1209 (eq (caar g) '$levi_civita) (eq (caar g) '%levi_civita)
1210 (eq (caar g) '$icurvature) (eq (caar g) '%icurvature)
1211 (eq (caar g) '$itr) (eq (caar g) '%itr)
1213 (return nil)
1216 ;If g has derivative indices then F must be constant in order to contract it
1217 (and e (not (kindp (caar f) '$constant)) (return nil))
1219 ;Contraction property of f is a list of (a.b)'s
1220 (cond
1221 ((setq cf (getcon (caar f))))
1222 (t (return nil))
1225 ; Determine the sign of the result based on the expression's symmetry
1226 ; properties. We use CANFORM to sort indices in the canonical order
1227 ; and then extract the resulting expression's sign.
1228 (setq sgn
1229 (cond ((eql -1 (cadr ($canform (list '(mtimes simp) f g)))) -1) (t 1))
1232 ;If g matches an a then use the b for name of result. If an a is a space
1233 ;use name of G for result.
1234 more
1235 (cond
1237 (eq (caar cf) '/ )
1238 (setq cf (car g))
1241 (eq (caar cf) (caar g))
1242 (setq cf (ncons (cdar cf)))
1245 (or (setq cf (cdr cf)) (return nil))
1246 (go more)
1249 (setq c (cdr c) d (cdr d))
1251 ;If CONTRACT2 of f's contravariant and g's covariant or f's covariant and
1252 ;g's contravariant indices is nil then return nil
1253 (cond
1255 (and b c (setq f (contract2 b c)))
1256 (setq b (car f) c (cdr f))
1259 (and a d (setq f (contract2 a d)))
1260 (setq a (car f) d (cdr f))
1263 (and a (minusi c) (setq f (contract2 a (minusi c))))
1264 ; (cdr f) now contains the free indices in (minusi c).
1265 ; what we need to do is find the corresponding items in c, and remove
1266 ; all other negative indices (i.e., those that were dropped by
1267 ; contract2).
1268 ; What we need to do is remove items from c one by one, and substitute
1269 ; an item from (car f), which we should remove from (car f):
1270 ; for i thru length(c)
1271 ; if c[i] not in (cdr f)
1272 ; if (car f) is nil, remove c[i]
1273 ; otherwise subst c[i]
1274 ; endfor
1275 ; Now set c to what we made of c, a to whatever is left of (cdr f)
1279 (i c (cdr i))
1280 (j (car f))
1283 ((null i) (setq a (removenotin j a) c (reverse k)))
1284 (cond
1286 (or (atom (car i)) (member (caddar i) (cdr f)))
1287 (setq k (cons (car i) k))
1290 (not (null j))
1291 (setq k (cons (car j) k) j (cdr j))
1297 (and (minusi a) c (setq f (contract2 (minusi a) c)))
1300 (i c (cdr i))
1301 (j (car f))
1304 ;; ((null i) (setq c (reverse k) a (append (plusi a) j)))
1305 ((null i)
1306 (setq
1307 c (reverse k)
1308 a (append
1309 (plusi a)
1310 (mapcar #'(lambda (x) (list '(mtimes simp) -1 x)) j)
1314 (cond
1315 ((member (car i) (cdr f)) (setq k (cons (car i) k)))
1317 (not (null j))
1318 (setq k (cons (list '(mtimes simp) -1 (car j)) k) j (cdr j))
1323 (t (return nil))
1325 ;Form combined indices of result
1326 (and d (setq b (append b d)))
1327 (and c (setq a (append c a)))
1328 ;Zl-remove repeated indices
1329 ;; (and (setq f (contract2 a b)) (setq a (car f) b (cdr f)))
1330 ;; (setq a (contractinside a))
1332 ;VTT: Special handling of Christoffel symbols. We can only contract them
1333 ;when we turn ICHR1 into ICHR2 or vice versa; other index combinations are
1334 ;illegal. This code checks if the index pattern is a valid one and replaces
1335 ;ICHR1 with ICHR2 or vice versa as appropriate.
1336 (cond
1338 (member (car cf) christoffels1)
1339 (cond
1340 ; VTT - before anything else, check that we're contracting on the last index only
1341 ((not (equal (append c (last (cdadr g))) (cdadr g))) (return nil))
1343 ;;(and (eql (length a) 2) (eql (length b) 1))
1344 (and (eql (+ (length (plusi a)) (length (minusi b))) 2) (eql (+ (length (plusi b)) (length (minusi a))) 1))
1345 (setq cf
1346 (cons
1347 (elt christoffels2 (position (car cf) christoffels1))
1348 (cdr cf)
1353 ;; (not (and (eql (length a) 3) (eql (length b) 0)))
1354 (not (and (eql (+ (length (plusi a)) (length (minusi b))) 3) (eql (+ (length (plusi b)) (length (minusi a))) 0)))
1355 (return nil)
1360 (member (car cf) christoffels2)
1361 (cond
1363 ;;(and (eql (length a) 3) (eql (length b) 0))
1364 (and (eql (+ (length (plusi a)) (length (minusi b))) 3) (eql (+ (length (plusi b)) (length (minusi a))) 0))
1365 (setq cf
1366 (cons
1367 (elt christoffels1 (position (car cf) christoffels2))
1368 (cdr cf)
1373 ;;(not (and (eql (length a) 2) (eql (length b) 1)))
1374 (not (and (eql (+ (length (plusi a)) (length (minusi b))) 2) (eql (+ (length (plusi b)) (length (minusi a))) 1)))
1375 (return nil)
1379 ((member (car cf) christoffels) (return nil))
1382 (setq f (meval (list cf (cons smlist a) (cons smlist b))))
1383 (and e
1385 ((e e (cdr e)))
1386 ((null e))
1387 (setq f (idiff f (car e)))
1390 (return (cond ((eql sgn -1) (list '(mtimes) sgn f)) (t f)))
1394 ;; In what amounts to quite an abuse of the Kronecker delta concept, we
1395 ;; permit an exceptional index combination of two contravariant indices.
1396 ;; This helps lc2kdt convert Levi-Civita symbols in a manner that does
1397 ;; not require resorting to numeric indices, causing all sorts of problems
1398 ;; with RENAME and CONTRACT.
1399 (defmfun $kdelta (l1 l2)
1400 (setq l2 (append l2 (minusi l1)) l1 (plusi l1))
1401 (cond
1403 (and ($listp l1) ($listp l2) (= ($length l1) 0) (= ($length l2) 2))
1404 (cond
1405 ((eq (cadr l2) (caddr l2)) 1)
1407 (and (numberp (cadr l2)) (numberp (caddr l2)))
1408 (cond
1409 ((= (cadr l2) (caddr l2)) t)
1410 (t 0)
1413 (t (list '(%kdelta) l1 l2))
1417 (and ($listp l1) ($listp l2) (= ($length l1) 2) (= ($length l2) 0))
1418 (cond
1419 ((eq (cadr l1) (caddr l1)) 1)
1421 (and (numberp (cadr l1)) (numberp (caddr l1)))
1422 (cond
1423 ((= (cadr l1) (caddr l1)) t)
1424 (t 0)
1427 (t (list '(%kdelta) l1 l2))
1431 (null (and ($listp l1) ($listp l2) (= (length l1) (length l2))))
1432 (merror "Improper arg to DELTA: ~M" (list '(%kdelta) l1 l2))
1434 (t (delta (cdr l1) (cdr l2)))
1438 ;kdels defines the symmetric combination of the Kronecker symbols
1440 (defmfun $kdels (l1 l2)
1441 (cond ((null (and ($listp l1)
1442 ($listp l2)
1443 (= (length l1) (length l2))))
1444 (merror "Improper arg to DELTA: ~M"
1445 (list '(%kdels) l1 l2)
1447 (t (delta (cdr l1) (cdr l2) 1))))
1449 (defun delta (lower upper &optional (eps -1))
1450 (cond ((null lower) $dim)
1451 ((null (cdr lower))
1452 (cond ((equal (car upper) (car lower))
1453 (cond ((numberp (car upper)) 1.) (t $dim)))
1454 ((and (numberp (car upper)) (numberp (car lower))) 0.)
1455 (t (list '(%kdelta) (cons smlist lower) (cons smlist upper)))))
1456 (t (do ((left nil (append left (ncons (car right))))
1457 (right lower (cdr right))
1458 (result))
1459 ((null right) (simplus (cons '(mplus) result) 1. t))
1460 (setq result (cons (simptimes
1461 (list '(mtimes) (delta (ncons (car right)) (ncons (car upper)) eps)
1462 (delta (append left (cdr right)) (cdr upper) eps)
1463 (cond ((oddp (length left)) eps) (t 1))
1464 ) 1. t
1465 ) result)
1466 )))))
1468 (declare-top (special $outchar $dispflag *linelabel* foobar derivlist))
1471 ;Displays P([L1],[L2],I1,I2,...) by making the elements of L2 into a single
1472 ;atom which serves as the exponent and the elements of L1 and I1,I2,... into a
1473 ;single atom with a comma in between which serves as the subscript.
1475 (defmfun $ishow (f)
1476 (progn (makelabel $linechar)
1477 (cond ($dispflag
1478 (displa (list '(mlabel) *linelabel* (ishow (specrepcheck (derat f)))))
1479 ; (setq $dispflag nil)
1481 (set *linelabel* f)))
1483 (defun ishow (f)
1484 ((lambda (foobar) ;FOOBAR initialized to NIL
1485 (cond ((atom f) f)
1486 ((rpobj f) ;If an indexed object ...
1487 (setq foobar
1488 (cond ((or (covi f) (cdddr f)) ;If covariant or
1489 (cons (list (caar f) ;derivative indices
1490 'array)
1491 (ncons (maknam (cons '$ (splice (covi f)
1492 (cdddr f)))))))
1493 (t (caar f))))
1494 (cond ((conti f) ;If contravariant indices
1495 (list '(mexpt simp)
1496 foobar
1497 ; (cons '(mtimes simp) ;Make indices appear
1498 ; (conti f)))) ;as exponents for
1499 (maknam (cons '$ (splice (conti f) nil))))) ; Changed for wxmaxima
1500 (t foobar))) ;proper display
1502 (cons (car f) (mapcar 'ishow (cdr f))))))
1503 nil)) ;Map onto subparts of F
1505 (defun splice (l1 l2)
1506 (cond (l2 (setq l2 (cons '|,| (splice1 l2)))
1507 (and l1 (setq l2 (nconc (splice1 l1) l2)))
1509 (t (splice1 l1))))
1511 (defun splice1 (l)
1512 (cond ((null (cdr l))(splice2 (car l)))
1513 (t (nconc (splice2 (car l))(cons '| | (splice1 (cdr l)))))))
1515 (defun splice2 (x)
1516 (cond ((fixnump x)(explode x))
1517 (t (cdr (explodec x)))))
1518 ; (t (cdr (explodec (print-invert-case x))))))
1520 (defun deriv (e)
1521 (prog (exp z count v)
1522 (cond ((null (cdr e)) (return (stotaldiff (car e))))
1523 ((null (cddr e)) (nconc e '(1.))))
1524 (setq exp (car e) z (setq e (append e nil)))
1525 loop (cond ((or (null derivlist) (member (cadr z) derivlist :test #'equal))
1526 (go doit)))
1527 ;DERIVLIST is set by $EV
1528 (setq z (cdr z))
1529 loop2(cond ((cdr z) (go loop))
1530 ((null (cdr e)) (return exp))
1531 (t (go noun)))
1532 doit (cond ((null (cddr z))
1533 (merror "Wrong number of args to DERIVATIVE"))
1534 ((not (fixnump (setq count (caddr z)))) (go noun))
1535 ((< count 0.)
1536 (merror "Improper count to DIFF: ~M"
1537 count)))
1538 loop1(setq v (cadr z))
1539 (and (fixnump v)
1540 $vect_coords
1541 (> v 0.)
1542 (not (> v $dim))
1543 (setq v
1544 (cond ((atom $vect_coords)
1545 (meval1 (list (list $vect_coords 'simp 'array)
1546 v)))
1547 ((eq (caar $vect_coords) 'mlist)
1548 (cond ((not (< v
1549 (length $vect_coords)))
1550 (merror
1551 "Coordinate list too short for derivative index"))
1552 (t (nth v $vect_coords))))
1553 (t v))))
1554 (cond ((zerop count) (rplacd z (cdddr z)) (go loop2))
1555 ((zerop1 (setq exp (sdiff exp v))) (return 0.)))
1556 (setq count (1- count))
1557 (go loop1)
1558 noun (return (diff%deriv (cons exp (cdr e))))))
1560 (defun chainrule1 (e x) ; --ys 15.02.02
1561 (prog (y)
1562 (cond ((and (atom e) (eq (setq y (car (mget e 'depends)))
1563 (cadr $coord))) (return (subst x y (chainrule e y))))
1564 (t (return (chainrule e x))))))
1566 (defun diffexpt1 (e x)
1567 ;; RETURN: n*v^n*rename(v'/v) where e=v^n
1568 (list '(mtimes) (caddr e) e
1569 ($rename
1570 (list '(mtimes) (list '(mexpt) (cadr e) -1)
1571 (sdiff (cadr e) x)
1577 ;Redefined so that the derivative of any indexed object appends on the
1578 ;coordinate index in sorted order unless the indexed object was declared
1579 ;constant in which case 0 is returned.
1580 (defun sdiff (e x)
1581 (simplifya
1582 (cond ((mnump e) 0.)
1583 ((and (alike1 e x) (not (and (rpobj e) (rpobj x)))) 1.)
1584 ((or (atom e) (member 'array (cdar e) :test #'eq))
1585 (chainrule1 e x))
1586 ((kindp (caar e) '$constant) 0.) ;New line added
1587 ((eq (caar e) 'mrat) (ratdx e x))
1588 ((eq (caar e) 'mplus)
1589 (simplus (cons '(mplus) (sdiffmap (cdr e) x))
1592 ((eq (caar e) 'mequal)
1593 (list (car e) (sdiff (cadr e) x) (sdiff (caddr e) x)))
1594 ((mbagp e) (cons (car e) (sdiffmap (cdr e) x)))
1595 ((eq (caar e) '$matrix)
1596 (cons (car e)
1597 (mapcar
1598 (function (lambda (y)
1599 (cons (car y)
1600 (sdiffmap (cdr y) x))))
1601 (cdr e))))
1602 ((eq (caar e) 'mtimes)
1603 (addn (sdifftimes (cdr e) x) t))
1604 ((eq (caar e) 'mexpt) (diffexpt e x))
1605 ;; ((rpobj e) (diffrpobj e x)) ;New line added
1606 ;; ((and (boundp '$imetric) (eq (caar e) '%determinant);New line added
1607 ;; (eq (cadr e) $imetric))
1608 ;; ((lambda (dummy)
1609 ;; (setq dummy ($idummy))
1610 ;; (cond ((eq dummy x) (setq dummy ($idummy))))
1611 ;; (list '(mtimes simp) 2. e
1612 ;; (list '($ichr2 simp) (cons smlist (list dummy x))
1613 ;; (cons smlist (ncons dummy)))))
1614 ;; nil))
1616 ((and
1617 (boundp '$imetric)
1618 (rpobj x)
1619 (eq (caar e) '%determinant)
1620 (eq (cadr e) $imetric)
1622 (cond
1623 ((and
1624 (eq (caar x) $imetric)
1625 (eql (length (cdadr x)) 0)
1626 (eql (length (cdaddr x)) 2)
1627 (eql (length (cdddr x)) 0)
1629 (list '(mtimes simp)
1631 (list '(%determinant simp) $imetric)
1632 (list (cons $imetric '(simp))
1633 (list '(mlist simp) (nth 0 (cdaddr x)) (nth 1 (cdaddr x)))
1634 '((mlist simp))
1638 ((and
1639 (eq (caar x) $imetric)
1640 (eql (length (cdadr x)) 2)
1641 (eql (length (cdaddr x)) 0)
1642 (eql (length (cdddr x)) 0)
1644 (list '(mtimes simp)
1645 (list '(%determinant simp) $imetric)
1646 (list (cons $imetric '(simp))
1647 '((mlist simp))
1648 (list '(mlist simp) (nth 0 (cdadr x)) (nth 1 (cdadr x)))
1652 (t 0.)
1657 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1658 ;; Differentiation of tensors with respect to tensors ;;
1659 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1661 ((and (rpobj e) (rpobj x)) ; (merror "Not yet..."))
1662 (cond
1664 ( ;; dg([a,b],[])/dg([],[m,n])
1665 (and
1666 (boundp '$imetric)
1667 (eq (caar e) $imetric)
1668 (eq (caar x) $imetric)
1669 (eql (length (cdadr e)) 2)
1670 (eql (length (cdaddr e)) 0)
1671 (eql (length (cdddr e)) 0)
1672 (eql (length (cdadr x)) 0)
1673 (eql (length (cdaddr x)) 2)
1674 (eql (length (cdddr x)) 0)
1676 (list '(mtimes simp)
1678 (list
1679 (cons $imetric '(simp))
1680 (list '(mlist simp) (nth 0 (cdadr e)) (nth 0 (cdaddr x)))
1681 '((mlist simp))
1683 (list
1684 (cons $imetric '(simp))
1685 (list '(mlist simp) (nth 1 (cdadr e)) (nth 1 (cdaddr x)))
1686 '((mlist simp))
1691 ( ;; dg([],[a,b])/dg([m,n],[])
1692 (and
1693 (boundp '$imetric)
1694 (eq (caar e) $imetric)
1695 (eq (caar x) $imetric)
1696 (eql (length (cdadr e)) 0)
1697 (eql (length (cdaddr e)) 2)
1698 (eql (length (cdddr e)) 0)
1699 (eql (length (cdadr x)) 2)
1700 (eql (length (cdaddr x)) 0)
1701 (eql (length (cdddr x)) 0)
1703 (list '(mtimes simp)
1705 (list
1706 (cons $imetric '(simp))
1707 '((mlist simp))
1708 (list '(mlist simp) (nth 0 (cdaddr e)) (nth 0 (cdadr x)))
1710 (list
1711 (cons $imetric '(simp))
1712 '((mlist simp))
1713 (list '(mlist simp) (nth 1 (cdaddr e)) (nth 1 (cdadr x)))
1718 ( ;; dg([a,b],[],y)/dg([],[m,n])
1719 (and
1720 (boundp '$imetric)
1721 (eq (caar e) $imetric)
1722 (eq (caar x) $imetric)
1723 (eql (length (cdadr e)) 2)
1724 (eql (length (cdaddr e)) 0)
1725 (eql (length (cdddr e)) 1)
1726 (eql (length (cdadr x)) 0)
1727 (eql (length (cdaddr x)) 2)
1728 (eql (length (cdddr x)) 0)
1730 (prog (d1 d2)
1731 (setq d1 ($idummy) d2 ($idummy))
1732 (return
1733 (list '(mtimes simp)
1734 (list
1735 (cons $imetric '(simp))
1736 '((mlist simp))
1737 (list '(mlist simp) d1 d2)
1738 (cadddr e)
1740 (list
1741 '(mplus simp)
1742 (list
1743 '(mtimes simp)
1744 (list
1745 (cons $imetric '(simp))
1746 (list
1747 '(mlist simp)
1748 (nth 0 (cdadr e))
1749 (nth 0 (cdaddr x))
1751 '((mlist simp))
1753 (list
1754 (cons $imetric '(simp))
1755 (list '(mlist simp) d1 (nth 1 (cdaddr x)))
1756 '((mlist simp))
1758 (list
1759 (cons $imetric '(simp))
1760 (list '(mlist simp) (nth 1 (cdadr e)) d2)
1761 '((mlist simp))
1764 (list
1765 '(mtimes simp)
1766 (list
1767 (cons $imetric '(simp))
1768 (list '(mlist simp) (nth 0 (cdadr e)) d1)
1769 '((mlist simp))
1771 (list
1772 (cons $imetric '(simp))
1773 (list
1774 '(mlist simp)
1775 (nth 1 (cdadr e))
1776 (nth 0 (cdaddr x))
1778 '((mlist simp))
1780 (list
1781 (cons $imetric '(simp))
1782 (list '(mlist simp) d2 (nth 1 (cdaddr x)))
1783 '((mlist simp))
1792 ( ;; dg([a,b],[],y)/dg([],[m,n],k)
1793 (and
1794 (boundp '$imetric)
1795 (eq (caar e) $imetric)
1796 (eq (caar x) $imetric)
1797 (eql (length (cdadr e)) 2)
1798 (eql (length (cdaddr e)) 0)
1799 (eql (length (cdddr e)) 1)
1800 (eql (length (cdadr x)) 0)
1801 (eql (length (cdaddr x)) 2)
1802 (eql (length (cdddr x)) 1)
1804 (list '(mtimes simp)
1806 (list
1807 (cons $imetric '(simp))
1808 (list '(mlist simp) (nth 0 (cdadr e)) (nth 0 (cdaddr x)))
1809 '((mlist simp))
1811 (list
1812 (cons $imetric '(simp))
1813 (list '(mlist simp) (nth 1 (cdadr e)) (nth 1 (cdaddr x)))
1814 '((mlist simp))
1816 (list
1817 '(%kdelta simp)
1818 (list '(mlist simp) (cadddr e))
1819 (list '(mlist simp) (cadddr x))
1824 ( ;; dg([a,b],[],y,d)/dg([],[m,n])
1825 (and
1826 (boundp '$imetric)
1827 (eq (caar e) $imetric)
1828 (eq (caar x) $imetric)
1829 (eql (length (cdadr e)) 2)
1830 (eql (length (cdaddr e)) 0)
1831 (eql (length (cdddr e)) 2)
1832 (eql (length (cdadr x)) 0)
1833 (eql (length (cdaddr x)) 2)
1834 (eql (length (cdddr x)) 0)
1836 (prog (d1 d2)
1837 (setq d1 ($idummy) d2 ($idummy))
1838 (return
1839 (list '(mtimes simp)
1840 (list
1841 (cons $imetric '(simp))
1842 '((mlist simp))
1843 (list '(mlist simp) d1 d2)
1844 (nth 0 (cdddr e))
1845 (nth 1 (cdddr e))
1847 (list
1848 '(mplus simp)
1849 (list
1850 '(mtimes simp)
1851 (list
1852 (cons $imetric '(simp))
1853 (list
1854 '(mlist simp)
1855 (nth 0 (cdadr e))
1856 (nth 0 (cdaddr x))
1858 '((mlist simp))
1860 (list
1861 (cons $imetric '(simp))
1862 (list '(mlist simp) d1 (nth 1 (cdaddr x)))
1863 '((mlist simp))
1865 (list
1866 (cons $imetric '(simp))
1867 (list '(mlist simp) (nth 1 (cdadr e)) d2)
1868 '((mlist simp))
1871 (list
1872 '(mtimes simp)
1873 (list
1874 (cons $imetric '(simp))
1875 (list '(mlist simp) (nth 0 (cdadr e)) d1)
1876 '((mlist simp))
1878 (list
1879 (cons $imetric '(simp))
1880 (list
1881 '(mlist simp)
1882 (nth 1 (cdadr e))
1883 (nth 0 (cdaddr x))
1885 '((mlist simp))
1887 (list
1888 (cons $imetric '(simp))
1889 (list '(mlist simp) d2 (nth 1 (cdaddr x)))
1890 '((mlist simp))
1899 ( ;; dg([a,b],[],y,d)/dg([],[m,n],k)
1900 (and
1901 (boundp '$imetric)
1902 (eq (caar e) $imetric)
1903 (eq (caar x) $imetric)
1904 (eql (length (cdadr e)) 2)
1905 (eql (length (cdaddr e)) 0)
1906 (eql (length (cdddr e)) 2)
1907 (eql (length (cdadr x)) 0)
1908 (eql (length (cdaddr x)) 2)
1909 (eql (length (cdddr x)) 1)
1911 (prog (d1 d2 d3 d4)
1912 (setq d1 ($idummy) d2 ($idummy) d3 ($idummy) d4 ($idummy))
1913 (return
1914 (list
1915 '(mtimes simp)
1916 (list
1917 '(mplus simp)
1918 (list
1919 '(mtimes simp)
1920 (list
1921 (cons $imetric '(simp))
1922 (list '(mlist simp) (nth 0 (cdadr e)) d3)
1923 '((mlist simp))
1925 (list
1926 (cons $imetric '(simp))
1927 (list '(mlist simp) d2 d4)
1928 '((mlist simp))
1930 (list
1931 (cons $imetric '(simp))
1932 (list '(mlist simp) (nth 1 (cdadr e)) d1)
1933 '((mlist simp))
1936 (list
1937 '(mtimes simp)
1938 (list
1939 (cons $imetric '(simp))
1940 (list '(mlist simp) (nth 0 (cdadr e)) d2)
1941 '((mlist simp))
1943 (list
1944 (cons $imetric '(simp))
1945 (list '(mlist simp) (nth 1 (cdadr e)) d3)
1946 '((mlist simp))
1948 (list
1949 (cons $imetric '(simp))
1950 (list '(mlist simp) d1 d4)
1951 '((mlist simp))
1955 (list
1956 '(mplus simp)
1957 (list
1958 '(mtimes simp)
1959 (list
1960 '(%kdelta simp)
1961 (list '(mlist simp) (nth 0 (cdaddr x)))
1962 (list '(mlist simp) d3)
1964 (list
1965 '(%kdelta simp)
1966 (list '(mlist simp) (nth 1 (cdaddr x)))
1967 (list '(mlist simp) d4)
1969 (list
1970 '(%kdelta simp)
1971 (list '(mlist simp) (nth 1 (cdddr e)))
1972 (list '(mlist simp) (nth 0 (cdddr x)))
1975 (list
1976 (cons $imetric '(simp))
1977 '((mlist simp))
1978 (list '(mlist simp) d2 d1)
1979 (nth 0 (cdddr e))
1982 (list
1983 '(mtimes simp)
1984 (list
1985 '(%kdelta simp)
1986 (list '(mlist simp) (nth 0 (cdaddr x)))
1987 (list '(mlist simp) d2)
1989 (list
1990 '(%kdelta simp)
1991 (list '(mlist simp) (nth 1 (cdaddr x)))
1992 (list '(mlist simp) d1)
1994 (list
1995 '(%kdelta simp)
1996 (list '(mlist simp) (nth 0 (cdddr e)))
1997 (list '(mlist simp) (nth 0 (cdddr x)))
2000 (list
2001 (cons $imetric '(simp))
2002 '((mlist simp))
2003 (list '(mlist simp) d3 d4)
2004 (nth 1 (cdddr e))
2013 ( ;; dg([a,b],[],y,d)/dg([],[m,n],k,l)
2014 (and
2015 (boundp '$imetric)
2016 (eq (caar e) $imetric)
2017 (eq (caar x) $imetric)
2018 (eql (length (cdadr e)) 2)
2019 (eql (length (cdaddr e)) 0)
2020 (eql (length (cdddr e)) 2)
2021 (eql (length (cdadr x)) 0)
2022 (eql (length (cdaddr x)) 2)
2023 (eql (length (cdddr x)) 2)
2025 (list '(mtimes simp)
2027 (list
2028 (cons $imetric '(simp))
2029 (list '(mlist simp) (nth 0 (cdadr e)) (nth 0 (cdaddr x)))
2030 '((mlist simp))
2032 (list
2033 (cons $imetric '(simp))
2034 (list '(mlist simp) (nth 1 (cdadr e)) (nth 1 (cdaddr x)))
2035 '((mlist simp))
2037 (list
2038 '(%kdelta simp)
2039 (list '(mlist simp) (cadddr e))
2040 (list '(mlist simp) (cadddr x))
2042 (list
2043 '(%kdelta simp)
2044 (list '(mlist simp) (nth 1 (cdddr e)))
2045 (list '(mlist simp) (nth 1 (cdddr x)))
2051 ((and
2052 (eq (caar e) (caar x))
2053 (eql (length (cdadr e)) (length (cdadr x)))
2054 (eql (length (cdaddr e)) (length (cdaddr x)))
2055 (eql (length (cdddr e)) (length (cdddr x)))
2057 (cons '(mtimes)
2058 (cons 1
2059 (append
2060 (mapcar
2061 #'(lambda (x y)
2062 (list
2063 '(%kdelta simp)
2064 (list '(mlist simp) x)
2065 (list '(mlist simp) y)
2067 ) (cdadr e) (cdadr x)
2069 (mapcar
2070 #'(lambda (x y)
2071 (list
2072 '(%kdelta simp)
2073 (list '(mlist simp) x)
2074 (list '(mlist simp) y)
2076 ) (cdaddr x) (cdaddr e)
2078 (mapcar
2079 #'(lambda (x y)
2080 (list
2081 '(%kdelta simp)
2082 (list '(mlist simp) x)
2083 (list '(mlist simp) y)
2086 (cdddr e) (cdddr x)
2092 ((or
2093 (and ;; catchall symbols constructed from the metric tensor
2094 (boundp '$imetric)
2095 (eq (caar x) $imetric)
2096 (member
2097 (caar e)
2098 (cons '$icurvature (cons '%icurvature christoffels))
2101 (and ;; d(some covi)/d(cov metric)
2102 (boundp '$imetric)
2103 (not (eq (caar e) $imetric))
2104 (eq (caar x) $imetric)
2105 (eql (length (cdadr x)) 2)
2106 (eql (length (cdaddr x)) 0)
2107 (eql (length (cdddr x)) 0)
2108 (> (+ (length (cdadr e)) (length (cdddr e))) 0)
2110 (and ;; d(some conti)/d(cont metric)
2111 (boundp '$imetric)
2112 (not (eq (caar e) $imetric))
2113 (eq (caar x) $imetric)
2114 (eql (length (cdadr x)) 0)
2115 (eql (length (cdaddr x)) 2)
2116 (eql (length (cdddr x)) 0)
2117 (> (length (cdaddr e)) 0)
2119 (and ;; da([a,b],y)/da([m,n],k) with a+b=m+n, y=k
2120 (depends (caar e) (caar x))
2121 (eql (+ (length (cdadr e)) (length (cdaddr e)))
2122 (+ (length (cdadr x)) (length (cdaddr x))))
2123 (eql (length (cdddr e)) (length (cdddr x)))
2126 (list '(%derivative) e x)
2128 (t 0.)
2131 ;; End of tensor vs. tensor differentiation
2133 ((not (depends e x))
2134 (cond ((fixnump x) (list '(%derivative) e x))
2135 ((atom x) 0.)
2136 (t (list '(%derivative) e x))))
2137 ;This line moved down
2138 ((eq (caar e) 'mnctimes)
2139 (simplus (list '(mplus)
2140 (list '(mnctimes)
2141 (sdiff (cadr e) x)
2142 (caddr e))
2143 (list '(mnctimes)
2144 (cadr e)
2145 (sdiff (caddr e) x)))
2147 nil))
2148 ((eq (caar e) 'mncexpt) (diffncexpt e x))
2149 ((eq (caar e) '%integrate) (diffint e x))
2150 ((eq (caar e) '%derivative)
2151 (cond ((or (atom (cadr e))
2152 (member 'array (cdaadr e) :test #'eq))
2153 (chainrule1 e x))
2154 ((freel (cdr e) x) 0.)
2155 (t (diff%deriv (list e x 1.)))))
2156 ((member (caar e) '(%sum %product) :test #'eq) (diffsumprod e x))
2157 (t (sdiffgrad e x)))
2161 ; VTT: several of these functions have been copied verbatim from comm.lisp and
2162 ; comm2.lisp, in order to implement indicial differentiation as distinct from
2163 ; differentiation with respect to an external variable.
2165 (defun idiffmap (e x) (mapcar #'(lambda (term) (idiff term x)) e))
2167 (defun idifftimes (l x)
2168 (prog (term left out)
2169 loop (setq term (car l) l (cdr l))
2170 (setq out (cons (muln (cons (idiff term x) (append left l)) t) out))
2171 (if (null l) (return out))
2172 (setq left (cons term left))
2173 (go loop)))
2175 (defun idiffexpt1 (e x)
2176 ;; RETURN: n*v^n*rename(v'/v) where e=v^n
2177 (list '(mtimes) (caddr e) e
2178 ;; ($rename
2179 (list '(mtimes) (list '(mexpt) (cadr e) -1)
2180 (idiff (cadr e) x)
2182 ;; )
2186 (defun idiffexpt (e x)
2187 (if (mnump (caddr e))
2188 (mul3 (caddr e) (power (cadr e) (addk (caddr e) -1)) (idiff (cadr e) x))
2189 (mul2 e (add2 (mul3 (power (cadr e) -1) (caddr e) (idiff (cadr e) x))
2190 (mul2 (simplifya (list '(%log) (cadr e)) t)
2191 (idiff (caddr e) x))))))
2193 (defmfun idiffint (e x)
2194 (let (a)
2195 (cond ((null (cdddr e))
2196 (cond ((alike1 x (caddr e)) (cadr e))
2197 ((and (not (atom (caddr e))) (atom x) (not (free (caddr e) x)))
2198 (mul2 (cadr e) (idiff (caddr e) x)))
2199 ((or ($constantp (setq a (idiff (cadr e) x)))
2200 (and (atom (caddr e)) (free a (caddr e))))
2201 (mul2 a (caddr e)))
2202 (t (simplifya (list '(%integrate) a (caddr e)) t))))
2203 ((alike1 x (caddr e)) (addn (idiffint1 (cdr e) x x) t))
2204 (t (addn (cons (if (equal (setq a (idiff (cadr e) x)) 0)
2206 (simplifya (list '(%integrate) a (caddr e)
2207 (cadddr e) (car (cddddr e)))
2209 (idiffint1 (cdr e) x (caddr e)))
2210 t)))))
2212 (defun idiffint1 (e x y)
2213 (let ((u (idiff (cadddr e) x)) (v (idiff (caddr e) x)))
2214 (list (if (pzerop u) 0 (mul2 u (maxima-substitute (cadddr e) y (car e))))
2215 (if (pzerop v) 0 (mul3 v (maxima-substitute (caddr e) y (car e)) -1)))))
2217 (defun idiff%deriv (e)
2218 (declare (special derivflag))
2219 (let (derivflag) (simplifya (cons '(%idiff) e) t)))
2221 (defun ideriv (e)
2222 (prog (exp z count)
2223 (cond ((null e) (wna-err '$idiff))
2224 ((null (cdr e)) (return (stotaldiff (car e))))
2225 ((null (cddr e)) (nconc e '(1))))
2226 (setq exp (car e) z (setq e (copy-list e)))
2227 loop (if (or (null derivlist) (member (cadr z) derivlist :test #'equal)) (go doit))
2228 ; DERIVLIST is set by $EV
2229 (setq z (cdr z))
2230 loop2(cond ((cdr z) (go loop))
2231 ((null (cdr e)) (return exp))
2232 (t (go noun)))
2233 doit (cond ((nonvarcheck (cadr z) '$idiff))
2234 ((null (cddr z)) (wna-err '$idiff))
2235 ((not (fixnump (caddr z))) (go noun))
2236 ((minusp (setq count (caddr z)))
2237 (merror "Improper count to IDIFF:~%~M" count)))
2238 loop1(cond ((zerop count) (rplacd z (cdddr z)) (go loop2))
2239 ((equal (setq exp (idiff exp (cadr z))) 0) (return 0)))
2240 (setq count (f1- count))
2241 (go loop1)
2242 noun (return (idiff%deriv (cons exp (cdr e))))))
2245 (defmfun idiffncexpt (e x)
2246 ((lambda (base* pow)
2247 (cond ((and (mnump pow) (or (not (fixnump pow)) (< pow 0))) ; POW cannot be 0
2248 (idiff%deriv (list e x 1)))
2249 ((and (atom base*) (eq base* x) (free pow base*))
2250 (mul2* pow (list '(mncexpt) base* (add2 pow -1))))
2251 ((fixnump pow)
2252 ((lambda (deriv ans)
2253 (do ((i 0 (f1+ i))) ((= i pow))
2254 (setq ans (cons (list '(mnctimes) (list '(mncexpt) base* i)
2255 (list '(mnctimes) deriv
2256 (list '(mncexpt) base* (f- pow 1 i))))
2257 ans)))
2258 (addn ans nil))
2259 (idiff base* x) nil))
2260 ((and (not (depends pow x)) (or (atom pow) (and (atom base*) (free pow base*))))
2261 ((lambda (deriv index)
2262 (simplifya
2263 (list '(%sum)
2264 (list '(mnctimes) (list '(mncexpt) base* index)
2265 (list '(mnctimes) deriv
2266 (list '(mncexpt) base*
2267 (list '(mplus) pow -1 (list '(mtimes) -1 index)))))
2268 index 0 (list '(mplus) pow -1)) nil))
2269 (idiff base* x) (gensumindex)))
2270 (t (idiff%deriv (list e x 1)))))
2271 (cadr e) (caddr e)))
2273 (defmfun idiffsumprod (e x)
2274 (cond ((or (not (atom x)) (not (free (cadddr e) x)) (not (free (car (cddddr e)) x)))
2275 (idiff%deriv (list e x 1)))
2276 ((eq (caddr e) x) 0)
2277 (t (let ((u (idiff (cadr e) x)))
2278 (setq u (simplifya (list '(%sum)
2279 (if (eq (caar e) '%sum) u (div u (cadr e)))
2280 (caddr e) (cadddr e) (car (cddddr e)))
2282 (if (eq (caar e) '%sum) u (mul2 e u))))))
2284 (defun idiffgrad (e x)
2285 (let ((fun (caar e)) grad args)
2286 (cond ((and (eq fun 'mqapply) (zl-get (caaadr e) 'grad))
2287 (idiffgrad (cons (cons (caaadr e) nil) (append (cdadr e) (cddr e)))
2289 ((or (eq fun 'mqapply) (null (setq grad (zl-get fun 'grad))))
2290 (if (not (depends e x)) 0 (idiff%deriv (list e x 1))))
2291 ((not (= (length (cdr e)) (length (car grad))))
2292 (merror "Wrong number of arguments for ~:M" fun))
2293 (t (setq args (idiffmap (cdr e) x))
2294 (addn (mapcar
2295 #'mul2
2296 (cdr (substitutel
2297 (cdr e) (car grad)
2298 (do ((l1 (cdr grad) (cdr l1))
2299 (args args (cdr args)) (l2))
2300 ((null l1) (cons '(mlist) (nreverse l2)))
2301 (setq l2 (cons (cond ((equal (car args) 0) 0)
2302 (t (car l1)))
2303 l2)))))
2304 args)
2305 t)))))
2307 (defmfun idiff (e x)
2308 (cond
2309 (($constantp e) 0.)
2310 ((alike1 e x) 1.)
2311 ((or (atom e) (member 'array (cdar e) :test #'eq))
2312 ;; (ichainrule e x))
2313 ;; (idiff%deriv (list e x 1)))
2315 ((kindp (caar e) '$constant) 0.) ;New line added
2316 ((eq (caar e) 'mrat) (ratdx e x))
2317 ((eq (caar e) 'mplus)
2318 (simplus (cons '(mplus) (idiffmap (cdr e) x))
2321 ((eq (caar e) 'mequal)
2322 (list (car e) ($idiff (cadr e) x) ($idiff (caddr e) x)))
2323 ((eq (caar e) '$matrix)
2324 (cons (car e)
2325 (mapcar
2326 (function (lambda (y)
2327 (cons (car y)
2328 (idiffmap (cdr y) x))))
2329 (cdr e))))
2330 ((eq (caar e) 'mtimes)
2331 (addn (idifftimes (cdr e) x) t))
2332 ((eq (caar e) 'mexpt) (idiffexpt1 e x))
2333 ((rpobj e) (diffrpobj e x))
2334 ((and (boundp '$imetric) (eq (caar e) '%determinant)
2335 (eq (cadr e) $imetric))
2336 ((lambda (dummy)
2337 (setq dummy ($idummy))
2338 (cond ((eq dummy x) (setq dummy ($idummy))))
2339 (list '(mtimes simp) 2. e
2340 ;; (list '(($ichr2) simp) (cons smlist (list dummy x))
2341 (list (diffop) (cons smlist (list dummy x))
2342 (cons smlist (ncons dummy)))))
2343 nil))
2344 ((eq (caar e) 'mnctimes)
2345 (simplus (list '(mplus)
2346 (list '(mnctimes)
2347 ($idiff (cadr e) x)
2348 (caddr e))
2349 (list '(mnctimes)
2350 (cadr e)
2351 ($idiff (caddr e) x)))
2353 nil))
2354 ((eq (caar e) 'mncexpt) (idiffncexpt e x))
2355 ((eq (caar e) '%integrate) (idiffint e x))
2356 ((eq (caar e) '%derivative)
2357 (cond ((or (atom (cadr e))
2358 (member 'array (cdaadr e) :test #'eq))
2359 ;; (ichainrule e x))
2360 ;; (idiff%deriv (list e x 1)))
2362 ;; ((freel (cdr e) x) 0.)
2363 (t (idiff%deriv (list e x 1.)))))
2364 ((member (caar e) '(%sum %product) :test #'eq) (idiffsumprod e x))
2365 (t (idiffgrad e x))
2369 (defun diffrpobj (e x) ;Derivative of an indexed object
2370 (cond
2371 ( ; Special case: functions declared with coord()
2372 (and
2373 (member (caar e) $coord :test #'eq) (null (cdadr e))
2374 (equal (length (cdaddr e)) 1) (null (cdddr e))
2376 (delta (ncons x) (cdaddr e))
2378 (t ; Everything else
2379 (nconc
2380 (list (car e) (cadr e) (caddr e))
2381 (cond
2383 (null (cdddr e))
2384 (ncons x)
2386 ( ; Derivative indices do not commute when frames are used
2387 (or $iframe_flag $itorsion_flag)
2388 (append (cdddr e) (ncons x))
2391 (itensor-sort (append (cdddr e) (ncons x)))
2400 (defmfun $lc0 (l1)
2401 (prog (a b c sign)
2402 (setq a (cdr l1))
2403 (ifnot (and a (cdr a)) (return (list '(%levi_civita) l1)))
2404 (setq b a)
2405 loop1(ifnot (fixnump (car a)) (return (list '(%levi_civita) l1)))
2406 (and (setq a (cdr a)) (go loop1))
2407 loop3(setq a (car b) b (cdr b) c b)
2408 loop2(cond ((= (car c) a) (return 0.))
2409 ((< (car c) a) (setq sign (not sign))))
2410 (and (setq c (cdr c)) (go loop2))
2411 (and (cdr b) (go loop3))
2412 (return (cond (sign -1.) (t 1.)))))
2413 (defmfun $levi_civita (l1 &optional (l2 nil))
2414 (cond
2415 ((eq l2 nil) ($lc0 l1))
2416 ((like l1 '((mlist)))
2417 (prog (l) (setq l nil)
2418 (do ((i ($length l2) (1- i))) ((< i 1)) (setq l (cons i l)))
2419 (return (list '($kdelta simp) (cons smlist l) l2))
2421 ((like l2 '((mlist)))
2422 (prog (l) (setq l nil)
2423 (do ((i ($length l1) (1- i))) ((< i 1)) (setq l (cons i l)))
2424 (return (list '($kdelta simp) l1 (cons smlist l)))
2426 (t (merror "Mixed-index Levi-Civita symbols not supported"))
2430 ;; simplification rules for the totally antisymmetric LC symbol
2431 (defun $lc_l (e)
2432 (prog (l1 l2 l nn)
2433 (catch 'match
2434 (cond ((atom e) (matcherr)))
2435 (cond ((atom (car e)) (matcherr)))
2436 (cond ((not (or (eq (caar e) '$levi_civita) (eq (caar e) '%levi_civita))) (matcherr)))
2437 (cond ((not ($listp (setq l1 ($covi e)))) (matcherr)))
2438 (cond ((not (alike1 '((mlist simp)) (setq l2 ($conti e)))) (matcherr)))
2439 (cond ((cdddr e) (matcherr)))
2440 (setq nn ($length l1))
2441 (setq l nil)
2442 (do ((i nn (1- i))) ((< i 1)) (setq l (cons ($idummy) l)))
2443 (return (values (list '(mtimes simp) ($kdelta l1 (cons smlist l))
2444 (list (cons (caar e) '(simp)) (cons smlist l) (ncons smlist))
2445 (list '(mexpt simp) (meval (list 'mfactorial nn)) -1)) t)
2451 (defun $lc_u (e)
2452 (prog (l1 l2 l nn)
2453 (catch 'match
2454 (cond ((atom e) (matcherr)))
2455 (cond ((atom (car e)) (matcherr)))
2456 (cond ((not (or (eq (caar e) '$levi_civita) (eq (caar e) '%levi_civita))) (matcherr)))
2457 (cond ((not (alike1 '((mlist simp)) (setq l1 ($covi e)))) (matcherr)))
2458 (cond ((not ($listp (setq l2 ($conti e)))) (matcherr)))
2459 (cond ((cdddr e) (matcherr)))
2460 (setq nn ($length l2))
2461 (setq l nil)
2462 (do ((i nn (1- i))) ((< i 1)) (setq l (cons ($idummy) l)))
2463 (return (values (list '(mtimes simp) ($kdelta (cons smlist l) l2)
2464 (list (cons (caar e) '(simp)) (ncons smlist) (cons smlist l))
2465 (list '(mexpt simp) (meval (list 'mfactorial nn)) -1)) t)
2471 (add2lnc '$lc_l $rules)
2472 (add2lnc '$lc_u $rules)
2474 (declare-top (special e empty $flipflag))
2476 (setq $flipflag nil empty '((mlist simp) ((mlist simp)) ((mlist simp))))
2478 (defun nonumber (l)
2479 (cond
2480 ((numberp (car l)) (nonumber (cdr l)))
2481 ((eq l nil) ())
2482 (t (cons (car l) (nonumber (cdr l))))
2486 (defun removeindex (e l)
2487 (cond ((null l) nil)
2488 ((atom e)
2489 (cond ((eq e (car l)) (cdr l))
2490 (t (cons (car l) (removeindex e (cdr l))))
2492 (t (removeindex (cdr e) (removeindex (car e) l)))
2496 (defun indices (e)
2497 (prog (top bottom x y p q r)
2498 (setq top nil bottom nil)
2499 (cond
2501 (rpobj e)
2502 (setq top (nonumber (conti e))
2503 bottom (nonumber (append (covi e) (cdddr e))))
2505 ((atom e))
2507 (and (eq (caar e) 'mexpt) (eql (caddr e) -1))
2508 (setq x (indices (cadr e)) bottom (append bottom (car x))
2509 top (append top (cadr x)))
2512 (and (member (caar e) '(%derivative $diff) :test #'eq)
2513 (or (eql (length e) 3) (eql (cadddr e) 1)))
2514 (setq x (indices (cadr e)) bottom (append bottom (cadr x))
2515 top (append top (car x)))
2516 (setq x (indices (caddr e)) bottom (append bottom (car x))
2517 top (append top (cadr x)))
2520 (member (caar e) '(mtimes mnctimes mncexpt) :test #'eq)
2521 (dolist (v (cdr e))
2522 (setq x (indices v) bottom (append bottom (cadr x))
2523 top (append top (car x)))
2527 (member(caar e) '(mplus mequal) :test #'eq)
2528 (setq top (indices (cadr e)) bottom (cadr top) top (car top))
2529 (setq p (intersect top bottom) q (removeindex p bottom)
2530 p (removeindex p top))
2531 (dolist (v (cddr e))
2532 (setq x (indices v) y (cadr x) x (car x))
2533 (setq r (intersect x y) x (removeindex r x) y (removeindex r y))
2534 (when
2535 (not (and (samelists x p) (samelists y q)))
2536 (merror "Improper indices in ~M" v)
2538 (setq top (union top r) bottom (union bottom r))
2542 (member (caar e) '($sum %sum) :test #'eq)
2543 (setq top (list (caddr e)) bottom (list (caddr e)))
2546 (member (caar e) '(%idiff $idiff) :test #'eq)
2547 ;;; This code would count derivative indices as covariant. However, it is
2548 ;;; not needed. If the user wants to count derivative indices, those should
2549 ;;; be part of the tensor expression; if the expression is undiff'd, there
2550 ;;; must be a reason!
2551 ;; (do
2552 ;; ((f (cddr e) (cddr f)))
2553 ;; ((null f))
2554 ;; (do
2555 ;; ((i 1 (1+ i)))
2556 ;; ((> i (cond ((cadr f) (cadr f)) (t 1))))
2557 ;; (setq bottom (cons (car f) bottom))
2558 ;; )
2559 ;; )
2560 (setq x (indices (cadr e)) bottom (append bottom (cadr x))
2561 top (append top (car x)))
2564 (return (list top bottom))
2568 (defmfun $indices (e)
2569 (prog (top bottom x)
2570 ;; (setq top (indices e) bottom (cadr top) top (car top) x (intersect top bottom))
2571 (setq top (indices e) bottom (cadr top) top (car top) x (cond ($flipflag (intersect bottom top)) (t (intersect top bottom))))
2572 (setq top (removeindex x top) bottom (removeindex x bottom))
2573 (return (cons smlist (list (cons smlist (append top bottom)) (cons smlist x))))
2577 (defun samelists (a b) ;"True" if A and B have the same distinct elements
2578 (and (= (length a) (length b))
2579 (do ((l
2581 (cdr l)))
2582 (nil)
2583 (cond ((null l) (return t))
2584 ((member (car l) b :test #'eq))
2585 (t (return nil))))))
2587 (defmfun $flush n ;Replaces the given (as arguments to FLUSH) indexed
2588 (prog (l) ;objects by zero if they have no derivative indices.
2589 (cond ((< n 2) (merror "FLUSH takes at least 2 arguments"))
2590 ((not
2591 (loop for v in (setq l (listify (f- 1 n)))
2592 always (symbolp v)))
2593 ; (apply 'and (mapcar 'symbolp
2594 ; (setq l (listify (f- 1 n))) ))
2595 (merror "All arguments but the first must be names of
2596 indexed objects")) (t (return (flush (arg 1) l t))))))
2598 (defmfun $flushd n ;Replaces the given (as arguments to FLUSHD) indexed
2599 (prog (l) ;objects by zero if they have any derivative indices.
2600 (cond ((< n 2) (merror "FLUSH takes at least 2 arguments"))
2601 ((not
2602 (loop for v in (setq l (listify (f- 1 n)))
2603 always (symbolp v))
2604 ; (apply 'and (mapcar 'symbolp
2605 ; (setq l (listify (f- 1 n)))))
2607 (merror "All arguments but the first must be names of
2608 indexed objects")) (t (return (flush (arg 1) l nil))))))
2610 (defun flush (e l flag)
2611 (cond ((atom e) e)
2612 ((rpobj e)
2613 (cond ((not (member (caar e) l :test #'eq)) e)
2614 ((not (null (cdddr e)))
2615 (cond (flag e)
2616 (t 0)))
2617 (t (cond (flag 0)
2618 (t e)))))
2619 (t (subst0 (cons (ncons (caar e))
2620 (mapcar (function (lambda (q) (flush q l flag)))
2621 (cdr e))) e))))
2623 (defmfun $flushnd (e name n) ;Replaces by zero all indexed objects
2624 (cond ((atom e) e) ;that have n or more derivative indices
2625 ((rpobj e)
2626 (cond ((and (equal (caar e) name)
2627 (> (length (cdddr e)) (1- n)))
2629 (t e)))
2630 (t (subst0 (cons (ncons (caar e))
2631 (mapcar (function
2632 (lambda (q) (funcall (symbol-function '$flushnd) q name n)))
2633 (cdr e))) e))))
2635 (declare-top (special index n))
2637 (defmfun $rename nargs
2638 (cond ((= nargs 1) (setq index 1)) (t (setq index (arg 2)))) (rename (arg 1)))
2640 (defun rename (e) ;Renames dummy indices consistently
2641 (cond
2642 ((atom e) e)
2643 ((or (rpobj e) (eq (caar e) 'mtimes););If an indexed object or a product
2644 (and (member (caar e) '(%derivative $diff) :test #'eq) ; or a derivative expression
2645 (or (eql (length e) 3) (eql (cadddr e) 1)))
2647 ((lambda (l)
2648 (simptimes (reorder (cond (l (sublis (itensor-cleanup l (setq n index)) e))(t e))) 1 t))
2649 (cdaddr ($indices e)) ;Gets list of dummy indices
2651 (t ;Otherwise map $RENAME on each of the subparts e.g. a sum
2652 (mysubst0 (simplifya (cons (ncons (caar e))
2653 (mapcar 'rename (cdr e)))
2658 (defun reorder (e) ;Reorders contravariant, covariant, derivative indices
2659 (mysubst0 ;Example: F([A,B],[C,D],E,F)
2660 (cons
2661 '(mtimes)
2662 (mapcar
2663 #'(lambda (x)
2664 (cond ((rpobj x)
2665 (setq x ($renorm x))
2666 (nconc (list (car x) ;($f simp)
2667 (cons smlist
2668 (cond ($allsym (itensor-sort (copy-tree (cdadr x))))
2669 (t (cdadr x)))) ;($a $b)
2670 (cons smlist
2671 (cond ($allsym
2672 (itensor-sort (copy-tree (cdaddr x))))
2673 (t (cdaddr x))))) ;($c $d)
2674 (cond ($iframe_flag (cdddr x))
2675 (t (itensor-sort (copy-tree (cdddr x))))))) ;($e $f)
2676 (t x)))
2677 (cond ((eq (caar e) 'mtimes) (cdr e))
2678 (t (ncons e)))))
2681 (let (dumx)
2682 (defun itensor-cleanup (a nn) (setq n nn dumx nil) (cleanup1 a))
2684 (defun cleanup1 (a)
2685 (and a (setq dumx (implode (nconc (exploden $idummyx) ;Keep proper order of
2686 (exploden n))) n (1+ n)) ;indices
2687 (cond ((eq dumx (car a)) (cleanup1 (cdr a)))
2688 (t (cons (cons (car a) dumx) (cleanup1 (cdr a))))))))
2689 ;Make list of dotted pairs indicating substitutions i.e. ((a . #1) (b . #2))
2691 (declare-top (unspecial n index))
2693 (defun itensor-sort (l) (cond ((cdr l) (sort l 'less)) (t l)))
2694 ;Sort into ascending order
2696 (defmfun $remcomps (tensor)
2697 (zl-remprop tensor 'expr) (zl-remprop tensor 'carrays)
2698 (zl-remprop tensor 'texprs) (zl-remprop tensor 'indexed)
2699 (zl-remprop tensor 'indexed) (zl-remprop tensor 'tsubr)
2700 (and (functionp tensor) (fmakunbound tensor))
2701 '$done)
2703 (defmfun $indexed_tensor (tensor)
2704 (let (fp new)
2705 (and (zl-get tensor 'expr)
2706 (merror "~M has expr" tensor))
2707 ; (args tensor nil)
2708 (and (setq fp (zl-get tensor 'subr))
2709 (progn (setq new (gensym))(putprop new fp 'subr)
2710 (zl-remprop tensor 'subr)(putprop tensor new 'tsubr)))
2711 (putprop tensor t 'indexed)
2712 (putprop tensor (subst tensor 'g '(lambda nn (tensoreval (quote g)(listify nn)))) 'expr)
2713 (eval (subst tensor 'g (quote (defmfun g nn (tensoreval 'g (listify nn))))))
2714 '$done))
2717 (defun allfixed (l)
2718 (and l (fixnump (car l)) (or (null (cdr l)) (allfixed (cdr l)))))
2720 (defun tensoreval (tensor indxs)
2721 ((lambda (der con)
2722 (and (cdr indxs) (setq con (cdadr indxs) der (cddr indxs)))
2723 (setq tensor (select tensor (cdar indxs) con der))
2724 ) nil nil))
2726 (defmfun $components (tensor comp)
2727 ((lambda (len1 len2 len3 name prop)
2728 (cond ((not (rpobj tensor)) (merror "Improper 1st arg to COMPONENTS: ~M" tensor)))
2729 (setq len1 (length (covi tensor)) len2 (length (conti tensor)) len3 (length (deri tensor)))
2730 (and (not (atom comp))
2731 (eq (caar comp) '$matrix)
2732 (cond ((= (f+ (f+ len1 len2) len3) 2)
2733 (setq name (gensym))
2734 (set name comp)
2735 (setq comp name)
2737 (t (merror "Needs two indices for COMPONENTS from matrix:~%~M" tensor))
2741 (cond ((and (symbolp comp) (> (f+ (f+ len1 len2) len3) 0))
2742 (setq prop 'carrays)
2744 ((samelists (setq name (append (covi tensor) (conti tensor) (deri tensor))) (cdadr ($indices comp)))
2745 (setq prop 'texprs comp (cons comp name))
2747 (t (merror "Args to COMPONENTS do not have the same free indices"))
2749 (setq tensor (caar tensor) len1 (list len1 len2 len3))
2750 (cond ((and (setq name (zl-get tensor prop))
2751 (setq len2 (assoc len1 name :test #'equal))
2753 (rplacd len2 comp)
2755 (t (putprop tensor (cons (cons len1 comp) name) prop))
2757 (or (zl-get tensor 'indexed) ($indexed_tensor tensor))
2758 '$done
2760 nil nil nil nil nil
2764 (defun select (tensor l1 l2 l3)
2765 (prog
2767 (setq l2 (append (minusi l1) l2) l1 (plusi l1))
2768 (return
2770 (lambda
2771 (prop subs idx)
2772 (cond
2774 (and
2775 (allfixed subs)
2776 (setq prop (zl-get tensor 'carrays))
2777 (setq prop (assoc idx prop :test #'equal))
2779 (cond
2781 (alike1
2782 (setq prop (cons (list (cdr prop) 'array) subs))
2783 (setq subs (meval prop))
2787 (t subs)
2791 (setq prop (assoc idx (zl-get tensor 'texprs) :test #'equal))
2792 (sublis
2793 (mapcar #'cons(cddr prop) subs)
2794 ($rename (cadr prop) (cond ((boundp 'n) n) (t 1)))
2798 (setq prop (zl-get tensor 'tsubr))
2799 (apply
2800 prop
2801 (list (cons smlist l1) (cons smlist l2) (cons smlist l3))
2805 (not (eq l3 nil))
2806 (apply '$idiff (select tensor l1 l2 (cdr l3)) (list (car l3)))
2810 (append
2811 (list (list tensor 'simp) (cons smlist l1) (cons smlist l2))
2817 nil (append l1 l2 l3) (list (length l1)(length l2)(length l3))
2824 (defmfun $entertensor nargs
2825 (prog (fun contr cov deriv)
2826 (cond
2828 (> nargs 1)
2829 (merror "ENTERTENSOR takes 0 or 1 arguments only")
2832 (= nargs 0)
2833 (mtell "Enter tensor name: ")
2834 (setq fun (meval (retrieve nil nil)))
2836 ((setq fun (arg 1)))
2838 (mtell "Enter a list of the covariant indices: ")
2839 (setq cov (checkindex (meval (retrieve nil nil)) fun))
2840 (cond ((atom cov) (setq cov (cons smlist (ncons cov)))))
2841 (mtell "Enter a list of the contravariant indices: ")
2842 (setq contr (checkindex (meval (retrieve nil nil)) fun))
2843 (cond ((atom contr) (setq contr (cons smlist (ncons contr)))))
2844 (mtell "Enter a list of the derivative indices: ")
2845 (setq deriv (checkindex (meval (retrieve nil nil)) fun))
2846 (setq deriv
2847 (cond ((atom deriv) (ncons deriv))
2848 (t (cdr deriv))
2851 (cond
2853 (memberl (cdr cov) deriv)
2854 (mtell "Warning: There are indices that are both covariant ~
2855 and derivative%")
2858 (return ($ishow (nconc (list (list fun 'simp) cov contr) deriv)))
2862 (defun checkindex (e f)
2863 (cond ((and (atom e) (not (eq e f))) e)
2864 ((and (eq (caar e) 'mlist)
2865 (loop for v in (cdr e) always (atom v))
2866 ; (apply 'and (mapcar 'atom (cdr e)))
2867 (not (member f e :test #'eq))) e)
2868 (t (merror "Indices must be atoms different from the tensor name"))))
2870 (defun memberl (a b)
2871 (do ((l a (cdr l))
2872 (carl))
2873 ((null l) nil)
2874 (setq carl (car l))
2875 (cond ((and (symbolp carl) (member carl b :test #'equal))
2876 (return t)))))
2878 (defun consmlist (l) (cons smlist l)) ;Converts from Lisp list to Macsyma list
2880 ;$INDICES2 is similar to $INDICES except that here dummy indices are picked off
2881 ;as they first occur in going from left to right through the product or indexed
2882 ;object. Also, $INDICES2 works only on the top level of a product and will
2883 ;miss indices for products of sums (which is used to advantage by $IC_CONVERT).
2885 (defmfun $indices2 (e)
2886 (cond ((atom e) empty)
2887 ((not (or (member (caar e) '(mtimes mnctimes) :test #'eq) (rpobj e)))
2888 ($indices e))
2889 (t ((lambda (indices)
2890 (do ((ind indices) (free) (dummy) (index))
2891 ((null ind)
2892 (consmlist (list (consmlist (nreverse free))
2893 (consmlist (nreverse dummy)))))
2894 (setq index (car ind))
2895 (cond ((member index dummy :test #'equal)
2896 (merror "~M has improper indices"
2897 (ishow e)))
2898 ((member index (cdr ind) :test #'equal)
2899 (setq dummy (cons index dummy)
2900 ind (delete index (copy-tree (cdr ind))
2901 :count 1 :test #'equal)))
2902 (t (setq free (cons index free)
2903 ind (cdr ind))))))
2904 (do ((e (cond ((member (caar e) '(mtimes mnctimes) :test #'eq) (cdr e))
2905 (t (ncons e))) (cdr e))
2906 (a) (l))
2907 ((null e) l)
2908 (setq a (car e))
2909 (and (rpobj a) (setq l (append l (covi a) (conti a)
2910 (cdddr a)))))))))
2912 (defmfun $changename (a b e) ;Change the name of the indexed object A to B in E
2913 (prog (old indspec ncov ncontr) ;INDSPEC is INDex SPECification flag
2914 (cond ((not (or (and (symbolp a) (setq old a))
2915 (and ($listp a) (equal (length (cdr a)) 3)
2916 (symbolp (setq old (cadr a)))
2917 (fixnump (setq ncov (caddr a)))
2918 (fixnump (setq ncontr (cadddr a)))
2919 (setq indspec t))))
2920 (merror "Improper first argument to CHANGENAME: ~M" a))
2921 ((not (symbolp b))
2922 (merror "Second argument to CHANGENAME must be a symbol"))
2923 (t (return (changename old indspec ncov ncontr b e))))))
2925 (defun changename (a indspec ncov ncontr b e)
2926 (cond ((or (atom e) (eq (caar e) 'rat)) e)
2927 ((rpobj e)
2928 (cond ((and (eq (caar e) a)
2929 (cond (indspec (and (equal (length (cdadr e)) ncov)
2930 (equal (length (cdaddr e))
2931 ncontr)))
2932 (t t)))
2933 (cons (cons b (cdar e)) (cdr e)))
2934 (t e)))
2935 (t (mysubst0 (cons (car e)
2936 (mapcar (function
2937 (lambda (q)
2938 (changename a indspec ncov
2939 ncontr b q)))
2940 (cdr e))) e))))
2942 (defmfun $coord n
2943 (do ((l (listify n) (cdr l)) (a))
2944 ((null l) '$done)
2945 (setq a (car l))
2946 (cond ((not (symbolp a))
2947 (merror "~M is not a valid name." a))
2948 (t (add2lnc a $coord)))))
2950 (defmfun $remcoord (&rest args)
2951 (cond ((and (= (length args) 1)
2952 (eq (car args) '$all))
2953 (setq $coord '((mlist)))
2954 '$done)
2955 (t (dolist (c args '$done)
2956 (setq $coord (delete c $coord :test #'eq))))))
2959 ;; Additions on 5/19/2004 -- VTT
2961 (defmfun $listoftens (e)
2962 (itensor-sort (cons smlist (listoftens e))))
2964 (defun listoftens (e)
2965 (cond ((atom e) nil)
2966 ((rpobj e) (list e))
2967 (t (let (l)
2968 (mapcar #'(lambda (x) (setq l (union l (listoftens x) :test #'equal))) (cdr e))
2969 l))))
2971 (defun numlist (&optional (n 1))
2972 (loop for i from n upto $dim collect i))
2974 ;;showcomps(tensor):=block([i1,i2,ind:indices(tensor)[1]],
2975 ;; if length(ind)=0 then ishow(ev(tensor))
2976 ;; else if length(ind)=1 then ishow(makelist(ev(tensor,ind[1]=i1),i1,1,dim))
2977 ;; else if length(ind)=2 then ishow(tensor=apply('matrix,makelist(makelist(ev(tensor,[ind[1]=i1,ind[2]=i2]),i1,1,dim),i2,1,dim)))
2978 ;; else for i1 thru dim do (showcomps(subst(i1,last(ind),tensor)),if length(ind)=3 and i1<dim then linenum:linenum+1)
2979 ;;);
2980 (defmfun $showcomps (e)
2981 (prog (ind)
2982 (setq ind (cdadr ($indices e)))
2983 (cond ((> 1 (length ind)) ($ishow (meval (list '($ev) e))))
2984 ((> 2 (length ind)) ($ishow (cons smlist (mapcar (lambda (i) (meval (list '($ev) e (list '(mequal) (car ind) i)))) (numlist)))))
2985 ((> 3 (length ind)) ($ishow (list '(mequal) e (cons '($matrix simp) (mapcar (lambda (j) (cons smlist (mapcar (lambda (i) (meval (list '($ev) e (list '(mequal) (car ind) i) (list '(mequal) (cadr ind) j)))) (numlist)))) (numlist))))))
2986 (t (mapcar (lambda (i) (funcall (symbol-function '$showcomps) ($substitute i (car (last ind)) e)) (and (> 4 (length ind)) (< i $dim) (setq $linenum (1+ $linenum)))) (numlist)))
2991 ; Implementation of the Hodge star operator. Based on the following
2992 ; MAXIMA-language implementation:
2994 ; hodge(e):=
2997 ; len:length(indices(e)[1]),
2998 ; idx1:makelist(idummy(),i,len+1,dim),
2999 ; idx2:makelist(idummy(),i,len+1,dim)
3000 ; ],
3001 ; funmake("*",makelist(funmake(imetric,[[idx1[i],idx2[i]]]),i,1,dim-len))*
3002 ; funmake(levi_civita,[[],append(idx1,indices(e)[1])])*e/len!
3003 ; )$
3005 (defmfun $hodge (e)
3006 (prog (len idx1 idx2)
3007 (setq
3008 len ($length (cadr ($indices e)))
3010 (cond ((> len $dim) (return 0)))
3011 (setq
3012 idx1 (do ((i $dim (1- i)) l) ((eq i len) l) (setq l (cons ($idummy) l)))
3013 idx2 (do ((i $dim (1- i)) l) ((eq i len) l) (setq l (cons ($idummy) l)))
3015 (return
3016 (append
3017 (list
3018 '(mtimes)
3020 (list '(rat) 1 (factorial len))
3021 (list
3022 '($levi_civita)
3023 '((mlist simp))
3024 (cons '(mlist simp) (append (reverse idx1) (cdadr ($indices e))))
3029 ((not idx1) l)
3030 (setq l (cons (list (list $imetric)
3031 (cons '(mlist) (list (car idx1) (car idx2)))) l)
3032 idx1 (cdr idx1)
3033 idx2 (cdr idx2)
3041 ; This version of remsym remains silent when an attempt is made to remove
3042 ; non-existent symmetries. Used by $idim below.
3044 (defun remsym (name ncov ncontr)
3045 (declare (special $symmetries))
3046 (let ((tensor (implode (nconc (exploden name) (ncons 45)
3047 (exploden ncov) (ncons 45)
3048 (exploden ncontr)))))
3049 (when (member tensor (cdr $symmetries) :test #'equal)
3050 (setq $symmetries (delete tensor $symmetries :test #'equal))
3051 (zl-remprop tensor '$sym)
3052 (zl-remprop tensor '$anti)
3053 (zl-remprop tensor '$cyc))))
3055 ; This function sets the metric dimensions and Levi-Civita symmetries.
3057 (defmfun $idim (n)
3058 (remsym '%levi_civita $dim 0)
3059 (remsym '%levi_civita 0 $dim)
3060 (remsym '$levi_civita $dim 0)
3061 (remsym '$levi_civita 0 $dim)
3062 (setq $dim n)
3063 (remsym '%levi_civita $dim 0)
3064 (remsym '%levi_civita 0 $dim)
3065 (remsym '$levi_civita $dim 0)
3066 (remsym '$levi_civita 0 $dim)
3067 ($decsym '%levi_civita n 0 '((mlist) (($anti) $all)) '((mlist)))
3068 ($decsym '%levi_civita 0 n '((mlist)) '((mlist) (($anti) $all)))
3069 ($decsym '$levi_civita n 0 '((mlist) (($anti) $all)) '((mlist)))
3070 ($decsym '$levi_civita 0 n '((mlist)) '((mlist) (($anti) $all)))
3073 (defun i-$dependencies (l &aux res)
3074 (dolist (z l)
3075 (cond
3076 ((atom z)
3077 (merror
3078 (intl:gettext
3079 "depends: argument must be a non-atomic expression; found ~M") z))
3080 ((or (eq (caar z) 'mqapply)
3081 (member 'array (cdar z) :test #'eq))
3082 (merror
3083 (intl:gettext
3084 "depends: argument cannot be a subscripted expression; found ~M") z))
3086 (do ((zz z (cdr zz))
3087 (y nil))
3088 ((null zz)
3089 (mputprop (caar z) (setq y (reverse y)) 'depends)
3090 (setq res (push (cons (ncons (caar z)) y) res))
3091 (unless (cdr $dependencies)
3092 (setq $dependencies '((mlist simp))))
3093 (add2lnc (cons (cons (caar z) nil) y) $dependencies))
3094 (cond
3095 ((and (cadr zz)
3096 (not (member (cadr zz) y)))
3097 (setq y (push (cadr zz) y))))))))
3098 (cons '(mlist simp) (reverse res)))
3100 ($load '$ex_calc)
3101 ($load '$lckdt)
3102 ($load '$iframe)