Fix typo in display-html-help
[maxima.git] / share / tensor / itensor.lisp
blobdcb1357e3c9c3a473cb9a10931c95c8d408693c3
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 (defun vecdiff (v i j d) ;Add frame bracket contribution when iframe_flag:true
551 (cond
553 $iframe_flag
554 (cons
555 '(mplus simp)
556 (list
557 (list (list v) '((mlist)) (list '(mlist) i) j)
558 (list
559 '(mtimes simp)
560 (list (list v) '((mlist)) (list '(mlist) d))
561 (list
562 '(mtimes simp)
564 (list '(%ifb) (list '(mlist) d j) (list '(mlist) i))
571 (list (list v) '((mlist)) (list '(mlist) i) j)
576 (defun liediff (v e n)
577 (cond
578 ((not (symbolp v)) (merror "~M is not a symbol" v))
580 (or (atom e) (eq (caar e) 'rat)) ; Scalar field
581 ; v([],[%1])*idiff(e,%1)
582 (let
583 ((dummy (implode (nconc (exploden $idummyx) (exploden n)))))
584 (list
585 '(mtimes) (list (list v) '((mlist)) (list '(mlist) dummy))
586 ($idiff e dummy)
591 (rpobj e) ; Tensor field
593 ; Dummy implementation for logic tests
594 ; (list '(%liediff) v e)
596 ; Shall the dummy index be in ICOUNTER sequence? Probably yes.
597 ; (let ((dummy (implode (nconc (exploden $idummyx) (exploden n)))))
598 (let
600 (dummy ($idummy))
601 (dummy2
602 (cond
603 ($iframe_flag ($idummy))
604 (t nil)
609 append
610 (list
611 '(mplus) 0
612 (list
613 '(mtimes) ; e([...],[...],%1)*v([],[%1])
614 (list (list v) '((mlist)) (list '(mlist) dummy))
615 ($idiff e dummy)
618 (maplist
619 #'(lambda (s) ; e([..%1..],[...])*v([],[%1],k)
620 (list
621 '(mtimes)
622 (cond ((atom (car s)) 1) (t -1))
623 (append
624 (list
625 (car e)
626 (cons
627 '(mlist)
628 (append
629 (subseq (cdadr e) 0 (- (length (cdadr e)) (length s)))
630 (cons
631 (cond ((atom (car s)) dummy)
632 (t (list '(mtimes simp) -1 dummy))
634 (cdr s)
638 (caddr e)
640 (cdddr e)
642 (vecdiff
644 (cond ((atom (car s)) dummy) (t (caddr (car s))))
645 (cond ((atom (car s)) (car s)) (t dummy))
646 dummy2
650 (cdadr e)
652 (maplist
653 #'(lambda (s) ; +e([...],[...],..%1..)*v([],[%1],k)
654 (list
655 '(mtimes)
656 (append
657 (list (car e) (cadr e) (caddr e))
658 (subseq (cdddr e) 0 (- (length (cdddr e)) (length s)))
659 (cons dummy (cdr s))
661 (vecdiff v dummy (car s) dummy2)
664 (cdddr e)
666 (maplist
667 #'(lambda (s) ; -e([...],[..%1..])*v([],[k],%1)
668 (list
669 '(mtimes) -1
670 (append
671 (list (car e) (cadr e)
672 (cons
673 '(mlist)
674 (append
675 (subseq (cdaddr e) 0 (- (length (cdaddr e)) (length s)))
676 (cons dummy (cdr s))
680 (cdddr e)
682 (vecdiff v (car s) dummy dummy2)
685 (cdaddr e)
691 (eq (caar e) 'mtimes) ; Leibniz rule
692 ; Lv(cadr e)*(cddr e)+(cadr e)*Lv(cddr e)
693 (list
694 '(mplus)
695 (cons '(mtimes) (cons (liediff v (cadr e) n) (cddr e)))
696 (cons
697 '(mtimes)
698 (list
699 (cadr e)
700 (liediff
702 (cond ((cdddr e) (cons '(mtimes) (cddr e))) (t (caddr e)))
710 (eq (caar e) 'mplus) ; Linearity
711 ; We prefer mapcar to iteration, but the recursive code also works
712 ; (list
713 ; '(mplus)
714 ; (liediff v (cadr e) n)
715 ; (liediff v (cond ((cdddr e) (cons '(mplus) (cddr e))) (t (caddr e))) n)
717 (cons '(mplus) (mapcar #'(lambda (u) (liediff v u n)) (cdr e)))
719 (t (merror "~M is not a tensorial expression liediff can handle" e))
723 (defmfun $liediff (v e) (liediff v e 1))
725 (defmfun $rediff (x) (meval '(($ev) x $idiff)))
727 (defmfun $undiff (x)
728 (cond
729 ((atom x) x)
731 (rpobj x)
732 (cond
734 (cdddr x)
735 (nconc
736 (list '(%idiff) (list (car x) (cadr x) (caddr x)))
737 (putinones (cdddr x))
740 (t x)
744 (mysubst0
745 (simplifya (cons (ncons (caar x)) (mapcar (symbol-function '$undiff) (cdr x))) t)
752 ;;(defmfun $evundiff (x) ($rediff ($undiff x)))
753 (defmfun $evundiff (x) (meval (list '($ev) ($undiff x) '$nouns)))
755 (defun putinones (e)
756 (cond
757 ((cdr e) (cons (car e) (cons 1. (putinones (cdr e)))))
758 (t (list (car e) 1.))
764 (defmfun $lorentz_gauge n
765 (cond ((equal n 0) (merror "LORENTZ_GAUGE requires at least one argument"))
766 ((equal n 1) (lorentz (arg 1) nil))
767 (t (lorentz (arg 1)
768 ((lambda (l) (cond ((loop for v in l
769 always (symbolp v)) l)
770 (t (merror
771 "Invalid tensor name(s) in argument to LORENTZ_GAUGE"))))
772 (listify (f- 1 n)))))))
774 ;Lorentz contraction of E: indexed objects with a derivative index matching a
775 ;contravariant index become 0. If L is NIL then do this for all indexed objects
776 ;otherwise do this only for those indexed objects whose names are members of L.
778 (defun lorentz (e l)
779 (cond ((atom e) e)
780 ((rpobj e)
781 (cond ((and (or (null l) (member (caar e) l :test #'eq))
782 (intersect (cdaddr e) (cdddr e)))
784 (t e)))
785 (t (mysubst0
786 (simplifya
787 (cons (ncons (caar e))
788 (mapcar (function (lambda (q) (lorentz q l)))
789 (cdr e)))
790 t) e))))
792 (defun less (x y) ;alphanumeric compare
793 (cond ((numberp x)
794 (cond ((numberp y) (< x y))
795 (t (alphalessp (ascii x) y))))
796 (t (cond ((numberp y) (alphalessp x (ascii y)))
797 (t (alphalessp x y))))))
799 ;; Christoffels contains all Christoffel-like symbols: i.e., symbols
800 ;; that make sense only with certain index patterns. These symbols are
801 ;; excluded from contractions, because those would produce illegal
802 ;; index combinations (e.g., ichr1([a,b],[c])). However, special rules
803 ;; exist to convert a covariant symbol into a mixed symbol and vice
804 ;; versa; for instance, g^ad*ichr1_bcd will contract to ichr2_bc^a.
805 (declare-top (special christoffels christoffels1 christoffels2))
807 (setq christoffels1 '($ichr1 %ichr1 $icc1 %icc1 $ifc1 %ifc1
808 $inmc1 %inmc1 $ikt1 %ikt1))
809 (setq christoffels2 '($ichr2 %ichr2 $icc2 %icc2 $ifc2 %ifc2
810 $inmc2 %inmc2 $ikt2 %ikt2))
811 (setq christoffels (append christoffels1 christoffels2 '(%ifb $ifb %itr $itr)))
813 ;; Main contraction function
814 (defmfun $contract (e)
815 (cond
816 ((atom e) e)
817 ((rpobj e) (contract5 e))
819 (eq (caar e) 'mtimes)
820 (mysubst0 (simplifya (cons '(mtimes) (contract4a e)) nil) e)
823 (eq (caar e) 'mplus)
824 (mysubst0 (simplus (cons '(mplus) (mapcar (symbol-function '$contract) (cdr e))) 1. t) e)
827 (mysubst0 (simplifya (cons (car e) (mapcar (symbol-function '$contract) (cdr e))) nil) e)
832 (defun contract4a (e)
833 (prog (l1 l2)
834 (setq l1 nil l2 nil)
835 (dolist (o (cdr e))
836 (cond
837 ((or (atom o) (atom (car o))) (setq l1 (cons o l1)))
839 (and (eq (caar o) 'mexpt) (eql (caddr o) -1))
840 (setq l2 (cons (cadr o) l2))
842 (t (setq l1 (cons o l1)))
845 (cond (l1 (setq l1 (contract4 (cons '(mtimes) l1)))))
846 (cond (l2 (setq l1 (cons (list '(mexpt)
847 (cons '(mtimes)
848 (contract4 (cons '(mtimes) l2))
853 ))))
854 (return l1)
858 ;; Contract a single tensor with itself
859 (defun contract5 (e)
860 (prog
861 ( ; See if e contracts with itself, find contraction symbol
862 (c (or (and (rpobj e) (getcon (caar e))) (return e)))
864 symbol
867 (c (getcon (caar e)) (cdr c))
869 ((or (eq (caar c) (caar e)) (null c)) (cond (c (cdar c)) (t nil)) )
873 (return
874 (cond
875 ((or (null symbol) (member (caar e) christoffels :test #'eq)) e)
878 (prog (cov con f sgn)
879 (setq sgn (cond ((rpobj ($canform e)) 1) (t -1))
880 cov (contractinside (derat (cadr e)))
881 con (derat (caddr e))
882 f (not (equal cov (derat (cadr e))))
884 ; Calling contract2 here won't do the trick as it messes up the
885 ; order of indices. So we remove indices that appear both in cov
886 ; and in con the hard way, with a do loop.
888 ((i cov (cdr i)))
889 ((null i))
890 (cond
891 ((not (atom (car i))))
893 (member (car i) con)
894 (setq f t con (delete (car i) con) cov (delete (car i) cov))
898 (setq c
899 (nconc
900 (list (cond (f (list symbol)) (t (car e))) cov con)
901 (cdddr e)
904 (return (cond ((and f (eql sgn -1)) (list '(mtimes) sgn c)) (t c)))
912 (defun head (x) (cond ((atom x) nil) (t (cons (car x) nil))))
914 (defun firstintersect (l1 l2) (head (intersect l1 l2)))
916 ;; Remove like members. Return (cons l1 l2) or nil if no like members found.
917 (defun contract2 (l1 l2)
919 (lambda (i) (and i (cons (setdiff l1 i) (setdiff l2 i))))
920 (firstintersect l1 l2)
924 ;; Return a list with those members of s1 that are not in s2
925 (defun setdiff (s1 s2)
927 ((j s1 (cdr j)) (a))
928 ((null j) (reverse a))
930 (and (not (numberp (car j))) (member (car j) s2 :test #'eq))
931 (setq a (cons (car j) a))
936 (defun contract3 (it lst) ;Tries to contract IT with some element of LST.
937 (prog (frst r rest) ;If none occurs then return NIL otherwise return
938 ;a list whose first member is the result of
939 ;contraction and whose cdr is a top-level copy
940 ;of LST with the element which contracted
941 ;removed.
942 loop (setq frst (car lst) lst (cdr lst))
943 ;; (and (eq (caar frst) '%kdelta) (go skip))
944 (and (setq r (contract1 it frst))
945 (return (cons r (nconc (nreverse rest) lst))))
946 ;Try contraction in reverse order since the
947 ;operation is commutative.
948 ;; skip (and (zl-get (caar frst) 'contractions)
949 skip (and (getcon (caar frst))
950 (setq r (contract1 frst it))
951 (return (cons r (nconc (nreverse rest) lst))))
952 (and (null lst) (return nil))
953 (setq rest (cons frst rest))
954 (go loop)))
956 (defun contract4 (l) ;contracts products
957 (prog (l1 l2 l3 f cl sf)
958 (setq cl (cdr l)) ;Following loop sets up 3 lists from the factors
959 ;on L: L1 - atoms or the contraction of non
960 ;indexed objects (the contraction is to handle
961 ;sub-expressions in case E is not fully expanded
962 ;as in A*B*(C*D+E*F). ), L2 - indexed objects in
963 ;L with contraction property, L3 - indexed
964 ;objects in L without contraction property
965 again(setq f (car cl) cl (cdr cl))
966 (cond ((atom f) (setq l1 (cons f l1)))
967 ((rpobj f)
968 ;;*** contract5 may return a negative result
969 (setq f (contract5 f))
970 (cond (
971 (and (or (eq (car f) '(mtimes)) (eq (car f) '(mtimes simp))) (eql (cadr f) -1))
972 (setq l1 (cons -1 l1) f (caddr f)) ))
973 (cond ((getcon (caar f))
974 (setq l2 (cons f l2)))
975 (t (setq l3 (cons f l3)))))
976 (t (setq l1 (cons ($contract f) l1))))
977 (and cl (go again))
978 (and (null l2) (return (nconc l1 l3)))
979 (and (null (cdr l2)) (setq cl l2) (go loop2+1))
980 ;If L2 is empty then no more contractions are
981 ;needed. If L2 has only 1 member then just
982 ;contract it with L3 otherwise contract the
983 ;members of L2 with themselves. The following
984 ;loop goes down L2 trying to contract members
985 ;with other members according to the following
986 ;method: moving from front to end take current
987 ;member (F) and see if it contracts with any
988 ;elements in the rest of the list (this is done
989 ;by CONTRACT3). If it doesn't then add it to CL.
990 ;If it does then take result of contraction and
991 ;add to L1, L2, or L3 as above.
992 loop1(setq f (car l2) l2 (cdr l2))
993 (cond ((null (setq sf (contract3 f l2)))
994 (setq cl (cons f cl)))
996 ;;*** contract3 may also return a negative result
997 (setq sf (mapcar #'(lambda (x)
998 (cond ((atom x) x) (
999 (and (or (equal (car x) '(mtimes)) (equal (car x) '(mtimes simp))) (eql (cadr x) -1))
1000 (setq l1 (cons -1 l1)) (caddr x)) (t x))
1001 ) sf ) )
1003 (setq l2 (cdr sf) sf (car sf))
1004 (cond ((atom sf) (setq l1 (cons sf l1)))
1005 ((rpobj sf)
1006 ;; (cond ((zl-get (caar sf)
1007 ;; 'contractions)
1008 (cond ((getcon (caar sf))
1009 (setq l2 (cons sf l2)))
1010 (t (setq l3 (cons sf l3)))))
1011 (t (setq l1 (cons sf l1))))))
1012 ;If L2 has at least 2 elements left then
1013 ;continue loop. If L2 has 1 element and CL
1014 ;is not empty and there were some contractions
1015 ;performed last time then add CL to L2 and try
1016 ;again. Otherwise add L2 to CL and quit.
1017 (and l2
1018 (cond ((cdr l2) (go loop1))
1019 ((and cl sf)
1020 (setq sf nil l2 (cons (car l2) cl) cl nil)
1021 (go loop1))
1022 (t (setq cl (nconc l2 cl)))))
1023 ;The following loop goes down CL trying to
1024 ;contract each member with some member in L3. If
1025 ;there is not a contraction then the element
1026 ;from CL is added onto L3 (this causes elements
1027 ;of CL to be contracted with each other). If
1028 ;there is a contraction then the result is added
1029 ;onto L3 by setting L3 to the result of
1030 ;CONTRACT3 here if CL is known not to be null.
1031 ;If L3 is empty then there is nothing left to
1032 ;contract.
1033 loop2(and (null cl) (return (nconc l1 l3)))
1034 loop2+1
1035 (and (null l3) (return (nconc l1 cl)))
1036 (setq f (car cl) cl (cdr cl))
1037 (cond ((setq sf (contract3 f l3))
1038 ;;*** contract3 may also return a negative result
1039 (setq sf (mapcar #'(lambda (x)
1040 (cond ((atom x) x) (
1041 (and (or (equal (car x) '(mtimes)) (equal (car x) '(mtimes simp))) (eql (cadr x) -1))
1042 (setq l1 (cons -1 l1)) (caddr x)) (t x))
1043 ) sf ) )
1045 (setq l3 sf))
1046 (t (setq l3 (cons f l3))))
1047 (go loop2)))
1049 ;; Create a 'normalized' (i.e., old-style) rpobj
1050 (defmfun $renorm (e &optional (force nil))
1051 (prog (c v)
1052 (and (not (rpobj e)) (merror "Not an RPOBJ: ~M" e))
1053 (and $allsym (setq force t))
1054 (setq c (cdaddr e) v nil)
1056 ((i (reverse (cdadr e)) (cdr i)))
1058 (or (null i) (and (atom (car i)) (not force))) ; Terminating condition
1059 (setq v (append (reverse i) v)) ; Remaining covariant indices
1061 (cond
1062 ((atom (car i)) (setq v (cons (car i) v)))
1063 (t (setq c (cons (caddar i) c)))
1066 (return
1067 (cons (car e) (append (list (cons smlist v) (cons smlist c)) (cdddr e)))
1072 ;; As above, but unconditionally. Not needed.
1073 ;(defun renorm (e) (append (list (car e) ($covi e) ($conti e)) (cdddr e)))
1075 ;; Add a minus sign to all elements in a list
1076 (defun neglist (l)
1077 (cond ((null l) nil)
1078 (t (cons (list '(mtimes simp) -1 (car l)) (neglist (cdr l))))
1082 ;; Create an 'abnormal' (i.e., new-style) rpobj
1083 (defun abnorm (e)
1084 (append (list (car e)
1085 (append ($covi e) (neglist (conti e)))
1086 '((mlist simp)))
1087 (cdddr e)
1091 ;; Substitute using EQUAL, to catch member lists
1092 (defun substlist (b a l)
1093 (cond ((null l) l)
1094 ((equal a (car l)) (cons b (cdr l)))
1095 (t (cons (car l) (substlist b a (cdr l))))
1099 ;; Removes items not in i from l.
1100 (defun removenotin (i l)
1101 (cond ((null l) l)
1102 ((member (car l) i :test #'eq) (cons (car l) (removenotin i (cdr l))))
1103 (t (removenotin i (cdr l)))
1107 ;; Removes items not in i from l. But the ones in l have a minus sign!
1108 (defun removenotinm (i l)
1109 (cond ((null l) l)
1110 ((atom (car l)) (cons (car l) (removenotinm i (cdr l))))
1111 ((and (isprod (caar l)) (eql (cadar l) -1)
1112 (not (member (caddar l) i :test #'eq))) (removenotinm i (cdr l)))
1113 (t (cons (car l) (removenotinm i (cdr l))))
1117 ;; Removes indices duplicated once with and once without a minus sign
1118 (defun contractinside (c)
1120 ((i (minusi c) (cdr i)))
1121 ((null i))
1122 (and (member (car i) c :test #'equal)
1123 (member (list '(mtimes simp) -1 (car i)) c :test #'equal)
1124 (setq c (delete (car i) (delete (list '(mtimes simp) -1 (car i)) c :test #'equal)))
1130 ;; This does the actual contraction of f with g. If f has any derivative
1131 ;; indices then it can't contract g. If f is Kronecker delta then see which of
1132 ;; the covariant, contravariant, or derivative indices matches those in g.
1133 (defun contract1 (f g)
1134 (prog (a b c d e cf sgn)
1135 (when (cdddr f) (return nil))
1136 (setq a (copy-tree (derat (cdadr f))) b (copy-tree (cdaddr f))
1137 c (copy-tree (derat (cadr g))) d (copy-tree (caddr g)) e (copy-tree (cdddr g))
1139 (cond ; This section is all Kronecker-delta code
1141 (or (eq (caar f) '%kdelta) (eq (caar f) '$kdelta))
1143 ; We normalize the indices first
1144 (setq b (append (minusi a) b) a (plusi a))
1146 ;We cannot contract with higher-order or malformed Kronecker deltas
1147 (and (or (/= (length a) 1) (/= (length b) 1 )) (return nil))
1149 (setq a (car a) b (car b))
1150 (return
1151 (simplifya
1152 (cond
1154 (and (cdr c) (not (numberp b)) (member b (cdr c) :test #'eq))
1155 (setq c (subst a b (cdr c)))
1156 (and
1157 (not (member (caar g) christoffels :test #'eq))
1158 (cdr d)
1159 (setq a (contract2 c (cdr d)))
1160 (setq c (car a) d (cons smlist (cdr a)))
1162 (setq c (contractinside c))
1163 (nconc (list (car g) (cons smlist c) d) e)
1166 (and e (not (numberp b)) (member b e :test #'eq))
1167 (nconc (list (car g) c d)
1168 (cond
1169 ($iframe_flag (subst a b e))
1170 (t (itensor-sort (subst a b e)))
1175 (and (cdr d) (not (numberp a)) (member a (cdr d) :test #'eq))
1176 (setq d (subst b a (cdr d)))
1177 (and
1178 (cdr c)
1179 (setq a (contract2 (cdr c) d))
1180 (setq d (cdr a) c (cons smlist (car a)))
1182 (nconc (list (car g) c (cons smlist d)) e)
1185 (and (cdr c) (not (numberp a))
1186 (member (list '(mtimes simp) -1 a) (cdr c) :test #'equal)
1188 (setq c (substlist (list '(mtimes simp) -1 b)
1189 (list '(mtimes simp) -1 a)
1190 (cdr c)
1193 (setq c (contractinside c))
1194 (nconc (list (car g) (cons smlist c) d) e)
1196 (t nil)
1204 ;No tensor can contract Kronecker-deltas, Levi-Civita symbols, or the torsion tensor.
1205 (and
1206 (or (eq (caar g) '$kdelta) (eq (caar g) '%kdelta)
1207 (eq (caar g) '$levi_civita) (eq (caar g) '%levi_civita)
1208 (eq (caar g) '$icurvature) (eq (caar g) '%icurvature)
1209 (eq (caar g) '$itr) (eq (caar g) '%itr)
1211 (return nil)
1214 ;If g has derivative indices then F must be constant in order to contract it
1215 (and e (not (kindp (caar f) '$constant)) (return nil))
1217 ;Contraction property of f is a list of (a.b)'s
1218 (cond
1219 ((setq cf (getcon (caar f))))
1220 (t (return nil))
1223 ; Determine the sign of the result based on the expression's symmetry
1224 ; properties. We use CANFORM to sort indices in the canonical order
1225 ; and then extract the resulting expression's sign.
1226 (setq sgn
1227 (cond ((eql -1 (cadr ($canform (list '(mtimes simp) f g)))) -1) (t 1))
1230 ;If g matches an a then use the b for name of result. If an a is a space
1231 ;use name of G for result.
1232 more
1233 (cond
1235 (eq (caar cf) '/ )
1236 (setq cf (car g))
1239 (eq (caar cf) (caar g))
1240 (setq cf (ncons (cdar cf)))
1243 (or (setq cf (cdr cf)) (return nil))
1244 (go more)
1247 (setq c (cdr c) d (cdr d))
1249 ;If CONTRACT2 of f's contravariant and g's covariant or f's covariant and
1250 ;g's contravariant indices is nil then return nil
1251 (cond
1253 (and b c (setq f (contract2 b c)))
1254 (setq b (car f) c (cdr f))
1257 (and a d (setq f (contract2 a d)))
1258 (setq a (car f) d (cdr f))
1261 (and a (minusi c) (setq f (contract2 a (minusi c))))
1262 ; (cdr f) now contains the free indices in (minusi c).
1263 ; what we need to do is find the corresponding items in c, and remove
1264 ; all other negative indices (i.e., those that were dropped by
1265 ; contract2).
1266 ; What we need to do is remove items from c one by one, and substitute
1267 ; an item from (car f), which we should remove from (car f):
1268 ; for i thru length(c)
1269 ; if c[i] not in (cdr f)
1270 ; if (car f) is nil, remove c[i]
1271 ; otherwise subst c[i]
1272 ; endfor
1273 ; Now set c to what we made of c, a to whatever is left of (cdr f)
1277 (i c (cdr i))
1278 (j (car f))
1281 ((null i) (setq a (removenotin j a) c (reverse k)))
1282 (cond
1284 (or (atom (car i)) (member (caddar i) (cdr f)))
1285 (setq k (cons (car i) k))
1288 (not (null j))
1289 (setq k (cons (car j) k) j (cdr j))
1295 (and (minusi a) c (setq f (contract2 (minusi a) c)))
1298 (i c (cdr i))
1299 (j (car f))
1302 ;; ((null i) (setq c (reverse k) a (append (plusi a) j)))
1303 ((null i)
1304 (setq
1305 c (reverse k)
1306 a (append
1307 (plusi a)
1308 (mapcar #'(lambda (x) (list '(mtimes simp) -1 x)) j)
1312 (cond
1313 ((member (car i) (cdr f)) (setq k (cons (car i) k)))
1315 (not (null j))
1316 (setq k (cons (list '(mtimes simp) -1 (car j)) k) j (cdr j))
1321 (t (return nil))
1323 ;Form combined indices of result
1324 (and d (setq b (append b d)))
1325 (and c (setq a (append c a)))
1326 ;Zl-remove repeated indices
1327 ;; (and (setq f (contract2 a b)) (setq a (car f) b (cdr f)))
1328 ;; (setq a (contractinside a))
1330 ;VTT: Special handling of Christoffel symbols. We can only contract them
1331 ;when we turn ICHR1 into ICHR2 or vice versa; other index combinations are
1332 ;illegal. This code checks if the index pattern is a valid one and replaces
1333 ;ICHR1 with ICHR2 or vice versa as appropriate.
1334 (cond
1336 (member (car cf) christoffels1)
1337 (cond
1338 ; VTT - before anything else, check that we're contracting on the last index only
1339 ((not (equal (append c (last (cdadr g))) (cdadr g))) (return nil))
1341 ;;(and (eql (length a) 2) (eql (length b) 1))
1342 (and (eql (+ (length (plusi a)) (length (minusi b))) 2) (eql (+ (length (plusi b)) (length (minusi a))) 1))
1343 (setq cf
1344 (cons
1345 (elt christoffels2 (position (car cf) christoffels1))
1346 (cdr cf)
1351 ;; (not (and (eql (length a) 3) (eql (length b) 0)))
1352 (not (and (eql (+ (length (plusi a)) (length (minusi b))) 3) (eql (+ (length (plusi b)) (length (minusi a))) 0)))
1353 (return nil)
1358 (member (car cf) christoffels2)
1359 (cond
1361 ;;(and (eql (length a) 3) (eql (length b) 0))
1362 (and (eql (+ (length (plusi a)) (length (minusi b))) 3) (eql (+ (length (plusi b)) (length (minusi a))) 0))
1363 (setq cf
1364 (cons
1365 (elt christoffels1 (position (car cf) christoffels2))
1366 (cdr cf)
1371 ;;(not (and (eql (length a) 2) (eql (length b) 1)))
1372 (not (and (eql (+ (length (plusi a)) (length (minusi b))) 2) (eql (+ (length (plusi b)) (length (minusi a))) 1)))
1373 (return nil)
1377 ((member (car cf) christoffels) (return nil))
1380 (setq f (meval (list cf (cons smlist a) (cons smlist b))))
1381 (and e
1383 ((e e (cdr e)))
1384 ((null e))
1385 (setq f (idiff f (car e)))
1388 (return (cond ((eql sgn -1) (list '(mtimes) sgn f)) (t f)))
1392 ;; In what amounts to quite an abuse of the Kronecker delta concept, we
1393 ;; permit an exceptional index combination of two contravariant indices.
1394 ;; This helps lc2kdt convert Levi-Civita symbols in a manner that does
1395 ;; not require resorting to numeric indices, causing all sorts of problems
1396 ;; with RENAME and CONTRACT.
1397 (defmfun $kdelta (l1 l2)
1398 (setq l2 (append l2 (minusi l1)) l1 (plusi l1))
1399 (cond
1401 (and ($listp l1) ($listp l2) (= ($length l1) 0) (= ($length l2) 2))
1402 (cond
1403 ((eq (cadr l2) (caddr l2)) 1)
1405 (and (numberp (cadr l2)) (numberp (caddr l2)))
1406 (cond
1407 ((= (cadr l2) (caddr l2)) t)
1408 (t 0)
1411 (t (list '(%kdelta) l1 l2))
1415 (and ($listp l1) ($listp l2) (= ($length l1) 2) (= ($length l2) 0))
1416 (cond
1417 ((eq (cadr l1) (caddr l1)) 1)
1419 (and (numberp (cadr l1)) (numberp (caddr l1)))
1420 (cond
1421 ((= (cadr l1) (caddr l1)) t)
1422 (t 0)
1425 (t (list '(%kdelta) l1 l2))
1429 (null (and ($listp l1) ($listp l2) (= (length l1) (length l2))))
1430 (merror "Improper arg to DELTA: ~M" (list '(%kdelta) l1 l2))
1432 (t (delta (cdr l1) (cdr l2)))
1436 ;kdels defines the symmetric combination of the Kronecker symbols
1438 (defmfun $kdels (l1 l2)
1439 (cond ((null (and ($listp l1)
1440 ($listp l2)
1441 (= (length l1) (length l2))))
1442 (merror "Improper arg to DELTA: ~M"
1443 (list '(%kdels) l1 l2)
1445 (t (delta (cdr l1) (cdr l2) 1))))
1447 (defun delta (lower upper &optional (eps -1))
1448 (cond ((null lower) $dim)
1449 ((null (cdr lower))
1450 (cond ((equal (car upper) (car lower))
1451 (cond ((numberp (car upper)) 1.) (t $dim)))
1452 ((and (numberp (car upper)) (numberp (car lower))) 0.)
1453 (t (list '(%kdelta) (cons smlist lower) (cons smlist upper)))))
1454 (t (do ((left nil (append left (ncons (car right))))
1455 (right lower (cdr right))
1456 (result))
1457 ((null right) (simplus (cons '(mplus) result) 1. t))
1458 (setq result (cons (simptimes
1459 (list '(mtimes) (delta (ncons (car right)) (ncons (car upper)) eps)
1460 (delta (append left (cdr right)) (cdr upper) eps)
1461 (cond ((oddp (length left)) eps) (t 1))
1462 ) 1. t
1463 ) result)
1464 )))))
1466 (declare-top (special $outchar $dispflag *linelabel* foobar derivlist))
1469 ;Displays P([L1],[L2],I1,I2,...) by making the elements of L2 into a single
1470 ;atom which serves as the exponent and the elements of L1 and I1,I2,... into a
1471 ;single atom with a comma in between which serves as the subscript.
1473 (defmfun $ishow (f)
1474 (progn (makelabel $linechar)
1475 (cond ($dispflag
1476 (displa (list '(mlabel) *linelabel* (ishow (specrepcheck (derat f)))))
1477 ; (setq $dispflag nil)
1479 (set *linelabel* f)))
1481 (defun ishow (f)
1482 ((lambda (foobar) ;FOOBAR initialized to NIL
1483 (cond ((atom f) f)
1484 ((rpobj f) ;If an indexed object ...
1485 (setq foobar
1486 (cond ((or (covi f) (cdddr f)) ;If covariant or
1487 (cons (list (caar f) ;derivative indices
1488 'array)
1489 (ncons (maknam (cons '$ (splice (covi f)
1490 (cdddr f)))))))
1491 (t (caar f))))
1492 (cond ((conti f) ;If contravariant indices
1493 (list '(mexpt simp)
1494 foobar
1495 ; (cons '(mtimes simp) ;Make indices appear
1496 ; (conti f)))) ;as exponents for
1497 (maknam (cons '$ (splice (conti f) nil))))) ; Changed for wxmaxima
1498 (t foobar))) ;proper display
1500 (cons (car f) (mapcar 'ishow (cdr f))))))
1501 nil)) ;Map onto subparts of F
1503 (defun splice (l1 l2)
1504 (cond (l2 (setq l2 (cons '|,| (splice1 l2)))
1505 (and l1 (setq l2 (nconc (splice1 l1) l2)))
1507 (t (splice1 l1))))
1509 (defun splice1 (l)
1510 (cond ((null (cdr l))(splice2 (car l)))
1511 (t (nconc (splice2 (car l))(cons '| | (splice1 (cdr l)))))))
1513 (defun splice2 (x)
1514 (cond ((fixnump x)(explode x))
1515 (t (cdr (explodec x)))))
1516 ; (t (cdr (explodec (print-invert-case x))))))
1518 (defun deriv (e)
1519 (prog (exp z count v)
1520 (cond ((null (cdr e)) (return (stotaldiff (car e))))
1521 ((null (cddr e)) (nconc e '(1.))))
1522 (setq exp (car e) z (setq e (append e nil)))
1523 loop (cond ((or (null derivlist) (member (cadr z) derivlist :test #'equal))
1524 (go doit)))
1525 ;DERIVLIST is set by $EV
1526 (setq z (cdr z))
1527 loop2(cond ((cdr z) (go loop))
1528 ((null (cdr e)) (return exp))
1529 (t (go noun)))
1530 doit (cond ((null (cddr z))
1531 (merror "Wrong number of args to DERIVATIVE"))
1532 ((not (fixnump (setq count (caddr z)))) (go noun))
1533 ((< count 0.)
1534 (merror "Improper count to DIFF: ~M"
1535 count)))
1536 loop1(setq v (cadr z))
1537 (and (fixnump v)
1538 $vect_coords
1539 (> v 0.)
1540 (not (> v $dim))
1541 (setq v
1542 (cond ((atom $vect_coords)
1543 (meval1 (list (list $vect_coords 'simp 'array)
1544 v)))
1545 ((eq (caar $vect_coords) 'mlist)
1546 (cond ((not (< v
1547 (length $vect_coords)))
1548 (merror
1549 "Coordinate list too short for derivative index"))
1550 (t (nth v $vect_coords))))
1551 (t v))))
1552 (cond ((zerop count) (rplacd z (cdddr z)) (go loop2))
1553 ((zerop1 (setq exp (sdiff exp v))) (return 0.)))
1554 (setq count (1- count))
1555 (go loop1)
1556 noun (return (diff%deriv (cons exp (cdr e))))))
1558 (defun chainrule1 (e x) ; --ys 15.02.02
1559 (prog (y)
1560 (cond ((and (atom e) (eq (setq y (car (mget e 'depends)))
1561 (cadr $coord))) (return (subst x y (chainrule e y))))
1562 (t (return (chainrule e x))))))
1564 (defun diffexpt1 (e x)
1565 ;; RETURN: n*v^n*rename(v'/v) where e=v^n
1566 (list '(mtimes) (caddr e) e
1567 ($rename
1568 (list '(mtimes) (list '(mexpt) (cadr e) -1)
1569 (sdiff (cadr e) x)
1575 ;Redefined so that the derivative of any indexed object appends on the
1576 ;coordinate index in sorted order unless the indexed object was declared
1577 ;constant in which case 0 is returned.
1578 (defun sdiff (e x)
1579 (simplifya
1580 (cond ((mnump e) 0.)
1581 ((and (alike1 e x) (not (and (rpobj e) (rpobj x)))) 1.)
1582 ((or (atom e) (member 'array (cdar e) :test #'eq))
1583 (chainrule1 e x))
1584 ((kindp (caar e) '$constant) 0.) ;New line added
1585 ((eq (caar e) 'mrat) (ratdx e x))
1586 ((eq (caar e) 'mplus)
1587 (simplus (cons '(mplus) (sdiffmap (cdr e) x))
1590 ((eq (caar e) 'mequal)
1591 (list (car e) (sdiff (cadr e) x) (sdiff (caddr e) x)))
1592 ((mbagp e) (cons (car e) (sdiffmap (cdr e) x)))
1593 ((eq (caar e) '$matrix)
1594 (cons (car e)
1595 (mapcar
1596 (function (lambda (y)
1597 (cons (car y)
1598 (sdiffmap (cdr y) x))))
1599 (cdr e))))
1600 ((eq (caar e) 'mtimes)
1601 (addn (sdifftimes (cdr e) x) t))
1602 ((eq (caar e) 'mexpt) (diffexpt e x))
1603 ;; ((rpobj e) (diffrpobj e x)) ;New line added
1604 ;; ((and (boundp '$imetric) (eq (caar e) '%determinant);New line added
1605 ;; (eq (cadr e) $imetric))
1606 ;; ((lambda (dummy)
1607 ;; (setq dummy ($idummy))
1608 ;; (cond ((eq dummy x) (setq dummy ($idummy))))
1609 ;; (list '(mtimes simp) 2. e
1610 ;; (list '($ichr2 simp) (cons smlist (list dummy x))
1611 ;; (cons smlist (ncons dummy)))))
1612 ;; nil))
1614 ((and
1615 (boundp '$imetric)
1616 (rpobj x)
1617 (eq (caar e) '%determinant)
1618 (eq (cadr e) $imetric)
1620 (cond
1621 ((and
1622 (eq (caar x) $imetric)
1623 (eql (length (cdadr x)) 0)
1624 (eql (length (cdaddr x)) 2)
1625 (eql (length (cdddr x)) 0)
1627 (list '(mtimes simp)
1629 (list '(%determinant simp) $imetric)
1630 (list (cons $imetric '(simp))
1631 (list '(mlist simp) (nth 0 (cdaddr x)) (nth 1 (cdaddr x)))
1632 '((mlist simp))
1636 ((and
1637 (eq (caar x) $imetric)
1638 (eql (length (cdadr x)) 2)
1639 (eql (length (cdaddr x)) 0)
1640 (eql (length (cdddr x)) 0)
1642 (list '(mtimes simp)
1643 (list '(%determinant simp) $imetric)
1644 (list (cons $imetric '(simp))
1645 '((mlist simp))
1646 (list '(mlist simp) (nth 0 (cdadr x)) (nth 1 (cdadr x)))
1650 (t 0.)
1655 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1656 ;; Differentiation of tensors with respect to tensors ;;
1657 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1659 ((and (rpobj e) (rpobj x)) ; (merror "Not yet..."))
1660 (cond
1662 ( ;; dg([a,b],[])/dg([],[m,n])
1663 (and
1664 (boundp '$imetric)
1665 (eq (caar e) $imetric)
1666 (eq (caar x) $imetric)
1667 (eql (length (cdadr e)) 2)
1668 (eql (length (cdaddr e)) 0)
1669 (eql (length (cdddr e)) 0)
1670 (eql (length (cdadr x)) 0)
1671 (eql (length (cdaddr x)) 2)
1672 (eql (length (cdddr x)) 0)
1674 (list '(mtimes simp)
1676 (list
1677 (cons $imetric '(simp))
1678 (list '(mlist simp) (nth 0 (cdadr e)) (nth 0 (cdaddr x)))
1679 '((mlist simp))
1681 (list
1682 (cons $imetric '(simp))
1683 (list '(mlist simp) (nth 1 (cdadr e)) (nth 1 (cdaddr x)))
1684 '((mlist simp))
1689 ( ;; dg([],[a,b])/dg([m,n],[])
1690 (and
1691 (boundp '$imetric)
1692 (eq (caar e) $imetric)
1693 (eq (caar x) $imetric)
1694 (eql (length (cdadr e)) 0)
1695 (eql (length (cdaddr e)) 2)
1696 (eql (length (cdddr e)) 0)
1697 (eql (length (cdadr x)) 2)
1698 (eql (length (cdaddr x)) 0)
1699 (eql (length (cdddr x)) 0)
1701 (list '(mtimes simp)
1703 (list
1704 (cons $imetric '(simp))
1705 '((mlist simp))
1706 (list '(mlist simp) (nth 0 (cdaddr e)) (nth 0 (cdadr x)))
1708 (list
1709 (cons $imetric '(simp))
1710 '((mlist simp))
1711 (list '(mlist simp) (nth 1 (cdaddr e)) (nth 1 (cdadr x)))
1716 ( ;; dg([a,b],[],y)/dg([],[m,n])
1717 (and
1718 (boundp '$imetric)
1719 (eq (caar e) $imetric)
1720 (eq (caar x) $imetric)
1721 (eql (length (cdadr e)) 2)
1722 (eql (length (cdaddr e)) 0)
1723 (eql (length (cdddr e)) 1)
1724 (eql (length (cdadr x)) 0)
1725 (eql (length (cdaddr x)) 2)
1726 (eql (length (cdddr x)) 0)
1728 (prog (d1 d2)
1729 (setq d1 ($idummy) d2 ($idummy))
1730 (return
1731 (list '(mtimes simp)
1732 (list
1733 (cons $imetric '(simp))
1734 '((mlist simp))
1735 (list '(mlist simp) d1 d2)
1736 (cadddr e)
1738 (list
1739 '(mplus simp)
1740 (list
1741 '(mtimes simp)
1742 (list
1743 (cons $imetric '(simp))
1744 (list
1745 '(mlist simp)
1746 (nth 0 (cdadr e))
1747 (nth 0 (cdaddr x))
1749 '((mlist simp))
1751 (list
1752 (cons $imetric '(simp))
1753 (list '(mlist simp) d1 (nth 1 (cdaddr x)))
1754 '((mlist simp))
1756 (list
1757 (cons $imetric '(simp))
1758 (list '(mlist simp) (nth 1 (cdadr e)) d2)
1759 '((mlist simp))
1762 (list
1763 '(mtimes simp)
1764 (list
1765 (cons $imetric '(simp))
1766 (list '(mlist simp) (nth 0 (cdadr e)) d1)
1767 '((mlist simp))
1769 (list
1770 (cons $imetric '(simp))
1771 (list
1772 '(mlist simp)
1773 (nth 1 (cdadr e))
1774 (nth 0 (cdaddr x))
1776 '((mlist simp))
1778 (list
1779 (cons $imetric '(simp))
1780 (list '(mlist simp) d2 (nth 1 (cdaddr x)))
1781 '((mlist simp))
1790 ( ;; dg([a,b],[],y)/dg([],[m,n],k)
1791 (and
1792 (boundp '$imetric)
1793 (eq (caar e) $imetric)
1794 (eq (caar x) $imetric)
1795 (eql (length (cdadr e)) 2)
1796 (eql (length (cdaddr e)) 0)
1797 (eql (length (cdddr e)) 1)
1798 (eql (length (cdadr x)) 0)
1799 (eql (length (cdaddr x)) 2)
1800 (eql (length (cdddr x)) 1)
1802 (list '(mtimes simp)
1804 (list
1805 (cons $imetric '(simp))
1806 (list '(mlist simp) (nth 0 (cdadr e)) (nth 0 (cdaddr x)))
1807 '((mlist simp))
1809 (list
1810 (cons $imetric '(simp))
1811 (list '(mlist simp) (nth 1 (cdadr e)) (nth 1 (cdaddr x)))
1812 '((mlist simp))
1814 (list
1815 '(%kdelta simp)
1816 (list '(mlist simp) (cadddr e))
1817 (list '(mlist simp) (cadddr x))
1822 ( ;; dg([a,b],[],y,d)/dg([],[m,n])
1823 (and
1824 (boundp '$imetric)
1825 (eq (caar e) $imetric)
1826 (eq (caar x) $imetric)
1827 (eql (length (cdadr e)) 2)
1828 (eql (length (cdaddr e)) 0)
1829 (eql (length (cdddr e)) 2)
1830 (eql (length (cdadr x)) 0)
1831 (eql (length (cdaddr x)) 2)
1832 (eql (length (cdddr x)) 0)
1834 (prog (d1 d2)
1835 (setq d1 ($idummy) d2 ($idummy))
1836 (return
1837 (list '(mtimes simp)
1838 (list
1839 (cons $imetric '(simp))
1840 '((mlist simp))
1841 (list '(mlist simp) d1 d2)
1842 (nth 0 (cdddr e))
1843 (nth 1 (cdddr e))
1845 (list
1846 '(mplus simp)
1847 (list
1848 '(mtimes simp)
1849 (list
1850 (cons $imetric '(simp))
1851 (list
1852 '(mlist simp)
1853 (nth 0 (cdadr e))
1854 (nth 0 (cdaddr x))
1856 '((mlist simp))
1858 (list
1859 (cons $imetric '(simp))
1860 (list '(mlist simp) d1 (nth 1 (cdaddr x)))
1861 '((mlist simp))
1863 (list
1864 (cons $imetric '(simp))
1865 (list '(mlist simp) (nth 1 (cdadr e)) d2)
1866 '((mlist simp))
1869 (list
1870 '(mtimes simp)
1871 (list
1872 (cons $imetric '(simp))
1873 (list '(mlist simp) (nth 0 (cdadr e)) d1)
1874 '((mlist simp))
1876 (list
1877 (cons $imetric '(simp))
1878 (list
1879 '(mlist simp)
1880 (nth 1 (cdadr e))
1881 (nth 0 (cdaddr x))
1883 '((mlist simp))
1885 (list
1886 (cons $imetric '(simp))
1887 (list '(mlist simp) d2 (nth 1 (cdaddr x)))
1888 '((mlist simp))
1897 ( ;; dg([a,b],[],y,d)/dg([],[m,n],k)
1898 (and
1899 (boundp '$imetric)
1900 (eq (caar e) $imetric)
1901 (eq (caar x) $imetric)
1902 (eql (length (cdadr e)) 2)
1903 (eql (length (cdaddr e)) 0)
1904 (eql (length (cdddr e)) 2)
1905 (eql (length (cdadr x)) 0)
1906 (eql (length (cdaddr x)) 2)
1907 (eql (length (cdddr x)) 1)
1909 (prog (d1 d2 d3 d4)
1910 (setq d1 ($idummy) d2 ($idummy) d3 ($idummy) d4 ($idummy))
1911 (return
1912 (list
1913 '(mtimes simp)
1914 (list
1915 '(mplus simp)
1916 (list
1917 '(mtimes simp)
1918 (list
1919 (cons $imetric '(simp))
1920 (list '(mlist simp) (nth 0 (cdadr e)) d3)
1921 '((mlist simp))
1923 (list
1924 (cons $imetric '(simp))
1925 (list '(mlist simp) d2 d4)
1926 '((mlist simp))
1928 (list
1929 (cons $imetric '(simp))
1930 (list '(mlist simp) (nth 1 (cdadr e)) d1)
1931 '((mlist simp))
1934 (list
1935 '(mtimes simp)
1936 (list
1937 (cons $imetric '(simp))
1938 (list '(mlist simp) (nth 0 (cdadr e)) d2)
1939 '((mlist simp))
1941 (list
1942 (cons $imetric '(simp))
1943 (list '(mlist simp) (nth 1 (cdadr e)) d3)
1944 '((mlist simp))
1946 (list
1947 (cons $imetric '(simp))
1948 (list '(mlist simp) d1 d4)
1949 '((mlist simp))
1953 (list
1954 '(mplus simp)
1955 (list
1956 '(mtimes simp)
1957 (list
1958 '(%kdelta simp)
1959 (list '(mlist simp) (nth 0 (cdaddr x)))
1960 (list '(mlist simp) d3)
1962 (list
1963 '(%kdelta simp)
1964 (list '(mlist simp) (nth 1 (cdaddr x)))
1965 (list '(mlist simp) d4)
1967 (list
1968 '(%kdelta simp)
1969 (list '(mlist simp) (nth 1 (cdddr e)))
1970 (list '(mlist simp) (nth 0 (cdddr x)))
1973 (list
1974 (cons $imetric '(simp))
1975 '((mlist simp))
1976 (list '(mlist simp) d2 d1)
1977 (nth 0 (cdddr e))
1980 (list
1981 '(mtimes simp)
1982 (list
1983 '(%kdelta simp)
1984 (list '(mlist simp) (nth 0 (cdaddr x)))
1985 (list '(mlist simp) d2)
1987 (list
1988 '(%kdelta simp)
1989 (list '(mlist simp) (nth 1 (cdaddr x)))
1990 (list '(mlist simp) d1)
1992 (list
1993 '(%kdelta simp)
1994 (list '(mlist simp) (nth 0 (cdddr e)))
1995 (list '(mlist simp) (nth 0 (cdddr x)))
1998 (list
1999 (cons $imetric '(simp))
2000 '((mlist simp))
2001 (list '(mlist simp) d3 d4)
2002 (nth 1 (cdddr e))
2011 ( ;; dg([a,b],[],y,d)/dg([],[m,n],k,l)
2012 (and
2013 (boundp '$imetric)
2014 (eq (caar e) $imetric)
2015 (eq (caar x) $imetric)
2016 (eql (length (cdadr e)) 2)
2017 (eql (length (cdaddr e)) 0)
2018 (eql (length (cdddr e)) 2)
2019 (eql (length (cdadr x)) 0)
2020 (eql (length (cdaddr x)) 2)
2021 (eql (length (cdddr x)) 2)
2023 (list '(mtimes simp)
2025 (list
2026 (cons $imetric '(simp))
2027 (list '(mlist simp) (nth 0 (cdadr e)) (nth 0 (cdaddr x)))
2028 '((mlist simp))
2030 (list
2031 (cons $imetric '(simp))
2032 (list '(mlist simp) (nth 1 (cdadr e)) (nth 1 (cdaddr x)))
2033 '((mlist simp))
2035 (list
2036 '(%kdelta simp)
2037 (list '(mlist simp) (cadddr e))
2038 (list '(mlist simp) (cadddr x))
2040 (list
2041 '(%kdelta simp)
2042 (list '(mlist simp) (nth 1 (cdddr e)))
2043 (list '(mlist simp) (nth 1 (cdddr x)))
2049 ((and
2050 (eq (caar e) (caar x))
2051 (eql (length (cdadr e)) (length (cdadr x)))
2052 (eql (length (cdaddr e)) (length (cdaddr x)))
2053 (eql (length (cdddr e)) (length (cdddr x)))
2055 (cons '(mtimes)
2056 (cons 1
2057 (append
2058 (mapcar
2059 #'(lambda (x y)
2060 (list
2061 '(%kdelta simp)
2062 (list '(mlist simp) x)
2063 (list '(mlist simp) y)
2065 ) (cdadr e) (cdadr x)
2067 (mapcar
2068 #'(lambda (x y)
2069 (list
2070 '(%kdelta simp)
2071 (list '(mlist simp) x)
2072 (list '(mlist simp) y)
2074 ) (cdaddr x) (cdaddr e)
2076 (mapcar
2077 #'(lambda (x y)
2078 (list
2079 '(%kdelta simp)
2080 (list '(mlist simp) x)
2081 (list '(mlist simp) y)
2084 (cdddr e) (cdddr x)
2090 ((or
2091 (and ;; catchall symbols constructed from the metric tensor
2092 (boundp '$imetric)
2093 (eq (caar x) $imetric)
2094 (member
2095 (caar e)
2096 (cons '$icurvature (cons '%icurvature christoffels))
2099 (and ;; d(some covi)/d(cov metric)
2100 (boundp '$imetric)
2101 (not (eq (caar e) $imetric))
2102 (eq (caar x) $imetric)
2103 (eql (length (cdadr x)) 2)
2104 (eql (length (cdaddr x)) 0)
2105 (eql (length (cdddr x)) 0)
2106 (> (+ (length (cdadr e)) (length (cdddr e))) 0)
2108 (and ;; d(some conti)/d(cont metric)
2109 (boundp '$imetric)
2110 (not (eq (caar e) $imetric))
2111 (eq (caar x) $imetric)
2112 (eql (length (cdadr x)) 0)
2113 (eql (length (cdaddr x)) 2)
2114 (eql (length (cdddr x)) 0)
2115 (> (length (cdaddr e)) 0)
2117 (and ;; da([a,b],y)/da([m,n],k) with a+b=m+n, y=k
2118 (depends (caar e) (caar x))
2119 (eql (+ (length (cdadr e)) (length (cdaddr e)))
2120 (+ (length (cdadr x)) (length (cdaddr x))))
2121 (eql (length (cdddr e)) (length (cdddr x)))
2124 (list '(%derivative) e x)
2126 (t 0.)
2129 ;; End of tensor vs. tensor differentiation
2131 ((not (depends e x))
2132 (cond ((fixnump x) (list '(%derivative) e x))
2133 ((atom x) 0.)
2134 (t (list '(%derivative) e x))))
2135 ;This line moved down
2136 ((eq (caar e) 'mnctimes)
2137 (simplus (list '(mplus)
2138 (list '(mnctimes)
2139 (sdiff (cadr e) x)
2140 (caddr e))
2141 (list '(mnctimes)
2142 (cadr e)
2143 (sdiff (caddr e) x)))
2145 nil))
2146 ((eq (caar e) 'mncexpt) (diffncexpt e x))
2147 ((eq (caar e) '%integrate) (diffint e x))
2148 ((eq (caar e) '%derivative)
2149 (cond ((or (atom (cadr e))
2150 (member 'array (cdaadr e) :test #'eq))
2151 (chainrule1 e x))
2152 ((freel (cdr e) x) 0.)
2153 (t (diff%deriv (list e x 1.)))))
2154 ((member (caar e) '(%sum %product) :test #'eq) (diffsumprod e x))
2155 (t (sdiffgrad e x)))
2159 ; VTT: several of these functions have been copied verbatim from comm.lisp and
2160 ; comm2.lisp, in order to implement indicial differentiation as distinct from
2161 ; differentiation with respect to an external variable.
2163 (defun idiffmap (e x) (mapcar #'(lambda (term) (idiff term x)) e))
2165 (defun idifftimes (l x)
2166 (prog (term left out)
2167 loop (setq term (car l) l (cdr l))
2168 (setq out (cons (muln (cons (idiff term x) (append left l)) t) out))
2169 (if (null l) (return out))
2170 (setq left (cons term left))
2171 (go loop)))
2173 (defun idiffexpt1 (e x)
2174 ;; RETURN: n*v^n*rename(v'/v) where e=v^n
2175 (list '(mtimes) (caddr e) e
2176 ;; ($rename
2177 (list '(mtimes) (list '(mexpt) (cadr e) -1)
2178 (idiff (cadr e) x)
2180 ;; )
2184 (defun idiffexpt (e x)
2185 (if (mnump (caddr e))
2186 (mul3 (caddr e) (power (cadr e) (addk (caddr e) -1)) (idiff (cadr e) x))
2187 (mul2 e (add2 (mul3 (power (cadr e) -1) (caddr e) (idiff (cadr e) x))
2188 (mul2 (simplifya (list '(%log) (cadr e)) t)
2189 (idiff (caddr e) x))))))
2191 (defmfun idiffint (e x)
2192 (let (a)
2193 (cond ((null (cdddr e))
2194 (cond ((alike1 x (caddr e)) (cadr e))
2195 ((and (not (atom (caddr e))) (atom x) (not (free (caddr e) x)))
2196 (mul2 (cadr e) (idiff (caddr e) x)))
2197 ((or ($constantp (setq a (idiff (cadr e) x)))
2198 (and (atom (caddr e)) (free a (caddr e))))
2199 (mul2 a (caddr e)))
2200 (t (simplifya (list '(%integrate) a (caddr e)) t))))
2201 ((alike1 x (caddr e)) (addn (idiffint1 (cdr e) x x) t))
2202 (t (addn (cons (if (equal (setq a (idiff (cadr e) x)) 0)
2204 (simplifya (list '(%integrate) a (caddr e)
2205 (cadddr e) (car (cddddr e)))
2207 (idiffint1 (cdr e) x (caddr e)))
2208 t)))))
2210 (defun idiffint1 (e x y)
2211 (let ((u (idiff (cadddr e) x)) (v (idiff (caddr e) x)))
2212 (list (if (pzerop u) 0 (mul2 u (maxima-substitute (cadddr e) y (car e))))
2213 (if (pzerop v) 0 (mul3 v (maxima-substitute (caddr e) y (car e)) -1)))))
2215 (defun idiff%deriv (e)
2216 (declare (special derivflag))
2217 (let (derivflag) (simplifya (cons '(%idiff) e) t)))
2219 (defun ideriv (e)
2220 (prog (exp z count)
2221 (cond ((null e) (wna-err '$idiff))
2222 ((null (cdr e)) (return (stotaldiff (car e))))
2223 ((null (cddr e)) (nconc e '(1))))
2224 (setq exp (car e) z (setq e (copy-list e)))
2225 loop (if (or (null derivlist) (member (cadr z) derivlist :test #'equal)) (go doit))
2226 ; DERIVLIST is set by $EV
2227 (setq z (cdr z))
2228 loop2(cond ((cdr z) (go loop))
2229 ((null (cdr e)) (return exp))
2230 (t (go noun)))
2231 doit (cond ((nonvarcheck (cadr z) '$idiff))
2232 ((null (cddr z)) (wna-err '$idiff))
2233 ((not (fixnump (caddr z))) (go noun))
2234 ((minusp (setq count (caddr z)))
2235 (merror "Improper count to IDIFF:~%~M" count)))
2236 loop1(cond ((zerop count) (rplacd z (cdddr z)) (go loop2))
2237 ((equal (setq exp (idiff exp (cadr z))) 0) (return 0)))
2238 (setq count (f1- count))
2239 (go loop1)
2240 noun (return (idiff%deriv (cons exp (cdr e))))))
2243 (defmfun idiffncexpt (e x)
2244 ((lambda (base* pow)
2245 (cond ((and (mnump pow) (or (not (fixnump pow)) (< pow 0))) ; POW cannot be 0
2246 (idiff%deriv (list e x 1)))
2247 ((and (atom base*) (eq base* x) (free pow base*))
2248 (mul2* pow (list '(mncexpt) base* (add2 pow -1))))
2249 ((fixnump pow)
2250 ((lambda (deriv ans)
2251 (do ((i 0 (f1+ i))) ((= i pow))
2252 (setq ans (cons (list '(mnctimes) (list '(mncexpt) base* i)
2253 (list '(mnctimes) deriv
2254 (list '(mncexpt) base* (f- pow 1 i))))
2255 ans)))
2256 (addn ans nil))
2257 (idiff base* x) nil))
2258 ((and (not (depends pow x)) (or (atom pow) (and (atom base*) (free pow base*))))
2259 ((lambda (deriv index)
2260 (simplifya
2261 (list '(%sum)
2262 (list '(mnctimes) (list '(mncexpt) base* index)
2263 (list '(mnctimes) deriv
2264 (list '(mncexpt) base*
2265 (list '(mplus) pow -1 (list '(mtimes) -1 index)))))
2266 index 0 (list '(mplus) pow -1)) nil))
2267 (idiff base* x) (gensumindex)))
2268 (t (idiff%deriv (list e x 1)))))
2269 (cadr e) (caddr e)))
2271 (defmfun idiffsumprod (e x)
2272 (cond ((or (not (atom x)) (not (free (cadddr e) x)) (not (free (car (cddddr e)) x)))
2273 (idiff%deriv (list e x 1)))
2274 ((eq (caddr e) x) 0)
2275 (t (let ((u (idiff (cadr e) x)))
2276 (setq u (simplifya (list '(%sum)
2277 (if (eq (caar e) '%sum) u (div u (cadr e)))
2278 (caddr e) (cadddr e) (car (cddddr e)))
2280 (if (eq (caar e) '%sum) u (mul2 e u))))))
2282 (defun idiffgrad (e x)
2283 (let ((fun (caar e)) grad args)
2284 (cond ((and (eq fun 'mqapply) (zl-get (caaadr e) 'grad))
2285 (idiffgrad (cons (cons (caaadr e) nil) (append (cdadr e) (cddr e)))
2287 ((or (eq fun 'mqapply) (null (setq grad (zl-get fun 'grad))))
2288 (if (not (depends e x)) 0 (idiff%deriv (list e x 1))))
2289 ((not (= (length (cdr e)) (length (car grad))))
2290 (merror "Wrong number of arguments for ~:M" fun))
2291 (t (setq args (idiffmap (cdr e) x))
2292 (addn (mapcar
2293 #'mul2
2294 (cdr (substitutel
2295 (cdr e) (car grad)
2296 (do ((l1 (cdr grad) (cdr l1))
2297 (args args (cdr args)) (l2))
2298 ((null l1) (cons '(mlist) (nreverse l2)))
2299 (setq l2 (cons (cond ((equal (car args) 0) 0)
2300 (t (car l1)))
2301 l2)))))
2302 args)
2303 t)))))
2305 (defmfun idiff (e x)
2306 (cond
2307 (($constantp e) 0.)
2308 ((alike1 e x) 1.)
2309 ((or (atom e) (member 'array (cdar e) :test #'eq))
2310 ;; (ichainrule e x))
2311 ;; (idiff%deriv (list e x 1)))
2313 ((kindp (caar e) '$constant) 0.) ;New line added
2314 ((eq (caar e) 'mrat) (ratdx e x))
2315 ((eq (caar e) 'mplus)
2316 (simplus (cons '(mplus) (idiffmap (cdr e) x))
2319 ((eq (caar e) 'mequal)
2320 (list (car e) ($idiff (cadr e) x) ($idiff (caddr e) x)))
2321 ((eq (caar e) '$matrix)
2322 (cons (car e)
2323 (mapcar
2324 (function (lambda (y)
2325 (cons (car y)
2326 (idiffmap (cdr y) x))))
2327 (cdr e))))
2328 ((eq (caar e) 'mtimes)
2329 (addn (idifftimes (cdr e) x) t))
2330 ((eq (caar e) 'mexpt) (idiffexpt1 e x))
2331 ((rpobj e) (diffrpobj e x))
2332 ((and (boundp '$imetric) (eq (caar e) '%determinant)
2333 (eq (cadr e) $imetric))
2334 ((lambda (dummy)
2335 (setq dummy ($idummy))
2336 (cond ((eq dummy x) (setq dummy ($idummy))))
2337 (list '(mtimes simp) 2. e
2338 ;; (list '(($ichr2) simp) (cons smlist (list dummy x))
2339 (list (diffop) (cons smlist (list dummy x))
2340 (cons smlist (ncons dummy)))))
2341 nil))
2342 ((eq (caar e) 'mnctimes)
2343 (simplus (list '(mplus)
2344 (list '(mnctimes)
2345 ($idiff (cadr e) x)
2346 (caddr e))
2347 (list '(mnctimes)
2348 (cadr e)
2349 ($idiff (caddr e) x)))
2351 nil))
2352 ((eq (caar e) 'mncexpt) (idiffncexpt e x))
2353 ((eq (caar e) '%integrate) (idiffint e x))
2354 ((eq (caar e) '%derivative)
2355 (cond ((or (atom (cadr e))
2356 (member 'array (cdaadr e) :test #'eq))
2357 ;; (ichainrule e x))
2358 ;; (idiff%deriv (list e x 1)))
2360 ;; ((freel (cdr e) x) 0.)
2361 (t (idiff%deriv (list e x 1.)))))
2362 ((member (caar e) '(%sum %product) :test #'eq) (idiffsumprod e x))
2363 (t (idiffgrad e x))
2367 (defun diffrpobj (e x) ;Derivative of an indexed object
2368 (cond
2369 ( ; Special case: functions declared with coord()
2370 (and
2371 (member (caar e) $coord :test #'eq) (null (cdadr e))
2372 (equal (length (cdaddr e)) 1) (null (cdddr e))
2374 (delta (ncons x) (cdaddr e))
2376 (t ; Everything else
2377 (nconc
2378 (list (car e) (cadr e) (caddr e))
2379 (cond
2381 (null (cdddr e))
2382 (ncons x)
2384 ( ; Derivative indices do not commute when frames are used
2385 (or $iframe_flag $itorsion_flag)
2386 (append (cdddr e) (ncons x))
2389 (itensor-sort (append (cdddr e) (ncons x)))
2398 (defmfun $lc0 (l1)
2399 (prog (a b c sign)
2400 (setq a (cdr l1))
2401 (ifnot (and a (cdr a)) (return (list '(%levi_civita) l1)))
2402 (setq b a)
2403 loop1(ifnot (fixnump (car a)) (return (list '(%levi_civita) l1)))
2404 (and (setq a (cdr a)) (go loop1))
2405 loop3(setq a (car b) b (cdr b) c b)
2406 loop2(cond ((= (car c) a) (return 0.))
2407 ((< (car c) a) (setq sign (not sign))))
2408 (and (setq c (cdr c)) (go loop2))
2409 (and (cdr b) (go loop3))
2410 (return (cond (sign -1.) (t 1.)))))
2411 (defmfun $levi_civita (l1 &optional (l2 nil))
2412 (cond
2413 ((eq l2 nil) ($lc0 l1))
2414 ((like l1 '((mlist)))
2415 (prog (l) (setq l nil)
2416 (do ((i ($length l2) (1- i))) ((< i 1)) (setq l (cons i l)))
2417 (return (list '($kdelta simp) (cons smlist l) l2))
2419 ((like l2 '((mlist)))
2420 (prog (l) (setq l nil)
2421 (do ((i ($length l1) (1- i))) ((< i 1)) (setq l (cons i l)))
2422 (return (list '($kdelta simp) l1 (cons smlist l)))
2424 (t (merror "Mixed-index Levi-Civita symbols not supported"))
2428 ;; simplification rules for the totally antisymmetric LC symbol
2429 (defun $lc_l (e)
2430 (prog (l1 l2 l nn)
2431 (catch 'match
2432 (cond ((atom e) (matcherr)))
2433 (cond ((atom (car e)) (matcherr)))
2434 (cond ((not (or (eq (caar e) '$levi_civita) (eq (caar e) '%levi_civita))) (matcherr)))
2435 (cond ((not ($listp (setq l1 ($covi e)))) (matcherr)))
2436 (cond ((not (alike1 '((mlist simp)) (setq l2 ($conti e)))) (matcherr)))
2437 (cond ((cdddr e) (matcherr)))
2438 (setq nn ($length l1))
2439 (setq l nil)
2440 (do ((i nn (1- i))) ((< i 1)) (setq l (cons ($idummy) l)))
2441 (return (values (list '(mtimes simp) ($kdelta l1 (cons smlist l))
2442 (list (cons (caar e) '(simp)) (cons smlist l) (ncons smlist))
2443 (list '(mexpt simp) (meval (list 'mfactorial nn)) -1)) t)
2449 (defun $lc_u (e)
2450 (prog (l1 l2 l nn)
2451 (catch 'match
2452 (cond ((atom e) (matcherr)))
2453 (cond ((atom (car e)) (matcherr)))
2454 (cond ((not (or (eq (caar e) '$levi_civita) (eq (caar e) '%levi_civita))) (matcherr)))
2455 (cond ((not (alike1 '((mlist simp)) (setq l1 ($covi e)))) (matcherr)))
2456 (cond ((not ($listp (setq l2 ($conti e)))) (matcherr)))
2457 (cond ((cdddr e) (matcherr)))
2458 (setq nn ($length l2))
2459 (setq l nil)
2460 (do ((i nn (1- i))) ((< i 1)) (setq l (cons ($idummy) l)))
2461 (return (values (list '(mtimes simp) ($kdelta (cons smlist l) l2)
2462 (list (cons (caar e) '(simp)) (ncons smlist) (cons smlist l))
2463 (list '(mexpt simp) (meval (list 'mfactorial nn)) -1)) t)
2469 (add2lnc '$lc_l $rules)
2470 (add2lnc '$lc_u $rules)
2472 (declare-top (special e empty $flipflag))
2474 (setq $flipflag nil empty '((mlist simp) ((mlist simp)) ((mlist simp))))
2476 (defun nonumber (l)
2477 (cond
2478 ((numberp (car l)) (nonumber (cdr l)))
2479 ((eq l nil) ())
2480 (t (cons (car l) (nonumber (cdr l))))
2484 (defun removeindex (e l)
2485 (cond ((null l) nil)
2486 ((atom e)
2487 (cond ((eq e (car l)) (cdr l))
2488 (t (cons (car l) (removeindex e (cdr l))))
2490 (t (removeindex (cdr e) (removeindex (car e) l)))
2494 (defun indices (e)
2495 (prog (top bottom x y p q r)
2496 (setq top nil bottom nil)
2497 (cond
2499 (rpobj e)
2500 (setq top (nonumber (conti e))
2501 bottom (nonumber (append (covi e) (cdddr e))))
2503 ((atom e))
2505 (and (eq (caar e) 'mexpt) (eql (caddr e) -1))
2506 (setq x (indices (cadr e)) bottom (append bottom (car x))
2507 top (append top (cadr x)))
2510 (and (member (caar e) '(%derivative $diff) :test #'eq)
2511 (or (eql (length e) 3) (eql (cadddr e) 1)))
2512 (setq x (indices (cadr e)) bottom (append bottom (cadr x))
2513 top (append top (car x)))
2514 (setq x (indices (caddr e)) bottom (append bottom (car x))
2515 top (append top (cadr x)))
2518 (member (caar e) '(mtimes mnctimes mncexpt) :test #'eq)
2519 (dolist (v (cdr e))
2520 (setq x (indices v) bottom (append bottom (cadr x))
2521 top (append top (car x)))
2525 (member(caar e) '(mplus mequal) :test #'eq)
2526 (setq top (indices (cadr e)) bottom (cadr top) top (car top))
2527 (setq p (intersect top bottom) q (removeindex p bottom)
2528 p (removeindex p top))
2529 (dolist (v (cddr e))
2530 (setq x (indices v) y (cadr x) x (car x))
2531 (setq r (intersect x y) x (removeindex r x) y (removeindex r y))
2532 (when
2533 (not (and (samelists x p) (samelists y q)))
2534 (merror "Improper indices in ~M" v)
2536 (setq top (union top r) bottom (union bottom r))
2540 (member (caar e) '($sum %sum) :test #'eq)
2541 (setq top (list (caddr e)) bottom (list (caddr e)))
2544 (member (caar e) '(%idiff $idiff) :test #'eq)
2545 ;;; This code would count derivative indices as covariant. However, it is
2546 ;;; not needed. If the user wants to count derivative indices, those should
2547 ;;; be part of the tensor expression; if the expression is undiff'd, there
2548 ;;; must be a reason!
2549 ;; (do
2550 ;; ((f (cddr e) (cddr f)))
2551 ;; ((null f))
2552 ;; (do
2553 ;; ((i 1 (1+ i)))
2554 ;; ((> i (cond ((cadr f) (cadr f)) (t 1))))
2555 ;; (setq bottom (cons (car f) bottom))
2556 ;; )
2557 ;; )
2558 (setq x (indices (cadr e)) bottom (append bottom (cadr x))
2559 top (append top (car x)))
2562 (return (list top bottom))
2566 (defmfun $indices (e)
2567 (prog (top bottom x)
2568 ;; (setq top (indices e) bottom (cadr top) top (car top) x (intersect top bottom))
2569 (setq top (indices e) bottom (cadr top) top (car top) x (cond ($flipflag (intersect bottom top)) (t (intersect top bottom))))
2570 (setq top (removeindex x top) bottom (removeindex x bottom))
2571 (return (cons smlist (list (cons smlist (append top bottom)) (cons smlist x))))
2575 (defun samelists (a b) ;"True" if A and B have the same distinct elements
2576 (and (= (length a) (length b))
2577 (do ((l
2579 (cdr l)))
2580 (nil)
2581 (cond ((null l) (return t))
2582 ((member (car l) b :test #'eq))
2583 (t (return nil))))))
2585 (defmfun $flush n ;Replaces the given (as arguments to FLUSH) indexed
2586 (prog (l) ;objects by zero if they have no derivative indices.
2587 (cond ((< n 2) (merror "FLUSH takes at least 2 arguments"))
2588 ((not
2589 (loop for v in (setq l (listify (f- 1 n)))
2590 always (symbolp v)))
2591 ; (apply 'and (mapcar 'symbolp
2592 ; (setq l (listify (f- 1 n))) ))
2593 (merror "All arguments but the first must be names of
2594 indexed objects")) (t (return (flush (arg 1) l t))))))
2596 (defmfun $flushd n ;Replaces the given (as arguments to FLUSHD) indexed
2597 (prog (l) ;objects by zero if they have any derivative indices.
2598 (cond ((< n 2) (merror "FLUSH takes at least 2 arguments"))
2599 ((not
2600 (loop for v in (setq l (listify (f- 1 n)))
2601 always (symbolp v))
2602 ; (apply 'and (mapcar 'symbolp
2603 ; (setq l (listify (f- 1 n)))))
2605 (merror "All arguments but the first must be names of
2606 indexed objects")) (t (return (flush (arg 1) l nil))))))
2608 (defun flush (e l flag)
2609 (cond ((atom e) e)
2610 ((rpobj e)
2611 (cond ((not (member (caar e) l :test #'eq)) e)
2612 ((not (null (cdddr e)))
2613 (cond (flag e)
2614 (t 0)))
2615 (t (cond (flag 0)
2616 (t e)))))
2617 (t (subst0 (cons (ncons (caar e))
2618 (mapcar (function (lambda (q) (flush q l flag)))
2619 (cdr e))) e))))
2621 (defmfun $flushnd (e name n) ;Replaces by zero all indexed objects
2622 (cond ((atom e) e) ;that have n or more derivative indices
2623 ((rpobj e)
2624 (cond ((and (equal (caar e) name)
2625 (> (length (cdddr e)) (1- n)))
2627 (t e)))
2628 (t (subst0 (cons (ncons (caar e))
2629 (mapcar (function
2630 (lambda (q) (funcall (symbol-function '$flushnd) q name n)))
2631 (cdr e))) e))))
2633 (defvar itensor-n)
2635 (defmfun $rename nargs
2636 (let (index)
2637 (cond ((= nargs 1) (setq index 1)) (t (setq index (arg 2))))
2638 (rename (arg 1) index)))
2640 (defun rename (e index) ;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 itensor-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 (lambda (e) (rename e index)) (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 itensor-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 itensor-n))) itensor-n (1+ itensor-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 (defun itensor-sort (l) (cond ((cdr l) (sort l 'less)) (t l)))
2692 ;Sort into ascending order
2694 (defmfun $remcomps (tensor)
2695 (zl-remprop tensor 'expr) (zl-remprop tensor 'carrays)
2696 (zl-remprop tensor 'texprs) (zl-remprop tensor 'indexed)
2697 (zl-remprop tensor 'indexed) (zl-remprop tensor 'tsubr)
2698 (and (functionp tensor) (fmakunbound tensor))
2699 '$done)
2701 (defmfun $indexed_tensor (tensor)
2702 (let (fp new)
2703 (and (zl-get tensor 'expr)
2704 (merror "~M has expr" tensor))
2705 ; (args tensor nil)
2706 (and (setq fp (zl-get tensor 'subr))
2707 (progn (setq new (gensym))(putprop new fp 'subr)
2708 (zl-remprop tensor 'subr)(putprop tensor new 'tsubr)))
2709 (putprop tensor t 'indexed)
2710 (putprop tensor (subst tensor 'g '(lambda nn (tensoreval (quote g)(listify nn)))) 'expr)
2711 (eval (subst tensor 'g (quote (defmfun g nn (tensoreval 'g (listify nn))))))
2712 '$done))
2715 (defun allfixed (l)
2716 (and l (fixnump (car l)) (or (null (cdr l)) (allfixed (cdr l)))))
2718 (defun tensoreval (tensor indxs)
2719 ((lambda (der con)
2720 (and (cdr indxs) (setq con (cdadr indxs) der (cddr indxs)))
2721 (setq tensor (select tensor (cdar indxs) con der))
2722 ) nil nil))
2724 (defmfun $components (tensor comp)
2725 ((lambda (len1 len2 len3 name prop)
2726 (cond ((not (rpobj tensor)) (merror "Improper 1st arg to COMPONENTS: ~M" tensor)))
2727 (setq len1 (length (covi tensor)) len2 (length (conti tensor)) len3 (length (deri tensor)))
2728 (and (not (atom comp))
2729 (eq (caar comp) '$matrix)
2730 (cond ((= (f+ (f+ len1 len2) len3) 2)
2731 (setq name (gensym))
2732 (set name comp)
2733 (setq comp name)
2735 (t (merror "Needs two indices for COMPONENTS from matrix:~%~M" tensor))
2739 (cond ((and (symbolp comp) (> (f+ (f+ len1 len2) len3) 0))
2740 (setq prop 'carrays)
2742 ((samelists (setq name (append (covi tensor) (conti tensor) (deri tensor))) (cdadr ($indices comp)))
2743 (setq prop 'texprs comp (cons comp name))
2745 (t (merror "Args to COMPONENTS do not have the same free indices"))
2747 (setq tensor (caar tensor) len1 (list len1 len2 len3))
2748 (cond ((and (setq name (zl-get tensor prop))
2749 (setq len2 (assoc len1 name :test #'equal))
2751 (rplacd len2 comp)
2753 (t (putprop tensor (cons (cons len1 comp) name) prop))
2755 (or (zl-get tensor 'indexed) ($indexed_tensor tensor))
2756 '$done
2758 nil nil nil nil nil
2762 (defun select (tensor l1 l2 l3)
2763 (prog
2765 (setq l2 (append (minusi l1) l2) l1 (plusi l1))
2766 (return
2768 (lambda
2769 (prop subs idx)
2770 (cond
2772 (and
2773 (allfixed subs)
2774 (setq prop (zl-get tensor 'carrays))
2775 (setq prop (assoc idx prop :test #'equal))
2777 (cond
2779 (alike1
2780 (setq prop (cons (list (cdr prop) 'array) subs))
2781 (setq subs (meval prop))
2785 (t subs)
2789 (setq prop (assoc idx (zl-get tensor 'texprs) :test #'equal))
2790 (sublis
2791 (mapcar #'cons(cddr prop) subs)
2792 ($rename (cadr prop) (cond ((boundp 'itensor-n) itensor-n) (t 1)))
2796 (setq prop (zl-get tensor 'tsubr))
2797 (apply
2798 prop
2799 (list (cons smlist l1) (cons smlist l2) (cons smlist l3))
2803 (not (eq l3 nil))
2804 (apply '$idiff (select tensor l1 l2 (cdr l3)) (list (car l3)))
2808 (append
2809 (list (list tensor 'simp) (cons smlist l1) (cons smlist l2))
2815 nil (append l1 l2 l3) (list (length l1)(length l2)(length l3))
2822 (defmfun $entertensor nargs
2823 (prog (fun contr cov deriv)
2824 (cond
2826 (> nargs 1)
2827 (merror "ENTERTENSOR takes 0 or 1 arguments only")
2830 (= nargs 0)
2831 (mtell "Enter tensor name: ")
2832 (setq fun (meval (retrieve nil nil)))
2834 ((setq fun (arg 1)))
2836 (mtell "Enter a list of the covariant indices: ")
2837 (setq cov (checkindex (meval (retrieve nil nil)) fun))
2838 (cond ((atom cov) (setq cov (cons smlist (ncons cov)))))
2839 (mtell "Enter a list of the contravariant indices: ")
2840 (setq contr (checkindex (meval (retrieve nil nil)) fun))
2841 (cond ((atom contr) (setq contr (cons smlist (ncons contr)))))
2842 (mtell "Enter a list of the derivative indices: ")
2843 (setq deriv (checkindex (meval (retrieve nil nil)) fun))
2844 (setq deriv
2845 (cond ((atom deriv) (ncons deriv))
2846 (t (cdr deriv))
2849 (cond
2851 (memberl (cdr cov) deriv)
2852 (mtell "Warning: There are indices that are both covariant ~
2853 and derivative%")
2856 (return ($ishow (nconc (list (list fun 'simp) cov contr) deriv)))
2860 (defun checkindex (e f)
2861 (cond ((and (atom e) (not (eq e f))) e)
2862 ((and (eq (caar e) 'mlist)
2863 (loop for v in (cdr e) always (atom v))
2864 ; (apply 'and (mapcar 'atom (cdr e)))
2865 (not (member f e :test #'eq))) e)
2866 (t (merror "Indices must be atoms different from the tensor name"))))
2868 (defun memberl (a b)
2869 (do ((l a (cdr l))
2870 (carl))
2871 ((null l) nil)
2872 (setq carl (car l))
2873 (cond ((and (symbolp carl) (member carl b :test #'equal))
2874 (return t)))))
2876 (defun consmlist (l) (cons smlist l)) ;Converts from Lisp list to Macsyma list
2878 ;$INDICES2 is similar to $INDICES except that here dummy indices are picked off
2879 ;as they first occur in going from left to right through the product or indexed
2880 ;object. Also, $INDICES2 works only on the top level of a product and will
2881 ;miss indices for products of sums (which is used to advantage by $IC_CONVERT).
2883 (defmfun $indices2 (e)
2884 (cond ((atom e) empty)
2885 ((not (or (member (caar e) '(mtimes mnctimes) :test #'eq) (rpobj e)))
2886 ($indices e))
2887 (t ((lambda (indices)
2888 (do ((ind indices) (free) (dummy) (index))
2889 ((null ind)
2890 (consmlist (list (consmlist (nreverse free))
2891 (consmlist (nreverse dummy)))))
2892 (setq index (car ind))
2893 (cond ((member index dummy :test #'equal)
2894 (merror "~M has improper indices"
2895 (ishow e)))
2896 ((member index (cdr ind) :test #'equal)
2897 (setq dummy (cons index dummy)
2898 ind (delete index (copy-tree (cdr ind))
2899 :count 1 :test #'equal)))
2900 (t (setq free (cons index free)
2901 ind (cdr ind))))))
2902 (do ((e (cond ((member (caar e) '(mtimes mnctimes) :test #'eq) (cdr e))
2903 (t (ncons e))) (cdr e))
2904 (a) (l))
2905 ((null e) l)
2906 (setq a (car e))
2907 (and (rpobj a) (setq l (append l (covi a) (conti a)
2908 (cdddr a)))))))))
2910 (defmfun $changename (a b e) ;Change the name of the indexed object A to B in E
2911 (prog (old indspec ncov ncontr) ;INDSPEC is INDex SPECification flag
2912 (cond ((not (or (and (symbolp a) (setq old a))
2913 (and ($listp a) (equal (length (cdr a)) 3)
2914 (symbolp (setq old (cadr a)))
2915 (fixnump (setq ncov (caddr a)))
2916 (fixnump (setq ncontr (cadddr a)))
2917 (setq indspec t))))
2918 (merror "Improper first argument to CHANGENAME: ~M" a))
2919 ((not (symbolp b))
2920 (merror "Second argument to CHANGENAME must be a symbol"))
2921 (t (return (changename old indspec ncov ncontr b e))))))
2923 (defun changename (a indspec ncov ncontr b e)
2924 (cond ((or (atom e) (eq (caar e) 'rat)) e)
2925 ((rpobj e)
2926 (cond ((and (eq (caar e) a)
2927 (cond (indspec (and (equal (length (cdadr e)) ncov)
2928 (equal (length (cdaddr e))
2929 ncontr)))
2930 (t t)))
2931 (cons (cons b (cdar e)) (cdr e)))
2932 (t e)))
2933 (t (mysubst0 (cons (car e)
2934 (mapcar (function
2935 (lambda (q)
2936 (changename a indspec ncov
2937 ncontr b q)))
2938 (cdr e))) e))))
2940 (defmfun $coord n
2941 (do ((l (listify n) (cdr l)) (a))
2942 ((null l) '$done)
2943 (setq a (car l))
2944 (cond ((not (symbolp a))
2945 (merror "~M is not a valid name." a))
2946 (t (add2lnc a $coord)))))
2948 (defmfun $remcoord (&rest args)
2949 (cond ((and (= (length args) 1)
2950 (eq (car args) '$all))
2951 (setq $coord '((mlist)))
2952 '$done)
2953 (t (dolist (c args '$done)
2954 (setq $coord (delete c $coord :test #'eq))))))
2957 ;; Additions on 5/19/2004 -- VTT
2959 (defmfun $listoftens (e)
2960 (itensor-sort (cons smlist (listoftens e))))
2962 (defun listoftens (e)
2963 (cond ((atom e) nil)
2964 ((rpobj e) (list e))
2965 (t (let (l)
2966 (mapcar #'(lambda (x) (setq l (union l (listoftens x) :test #'equal))) (cdr e))
2967 l))))
2969 (defun numlist (&optional (n 1))
2970 (loop for i from n upto $dim collect i))
2972 ;;showcomps(tensor):=block([i1,i2,ind:indices(tensor)[1]],
2973 ;; if length(ind)=0 then ishow(ev(tensor))
2974 ;; else if length(ind)=1 then ishow(makelist(ev(tensor,ind[1]=i1),i1,1,dim))
2975 ;; 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)))
2976 ;; else for i1 thru dim do (showcomps(subst(i1,last(ind),tensor)),if length(ind)=3 and i1<dim then linenum:linenum+1)
2977 ;;);
2978 (defmfun $showcomps (e)
2979 (prog (ind)
2980 (setq ind (cdadr ($indices e)))
2981 (cond ((> 1 (length ind)) ($ishow (meval (list '($ev) e))))
2982 ((> 2 (length ind)) ($ishow (cons smlist (mapcar (lambda (i) (meval (list '($ev) e (list '(mequal) (car ind) i)))) (numlist)))))
2983 ((> 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))))))
2984 (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)))
2989 ; Implementation of the Hodge star operator. Based on the following
2990 ; MAXIMA-language implementation:
2992 ; hodge(e):=
2995 ; len:length(indices(e)[1]),
2996 ; idx1:makelist(idummy(),i,len+1,dim),
2997 ; idx2:makelist(idummy(),i,len+1,dim)
2998 ; ],
2999 ; funmake("*",makelist(funmake(imetric,[[idx1[i],idx2[i]]]),i,1,dim-len))*
3000 ; funmake(levi_civita,[[],append(idx1,indices(e)[1])])*e/len!
3001 ; )$
3003 (defmfun $hodge (e)
3004 (prog (len idx1 idx2)
3005 (setq
3006 len ($length (cadr ($indices e)))
3008 (cond ((> len $dim) (return 0)))
3009 (setq
3010 idx1 (do ((i $dim (1- i)) l) ((eq i len) l) (setq l (cons ($idummy) l)))
3011 idx2 (do ((i $dim (1- i)) l) ((eq i len) l) (setq l (cons ($idummy) l)))
3013 (return
3014 (append
3015 (list
3016 '(mtimes)
3018 (list '(rat) 1 (factorial len))
3019 (list
3020 '($levi_civita)
3021 '((mlist simp))
3022 (cons '(mlist simp) (append (reverse idx1) (cdadr ($indices e))))
3027 ((not idx1) l)
3028 (setq l (cons (list (list $imetric)
3029 (cons '(mlist) (list (car idx1) (car idx2)))) l)
3030 idx1 (cdr idx1)
3031 idx2 (cdr idx2)
3039 ; This version of remsym remains silent when an attempt is made to remove
3040 ; non-existent symmetries. Used by $idim below.
3042 (defun remsym (name ncov ncontr)
3043 (declare (special $symmetries))
3044 (let ((tensor (implode (nconc (exploden name) (ncons 45)
3045 (exploden ncov) (ncons 45)
3046 (exploden ncontr)))))
3047 (when (member tensor (cdr $symmetries) :test #'equal)
3048 (setq $symmetries (delete tensor $symmetries :test #'equal))
3049 (zl-remprop tensor '$sym)
3050 (zl-remprop tensor '$anti)
3051 (zl-remprop tensor '$cyc))))
3053 ; This function sets the metric dimensions and Levi-Civita symmetries.
3055 (defmfun $idim (n)
3056 (remsym '%levi_civita $dim 0)
3057 (remsym '%levi_civita 0 $dim)
3058 (remsym '$levi_civita $dim 0)
3059 (remsym '$levi_civita 0 $dim)
3060 (setq $dim n)
3061 (remsym '%levi_civita $dim 0)
3062 (remsym '%levi_civita 0 $dim)
3063 (remsym '$levi_civita $dim 0)
3064 (remsym '$levi_civita 0 $dim)
3065 ($decsym '%levi_civita n 0 '((mlist) (($anti) $all)) '((mlist)))
3066 ($decsym '%levi_civita 0 n '((mlist)) '((mlist) (($anti) $all)))
3067 ($decsym '$levi_civita n 0 '((mlist) (($anti) $all)) '((mlist)))
3068 ($decsym '$levi_civita 0 n '((mlist)) '((mlist) (($anti) $all)))
3071 (defun i-$dependencies (l &aux res)
3072 (dolist (z l)
3073 (cond
3074 ((atom z)
3075 (merror
3076 (intl:gettext
3077 "depends: argument must be a non-atomic expression; found ~M") z))
3078 ((or (eq (caar z) 'mqapply)
3079 (member 'array (cdar z) :test #'eq))
3080 (merror
3081 (intl:gettext
3082 "depends: argument cannot be a subscripted expression; found ~M") z))
3084 (do ((zz z (cdr zz))
3085 (y nil))
3086 ((null zz)
3087 (mputprop (caar z) (setq y (reverse y)) 'depends)
3088 (setq res (push (cons (ncons (caar z)) y) res))
3089 (unless (cdr $dependencies)
3090 (setq $dependencies '((mlist simp))))
3091 (add2lnc (cons (cons (caar z) nil) y) $dependencies))
3092 (cond
3093 ((and (cadr zz)
3094 (not (member (cadr zz) y)))
3095 (setq y (push (cadr zz) y))))))))
3096 (cons '(mlist simp) (reverse res)))
3098 ($load '$ex_calc)
3099 ($load '$lckdt)
3100 ($load '$iframe)