Update the ChangeLog for bug #4008
[maxima.git] / share / tensor / itensor.lisp
blob649e5dfca61f132b86695309df1c41bc712d6cf6
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 (declare-top (special x temp d))
390 (defmfun $covdiff nargs
391 (prog
392 (x e temp d i)
393 (and (< nargs 2) (merror "COVDIFF must have at least 2 args"))
394 (setq i 2 e (arg 1))
395 again (setq x (arg i) e (covdiff e) i (1+ i))
396 (and (> i nargs) (return e))
397 (go again)
401 (defun covdiff (e) ; The covariant derivative...
402 (setq d ($idummy))
403 (cond
404 ( ; is the partial derivative for scalars (*** torsion?)
405 (or (atom e) (eq (caar e) 'rat))
406 (idiff e x)
409 (rpobj e)
410 (setq temp
411 (mapcar
412 #'(lambda (v)
413 (list '(mtimes)
414 (list (diffop) (list smlist d x) (list smlist v))
415 (consubst d v e)
418 (conti e)
421 (simplus
422 (cons
423 '(mplus)
424 (cons
425 (idiff e x)
426 (cond
428 (or (covi e) (cdddr e))
429 (cons (list '(mtimes) -1. (cons '(mplus)
430 (nconc
431 (mapcar
432 #'(lambda (v)
433 (list '(mtimes)
434 (list
435 (diffop)
436 (list smlist v x)
437 (list smlist d)
439 (covsubst d v e)
442 (covi e)
444 (mapcar
445 #'(lambda (v)
446 (list
447 '(mtimes)
448 (list
449 (diffop)
450 (list smlist v x)
451 (list smlist d)
453 (dersubst d v e)
456 (cdddr e)
461 temp
464 (t temp)
468 1. t
472 (eq (caar e) 'mtimes) ; (a*b)'
473 (simplus
474 (covdifftimes (cdr e) x)
479 (eq (caar e) 'mplus) ; (a+b)'=a'+b'
480 (simplifya
481 (cons
482 '(mplus)
483 (mapcar 'covdiff (cdr e))
489 (eq (caar e) 'mexpt) ; (a^b)'=b*a^(b-1)*a'
490 (simptimes
491 (list
492 '(mtimes)
493 (caddr e)
494 (list
495 '(mexpt)
496 (cadr e)
497 (list '(mplus) -1. (caddr e))
499 ($covdiff (cadr e) x)
501 1. nil
505 (eq (caar e) 'mequal)
506 (list (car e) (covdiff (cadr e)) (covdiff (caddr e)))
508 ((and (eq (caar e) '%determinant) (eq (cadr e) $imetric))
509 (cond ((or $iframe_flag $itorsion_flag $inonmet_flag)
510 (prog (d1 d2) (setq d1 ($idummy) d2 ($idummy))
511 (return (simptimes (list '(mtimes) e
512 (list (cons $imetric '(simp)) '((mlist simp)) (list '(mlist simp) d1 d2))
513 (cond ((position '$extdiff *mlambda-call-stack*) ; Special case, we're in extdiff()
514 ($idiff (list (cons $imetric '(simp)) (list '(mlist simp) d1 d2) '((mlist simp))) x))
515 (t ($covdiff (list (cons $imetric '(simp)) (list '(mlist simp) d1 d2) '((mlist simp))) x))
517 ) 1. t))
519 (t 0)
522 (t (merror "Not acceptable to COVDIFF: ~M" (ishow e)))
527 (defun covdifftimes (l x)
528 (prog (sp left out)
529 (setq out (ncons '(mplus)))
530 loop (setq sp (car l) l (cdr l))
531 (nconc out
532 (list
533 (simptimes
534 (cons '(mtimes) (cons ($covdiff sp x) (append left l)))
535 1. t
539 (cond ((null l) (return out)))
540 (setq left (nconc left (ncons sp)))
541 (go loop)
545 (declare-top (unspecial r temp d))
547 (defun vecdiff (v i j d) ;Add frame bracket contribution when iframe_flag:true
548 (cond
550 $iframe_flag
551 (cons
552 '(mplus simp)
553 (list
554 (list (list v) '((mlist)) (list '(mlist) i) j)
555 (list
556 '(mtimes simp)
557 (list (list v) '((mlist)) (list '(mlist) d))
558 (list
559 '(mtimes simp)
561 (list '(%ifb) (list '(mlist) d j) (list '(mlist) i))
568 (list (list v) '((mlist)) (list '(mlist) i) j)
573 (defun liediff (v e n)
574 (cond
575 ((not (symbolp v)) (merror "~M is not a symbol" v))
577 (or (atom e) (eq (caar e) 'rat)) ; Scalar field
578 ; v([],[%1])*idiff(e,%1)
579 (let
580 ((dummy (implode (nconc (exploden $idummyx) (exploden n)))))
581 (list
582 '(mtimes) (list (list v) '((mlist)) (list '(mlist) dummy))
583 ($idiff e dummy)
588 (rpobj e) ; Tensor field
590 ; Dummy implementation for logic tests
591 ; (list '(%liediff) v e)
593 ; Shall the dummy index be in ICOUNTER sequence? Probably yes.
594 ; (let ((dummy (implode (nconc (exploden $idummyx) (exploden n)))))
595 (let
597 (dummy ($idummy))
598 (dummy2
599 (cond
600 ($iframe_flag ($idummy))
601 (t nil)
606 append
607 (list
608 '(mplus) 0
609 (list
610 '(mtimes) ; e([...],[...],%1)*v([],[%1])
611 (list (list v) '((mlist)) (list '(mlist) dummy))
612 ($idiff e dummy)
615 (maplist
616 #'(lambda (s) ; e([..%1..],[...])*v([],[%1],k)
617 (list
618 '(mtimes)
619 (cond ((atom (car s)) 1) (t -1))
620 (append
621 (list
622 (car e)
623 (cons
624 '(mlist)
625 (append
626 (subseq (cdadr e) 0 (- (length (cdadr e)) (length s)))
627 (cons
628 (cond ((atom (car s)) dummy)
629 (t (list '(mtimes simp) -1 dummy))
631 (cdr s)
635 (caddr e)
637 (cdddr e)
639 (vecdiff
641 (cond ((atom (car s)) dummy) (t (caddr (car s))))
642 (cond ((atom (car s)) (car s)) (t dummy))
643 dummy2
647 (cdadr e)
649 (maplist
650 #'(lambda (s) ; +e([...],[...],..%1..)*v([],[%1],k)
651 (list
652 '(mtimes)
653 (append
654 (list (car e) (cadr e) (caddr e))
655 (subseq (cdddr e) 0 (- (length (cdddr e)) (length s)))
656 (cons dummy (cdr s))
658 (vecdiff v dummy (car s) dummy2)
661 (cdddr e)
663 (maplist
664 #'(lambda (s) ; -e([...],[..%1..])*v([],[k],%1)
665 (list
666 '(mtimes) -1
667 (append
668 (list (car e) (cadr e)
669 (cons
670 '(mlist)
671 (append
672 (subseq (cdaddr e) 0 (- (length (cdaddr e)) (length s)))
673 (cons dummy (cdr s))
677 (cdddr e)
679 (vecdiff v (car s) dummy dummy2)
682 (cdaddr e)
688 (eq (caar e) 'mtimes) ; Leibniz rule
689 ; Lv(cadr e)*(cddr e)+(cadr e)*Lv(cddr e)
690 (list
691 '(mplus)
692 (cons '(mtimes) (cons (liediff v (cadr e) n) (cddr e)))
693 (cons
694 '(mtimes)
695 (list
696 (cadr e)
697 (liediff
699 (cond ((cdddr e) (cons '(mtimes) (cddr e))) (t (caddr e)))
707 (eq (caar e) 'mplus) ; Linearity
708 ; We prefer mapcar to iteration, but the recursive code also works
709 ; (list
710 ; '(mplus)
711 ; (liediff v (cadr e) n)
712 ; (liediff v (cond ((cdddr e) (cons '(mplus) (cddr e))) (t (caddr e))) n)
714 (cons '(mplus) (mapcar #'(lambda (u) (liediff v u n)) (cdr e)))
716 (t (merror "~M is not a tensorial expression liediff can handle" e))
720 (defmfun $liediff (v e) (liediff v e 1))
722 (defmfun $rediff (x) (meval '(($ev) x $idiff)))
724 ;;(defmfun $evundiff (x) ($rediff ($undiff x)))
725 (defmfun $evundiff (x) (meval (list '($ev) ($undiff x) '$nouns)))
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 '$undiff (cdr x))) t)
752 (defun putinones (e)
753 (cond
754 ((cdr e) (cons (car e) (cons 1. (putinones (cdr e)))))
755 (t (list (car e) 1.))
761 (defmfun $lorentz_gauge n
762 (cond ((equal n 0) (merror "LORENTZ_GAUGE requires at least one argument"))
763 ((equal n 1) (lorentz (arg 1) nil))
764 (t (lorentz (arg 1)
765 ((lambda (l) (cond ((loop for v in l
766 always (symbolp v)) l)
767 (t (merror
768 "Invalid tensor name(s) in argument to LORENTZ_GAUGE"))))
769 (listify (f- 1 n)))))))
771 ;Lorentz contraction of E: indexed objects with a derivative index matching a
772 ;contravariant index become 0. If L is NIL then do this for all indexed objects
773 ;otherwise do this only for those indexed objects whose names are members of L.
775 (defun lorentz (e l)
776 (cond ((atom e) e)
777 ((rpobj e)
778 (cond ((and (or (null l) (member (caar e) l :test #'eq))
779 (intersect (cdaddr e) (cdddr e)))
781 (t e)))
782 (t (mysubst0
783 (simplifya
784 (cons (ncons (caar e))
785 (mapcar (function (lambda (q) (lorentz q l)))
786 (cdr e)))
787 t) e))))
789 (defun less (x y) ;alphanumeric compare
790 (cond ((numberp x)
791 (cond ((numberp y) (< x y))
792 (t (alphalessp (ascii x) y))))
793 (t (cond ((numberp y) (alphalessp x (ascii y)))
794 (t (alphalessp x y))))))
796 ;; Christoffels contains all Christoffel-like symbols: i.e., symbols
797 ;; that make sense only with certain index patterns. These symbols are
798 ;; excluded from contractions, because those would produce illegal
799 ;; index combinations (e.g., ichr1([a,b],[c])). However, special rules
800 ;; exist to convert a covariant symbol into a mixed symbol and vice
801 ;; versa; for instance, g^ad*ichr1_bcd will contract to ichr2_bc^a.
802 (declare-top (special christoffels christoffels1 christoffels2))
804 (setq christoffels1 '($ichr1 %ichr1 $icc1 %icc1 $ifc1 %ifc1
805 $inmc1 %inmc1 $ikt1 %ikt1))
806 (setq christoffels2 '($ichr2 %ichr2 $icc2 %icc2 $ifc2 %ifc2
807 $inmc2 %inmc2 $ikt2 %ikt2))
808 (setq christoffels (append christoffels1 christoffels2 '(%ifb $ifb %itr $itr)))
810 ;; Main contraction function
811 (defmfun $contract (e)
812 (cond
813 ((atom e) e)
814 ((rpobj e) (contract5 e))
816 (eq (caar e) 'mtimes)
817 (mysubst0 (simplifya (cons '(mtimes) (contract4a e)) nil) e)
820 (eq (caar e) 'mplus)
821 (mysubst0 (simplus (cons '(mplus) (mapcar '$contract (cdr e))) 1. t) e)
824 (mysubst0 (simplifya (cons (car e) (mapcar '$contract (cdr e))) nil) e)
829 (defun contract4a (e)
830 (prog (l1 l2)
831 (setq l1 nil l2 nil)
832 (dolist (o (cdr e))
833 (cond
834 ((or (atom o) (atom (car o))) (setq l1 (cons o l1)))
836 (and (eq (caar o) 'mexpt) (eql (caddr o) -1))
837 (setq l2 (cons (cadr o) l2))
839 (t (setq l1 (cons o l1)))
842 (cond (l1 (setq l1 (contract4 (cons '(mtimes) l1)))))
843 (cond (l2 (setq l1 (cons (list '(mexpt)
844 (cons '(mtimes)
845 (contract4 (cons '(mtimes) l2))
850 ))))
851 (return l1)
855 ;; Contract a single tensor with itself
856 (defun contract5 (e)
857 (prog
858 ( ; See if e contracts with itself, find contraction symbol
859 (c (or (and (rpobj e) (getcon (caar e))) (return e)))
861 symbol
864 (c (getcon (caar e)) (cdr c))
866 ((or (eq (caar c) (caar e)) (null c)) (cond (c (cdar c)) (t nil)) )
870 (return
871 (cond
872 ((or (null symbol) (member (caar e) christoffels :test #'eq)) e)
875 (prog (cov con f sgn)
876 (setq sgn (cond ((rpobj ($canform e)) 1) (t -1))
877 cov (contractinside (derat (cadr e)))
878 con (derat (caddr e))
879 f (not (equal cov (derat (cadr e))))
881 ; Calling contract2 here won't do the trick as it messes up the
882 ; order of indices. So we remove indices that appear both in cov
883 ; and in con the hard way, with a do loop.
885 ((i cov (cdr i)))
886 ((null i))
887 (cond
888 ((not (atom (car i))))
890 (member (car i) con)
891 (setq f t con (delete (car i) con) cov (delete (car i) cov))
895 (setq c
896 (nconc
897 (list (cond (f (list symbol)) (t (car e))) cov con)
898 (cdddr e)
901 (return (cond ((and f (eql sgn -1)) (list '(mtimes) sgn c)) (t c)))
909 (defun head (x) (cond ((atom x) nil) (t (cons (car x) nil))))
911 (defun firstintersect (l1 l2) (head (intersect l1 l2)))
913 ;; Remove like members. Return (cons l1 l2) or nil if no like members found.
914 (defun contract2 (l1 l2)
916 (lambda (i) (and i (cons (setdiff l1 i) (setdiff l2 i))))
917 (firstintersect l1 l2)
921 ;; Return a list with those members of s1 that are not in s2
922 (defun setdiff (s1 s2)
924 ((j s1 (cdr j)) (a))
925 ((null j) (reverse a))
927 (and (not (numberp (car j))) (member (car j) s2 :test #'eq))
928 (setq a (cons (car j) a))
933 (defun contract3 (it lst) ;Tries to contract IT with some element of LST.
934 (prog (frst r rest) ;If none occurs then return NIL otherwise return
935 ;a list whose first member is the result of
936 ;contraction and whose cdr is a top-level copy
937 ;of LST with the element which contracted
938 ;removed.
939 loop (setq frst (car lst) lst (cdr lst))
940 ;; (and (eq (caar frst) '%kdelta) (go skip))
941 (and (setq r (contract1 it frst))
942 (return (cons r (nconc (nreverse rest) lst))))
943 ;Try contraction in reverse order since the
944 ;operation is commutative.
945 ;; skip (and (zl-get (caar frst) 'contractions)
946 skip (and (getcon (caar frst))
947 (setq r (contract1 frst it))
948 (return (cons r (nconc (nreverse rest) lst))))
949 (and (null lst) (return nil))
950 (setq rest (cons frst rest))
951 (go loop)))
953 (defun contract4 (l) ;contracts products
954 (prog (l1 l2 l3 f cl sf)
955 (setq cl (cdr l)) ;Following loop sets up 3 lists from the factors
956 ;on L: L1 - atoms or the contraction of non
957 ;indexed objects (the contraction is to handle
958 ;sub-expressions in case E is not fully expanded
959 ;as in A*B*(C*D+E*F). ), L2 - indexed objects in
960 ;L with contraction property, L3 - indexed
961 ;objects in L without contraction property
962 again(setq f (car cl) cl (cdr cl))
963 (cond ((atom f) (setq l1 (cons f l1)))
964 ((rpobj f)
965 ;;*** contract5 may return a negative result
966 (setq f (contract5 f))
967 (cond (
968 (and (or (eq (car f) '(mtimes)) (eq (car f) '(mtimes simp))) (eql (cadr f) -1))
969 (setq l1 (cons -1 l1) f (caddr f)) ))
970 (cond ((getcon (caar f))
971 (setq l2 (cons f l2)))
972 (t (setq l3 (cons f l3)))))
973 (t (setq l1 (cons ($contract f) l1))))
974 (and cl (go again))
975 (and (null l2) (return (nconc l1 l3)))
976 (and (null (cdr l2)) (setq cl l2) (go loop2+1))
977 ;If L2 is empty then no more contractions are
978 ;needed. If L2 has only 1 member then just
979 ;contract it with L3 otherwise contract the
980 ;members of L2 with themselves. The following
981 ;loop goes down L2 trying to contract members
982 ;with other members according to the following
983 ;method: moving from front to end take current
984 ;member (F) and see if it contracts with any
985 ;elements in the rest of the list (this is done
986 ;by CONTRACT3). If it doesn't then add it to CL.
987 ;If it does then take result of contraction and
988 ;add to L1, L2, or L3 as above.
989 loop1(setq f (car l2) l2 (cdr l2))
990 (cond ((null (setq sf (contract3 f l2)))
991 (setq cl (cons f cl)))
993 ;;*** contract3 may also return a negative result
994 (setq sf (mapcar #'(lambda (x)
995 (cond ((atom x) x) (
996 (and (or (equal (car x) '(mtimes)) (equal (car x) '(mtimes simp))) (eql (cadr x) -1))
997 (setq l1 (cons -1 l1)) (caddr x)) (t x))
998 ) sf ) )
1000 (setq l2 (cdr sf) sf (car sf))
1001 (cond ((atom sf) (setq l1 (cons sf l1)))
1002 ((rpobj sf)
1003 ;; (cond ((zl-get (caar sf)
1004 ;; 'contractions)
1005 (cond ((getcon (caar sf))
1006 (setq l2 (cons sf l2)))
1007 (t (setq l3 (cons sf l3)))))
1008 (t (setq l1 (cons sf l1))))))
1009 ;If L2 has at least 2 elements left then
1010 ;continue loop. If L2 has 1 element and CL
1011 ;is not empty and there were some contractions
1012 ;performed last time then add CL to L2 and try
1013 ;again. Otherwise add L2 to CL and quit.
1014 (and l2
1015 (cond ((cdr l2) (go loop1))
1016 ((and cl sf)
1017 (setq sf nil l2 (cons (car l2) cl) cl nil)
1018 (go loop1))
1019 (t (setq cl (nconc l2 cl)))))
1020 ;The following loop goes down CL trying to
1021 ;contract each member with some member in L3. If
1022 ;there is not a contraction then the element
1023 ;from CL is added onto L3 (this causes elements
1024 ;of CL to be contracted with each other). If
1025 ;there is a contraction then the result is added
1026 ;onto L3 by setting L3 to the result of
1027 ;CONTRACT3 here if CL is known not to be null.
1028 ;If L3 is empty then there is nothing left to
1029 ;contract.
1030 loop2(and (null cl) (return (nconc l1 l3)))
1031 loop2+1
1032 (and (null l3) (return (nconc l1 cl)))
1033 (setq f (car cl) cl (cdr cl))
1034 (cond ((setq sf (contract3 f l3))
1035 ;;*** contract3 may also return a negative result
1036 (setq sf (mapcar #'(lambda (x)
1037 (cond ((atom x) x) (
1038 (and (or (equal (car x) '(mtimes)) (equal (car x) '(mtimes simp))) (eql (cadr x) -1))
1039 (setq l1 (cons -1 l1)) (caddr x)) (t x))
1040 ) sf ) )
1042 (setq l3 sf))
1043 (t (setq l3 (cons f l3))))
1044 (go loop2)))
1046 ;; Create a 'normalized' (i.e., old-style) rpobj
1047 (defmfun $renorm (e &optional (force nil))
1048 (prog (c v)
1049 (and (not (rpobj e)) (merror "Not an RPOBJ: ~M" e))
1050 (and $allsym (setq force t))
1051 (setq c (cdaddr e) v nil)
1053 ((i (reverse (cdadr e)) (cdr i)))
1055 (or (null i) (and (atom (car i)) (not force))) ; Terminating condition
1056 (setq v (append (reverse i) v)) ; Remaining covariant indices
1058 (cond
1059 ((atom (car i)) (setq v (cons (car i) v)))
1060 (t (setq c (cons (caddar i) c)))
1063 (return
1064 (cons (car e) (append (list (cons smlist v) (cons smlist c)) (cdddr e)))
1069 ;; As above, but unconditionally. Not needed.
1070 ;(defun renorm (e) (append (list (car e) ($covi e) ($conti e)) (cdddr e)))
1072 ;; Add a minus sign to all elements in a list
1073 (defun neglist (l)
1074 (cond ((null l) nil)
1075 (t (cons (list '(mtimes simp) -1 (car l)) (neglist (cdr l))))
1079 ;; Create an 'abnormal' (i.e., new-style) rpobj
1080 (defun abnorm (e)
1081 (append (list (car e)
1082 (append ($covi e) (neglist (conti e)))
1083 '((mlist simp)))
1084 (cdddr e)
1088 ;; Substitute using EQUAL, to catch member lists
1089 (defun substlist (b a l)
1090 (cond ((null l) l)
1091 ((equal a (car l)) (cons b (cdr l)))
1092 (t (cons (car l) (substlist b a (cdr l))))
1096 ;; Removes items not in i from l.
1097 (defun removenotin (i l)
1098 (cond ((null l) l)
1099 ((member (car l) i :test #'eq) (cons (car l) (removenotin i (cdr l))))
1100 (t (removenotin i (cdr l)))
1104 ;; Removes items not in i from l. But the ones in l have a minus sign!
1105 (defun removenotinm (i l)
1106 (cond ((null l) l)
1107 ((atom (car l)) (cons (car l) (removenotinm i (cdr l))))
1108 ((and (isprod (caar l)) (eql (cadar l) -1)
1109 (not (member (caddar l) i :test #'eq))) (removenotinm i (cdr l)))
1110 (t (cons (car l) (removenotinm i (cdr l))))
1114 ;; Removes indices duplicated once with and once without a minus sign
1115 (defun contractinside (c)
1117 ((i (minusi c) (cdr i)))
1118 ((null i))
1119 (and (member (car i) c :test #'equal)
1120 (member (list '(mtimes simp) -1 (car i)) c :test #'equal)
1121 (setq c (delete (car i) (delete (list '(mtimes simp) -1 (car i)) c :test #'equal)))
1127 ;; This does the actual contraction of f with g. If f has any derivative
1128 ;; indices then it can't contract g. If f is Kronecker delta then see which of
1129 ;; the covariant, contravariant, or derivative indices matches those in g.
1130 (defun contract1 (f g)
1131 (prog (a b c d e cf sgn)
1132 (when (cdddr f) (return nil))
1133 (setq a (copy-tree (derat (cdadr f))) b (copy-tree (cdaddr f))
1134 c (copy-tree (derat (cadr g))) d (copy-tree (caddr g)) e (copy-tree (cdddr g))
1136 (cond ; This section is all Kronecker-delta code
1138 (or (eq (caar f) '%kdelta) (eq (caar f) '$kdelta))
1140 ; We normalize the indices first
1141 (setq b (append (minusi a) b) a (plusi a))
1143 ;We cannot contract with higher-order or malformed Kronecker deltas
1144 (and (or (/= (length a) 1) (/= (length b) 1 )) (return nil))
1146 (setq a (car a) b (car b))
1147 (return
1148 (simplifya
1149 (cond
1151 (and (cdr c) (not (numberp b)) (member b (cdr c) :test #'eq))
1152 (setq c (subst a b (cdr c)))
1153 (and
1154 (not (member (caar g) christoffels :test #'eq))
1155 (cdr d)
1156 (setq a (contract2 c (cdr d)))
1157 (setq c (car a) d (cons smlist (cdr a)))
1159 (setq c (contractinside c))
1160 (nconc (list (car g) (cons smlist c) d) e)
1163 (and e (not (numberp b)) (member b e :test #'eq))
1164 (nconc (list (car g) c d)
1165 (cond
1166 ($iframe_flag (subst a b e))
1167 (t (itensor-sort (subst a b e)))
1172 (and (cdr d) (not (numberp a)) (member a (cdr d) :test #'eq))
1173 (setq d (subst b a (cdr d)))
1174 (and
1175 (cdr c)
1176 (setq a (contract2 (cdr c) d))
1177 (setq d (cdr a) c (cons smlist (car a)))
1179 (nconc (list (car g) c (cons smlist d)) e)
1182 (and (cdr c) (not (numberp a))
1183 (member (list '(mtimes simp) -1 a) (cdr c) :test #'equal)
1185 (setq c (substlist (list '(mtimes simp) -1 b)
1186 (list '(mtimes simp) -1 a)
1187 (cdr c)
1190 (setq c (contractinside c))
1191 (nconc (list (car g) (cons smlist c) d) e)
1193 (t nil)
1201 ;No tensor can contract Kronecker-deltas, Levi-Civita symbols, or the torsion tensor.
1202 (and
1203 (or (eq (caar g) '$kdelta) (eq (caar g) '%kdelta)
1204 (eq (caar g) '$levi_civita) (eq (caar g) '%levi_civita)
1205 (eq (caar g) '$icurvature) (eq (caar g) '%icurvature)
1206 (eq (caar g) '$itr) (eq (caar g) '%itr)
1208 (return nil)
1211 ;If g has derivative indices then F must be constant in order to contract it
1212 (and e (not (kindp (caar f) '$constant)) (return nil))
1214 ;Contraction property of f is a list of (a.b)'s
1215 (cond
1216 ((setq cf (getcon (caar f))))
1217 (t (return nil))
1220 ; Determine the sign of the result based on the expression's symmetry
1221 ; properties. We use CANFORM to sort indices in the canonical order
1222 ; and then extract the resulting expression's sign.
1223 (setq sgn
1224 (cond ((eql -1 (cadr ($canform (list '(mtimes simp) f g)))) -1) (t 1))
1227 ;If g matches an a then use the b for name of result. If an a is a space
1228 ;use name of G for result.
1229 more
1230 (cond
1232 (eq (caar cf) '/ )
1233 (setq cf (car g))
1236 (eq (caar cf) (caar g))
1237 (setq cf (ncons (cdar cf)))
1240 (or (setq cf (cdr cf)) (return nil))
1241 (go more)
1244 (setq c (cdr c) d (cdr d))
1246 ;If CONTRACT2 of f's contravariant and g's covariant or f's covariant and
1247 ;g's contravariant indices is nil then return nil
1248 (cond
1250 (and b c (setq f (contract2 b c)))
1251 (setq b (car f) c (cdr f))
1254 (and a d (setq f (contract2 a d)))
1255 (setq a (car f) d (cdr f))
1258 (and a (minusi c) (setq f (contract2 a (minusi c))))
1259 ; (cdr f) now contains the free indices in (minusi c).
1260 ; what we need to do is find the corresponding items in c, and remove
1261 ; all other negative indices (i.e., those that were dropped by
1262 ; contract2).
1263 ; What we need to do is remove items from c one by one, and substitute
1264 ; an item from (car f), which we should remove from (car f):
1265 ; for i thru length(c)
1266 ; if c[i] not in (cdr f)
1267 ; if (car f) is nil, remove c[i]
1268 ; otherwise subst c[i]
1269 ; endfor
1270 ; Now set c to what we made of c, a to whatever is left of (cdr f)
1274 (i c (cdr i))
1275 (j (car f))
1278 ((null i) (setq a (removenotin j a) c (reverse k)))
1279 (cond
1281 (or (atom (car i)) (member (caddar i) (cdr f)))
1282 (setq k (cons (car i) k))
1285 (not (null j))
1286 (setq k (cons (car j) k) j (cdr j))
1292 (and (minusi a) c (setq f (contract2 (minusi a) c)))
1295 (i c (cdr i))
1296 (j (car f))
1299 ;; ((null i) (setq c (reverse k) a (append (plusi a) j)))
1300 ((null i)
1301 (setq
1302 c (reverse k)
1303 a (append
1304 (plusi a)
1305 (mapcar #'(lambda (x) (list '(mtimes simp) -1 x)) j)
1309 (cond
1310 ((member (car i) (cdr f)) (setq k (cons (car i) k)))
1312 (not (null j))
1313 (setq k (cons (list '(mtimes simp) -1 (car j)) k) j (cdr j))
1318 (t (return nil))
1320 ;Form combined indices of result
1321 (and d (setq b (append b d)))
1322 (and c (setq a (append c a)))
1323 ;Zl-remove repeated indices
1324 ;; (and (setq f (contract2 a b)) (setq a (car f) b (cdr f)))
1325 ;; (setq a (contractinside a))
1327 ;VTT: Special handling of Christoffel symbols. We can only contract them
1328 ;when we turn ICHR1 into ICHR2 or vice versa; other index combinations are
1329 ;illegal. This code checks if the index pattern is a valid one and replaces
1330 ;ICHR1 with ICHR2 or vice versa as appropriate.
1331 (cond
1333 (member (car cf) christoffels1)
1334 (cond
1335 ; VTT - before anything else, check that we're contracting on the last index only
1336 ((not (equal (append c (last (cdadr g))) (cdadr g))) (return nil))
1338 ;;(and (eql (length a) 2) (eql (length b) 1))
1339 (and (eql (+ (length (plusi a)) (length (minusi b))) 2) (eql (+ (length (plusi b)) (length (minusi a))) 1))
1340 (setq cf
1341 (cons
1342 (elt christoffels2 (position (car cf) christoffels1))
1343 (cdr cf)
1348 ;; (not (and (eql (length a) 3) (eql (length b) 0)))
1349 (not (and (eql (+ (length (plusi a)) (length (minusi b))) 3) (eql (+ (length (plusi b)) (length (minusi a))) 0)))
1350 (return nil)
1355 (member (car cf) christoffels2)
1356 (cond
1358 ;;(and (eql (length a) 3) (eql (length b) 0))
1359 (and (eql (+ (length (plusi a)) (length (minusi b))) 3) (eql (+ (length (plusi b)) (length (minusi a))) 0))
1360 (setq cf
1361 (cons
1362 (elt christoffels1 (position (car cf) christoffels2))
1363 (cdr cf)
1368 ;;(not (and (eql (length a) 2) (eql (length b) 1)))
1369 (not (and (eql (+ (length (plusi a)) (length (minusi b))) 2) (eql (+ (length (plusi b)) (length (minusi a))) 1)))
1370 (return nil)
1374 ((member (car cf) christoffels) (return nil))
1377 (setq f (meval (list cf (cons smlist a) (cons smlist b))))
1378 (and e
1380 ((e e (cdr e)))
1381 ((null e))
1382 (setq f (idiff f (car e)))
1385 (return (cond ((eql sgn -1) (list '(mtimes) sgn f)) (t f)))
1389 ;; In what amounts to quite an abuse of the Kronecker delta concept, we
1390 ;; permit an exceptional index combination of two contravariant indices.
1391 ;; This helps lc2kdt convert Levi-Civita symbols in a manner that does
1392 ;; not require resorting to numeric indices, causing all sorts of problems
1393 ;; with RENAME and CONTRACT.
1394 (defmfun $kdelta (l1 l2)
1395 (setq l2 (append l2 (minusi l1)) l1 (plusi l1))
1396 (cond
1398 (and ($listp l1) ($listp l2) (= ($length l1) 0) (= ($length l2) 2))
1399 (cond
1400 ((eq (cadr l2) (caddr l2)) 1)
1402 (and (numberp (cadr l2)) (numberp (caddr l2)))
1403 (cond
1404 ((= (cadr l2) (caddr l2)) t)
1405 (t 0)
1408 (t (list '(%kdelta) l1 l2))
1412 (and ($listp l1) ($listp l2) (= ($length l1) 2) (= ($length l2) 0))
1413 (cond
1414 ((eq (cadr l1) (caddr l1)) 1)
1416 (and (numberp (cadr l1)) (numberp (caddr l1)))
1417 (cond
1418 ((= (cadr l1) (caddr l1)) t)
1419 (t 0)
1422 (t (list '(%kdelta) l1 l2))
1426 (null (and ($listp l1) ($listp l2) (= (length l1) (length l2))))
1427 (merror "Improper arg to DELTA: ~M" (list '(%kdelta) l1 l2))
1429 (t (delta (cdr l1) (cdr l2)))
1433 ;kdels defines the symmetric combination of the Kronecker symbols
1435 (defmfun $kdels (l1 l2)
1436 (cond ((null (and ($listp l1)
1437 ($listp l2)
1438 (= (length l1) (length l2))))
1439 (merror "Improper arg to DELTA: ~M"
1440 (list '(%kdels) l1 l2)
1442 (t (delta (cdr l1) (cdr l2) 1))))
1444 (defun delta (lower upper &optional (eps -1))
1445 (cond ((null lower) $dim)
1446 ((null (cdr lower))
1447 (cond ((equal (car upper) (car lower))
1448 (cond ((numberp (car upper)) 1.) (t $dim)))
1449 ((and (numberp (car upper)) (numberp (car lower))) 0.)
1450 (t (list '(%kdelta) (cons smlist lower) (cons smlist upper)))))
1451 (t (do ((left nil (append left (ncons (car right))))
1452 (right lower (cdr right))
1453 (result))
1454 ((null right) (simplus (cons '(mplus) result) 1. t))
1455 (setq result (cons (simptimes
1456 (list '(mtimes) (delta (ncons (car right)) (ncons (car upper)) eps)
1457 (delta (append left (cdr right)) (cdr upper) eps)
1458 (cond ((oddp (length left)) eps) (t 1))
1459 ) 1. t
1460 ) result)
1461 )))))
1463 (declare-top (special $outchar $dispflag *linelabel* foobar derivlist))
1466 ;Displays P([L1],[L2],I1,I2,...) by making the elements of L2 into a single
1467 ;atom which serves as the exponent and the elements of L1 and I1,I2,... into a
1468 ;single atom with a comma in between which serves as the subscript.
1470 (defmfun $ishow (f)
1471 (progn (makelabel $linechar)
1472 (cond ($dispflag
1473 (displa (list '(mlabel) *linelabel* (ishow (specrepcheck (derat f)))))
1474 ; (setq $dispflag nil)
1476 (set *linelabel* f)))
1478 (defun ishow (f)
1479 ((lambda (foobar) ;FOOBAR initialized to NIL
1480 (cond ((atom f) f)
1481 ((rpobj f) ;If an indexed object ...
1482 (setq foobar
1483 (cond ((or (covi f) (cdddr f)) ;If covariant or
1484 (cons (list (caar f) ;derivative indices
1485 'array)
1486 (ncons (maknam (cons '$ (splice (covi f)
1487 (cdddr f)))))))
1488 (t (caar f))))
1489 (cond ((conti f) ;If contravariant indices
1490 (list '(mexpt simp)
1491 foobar
1492 ; (cons '(mtimes simp) ;Make indices appear
1493 ; (conti f)))) ;as exponents for
1494 (maknam (cons '$ (splice (conti f) nil))))) ; Changed for wxmaxima
1495 (t foobar))) ;proper display
1497 (cons (car f) (mapcar 'ishow (cdr f))))))
1498 nil)) ;Map onto subparts of F
1500 (defun splice (l1 l2)
1501 (cond (l2 (setq l2 (cons '|,| (splice1 l2)))
1502 (and l1 (setq l2 (nconc (splice1 l1) l2)))
1504 (t (splice1 l1))))
1506 (defun splice1 (l)
1507 (cond ((null (cdr l))(splice2 (car l)))
1508 (t (nconc (splice2 (car l))(cons '| | (splice1 (cdr l)))))))
1510 (defun splice2 (x)
1511 (cond ((fixnump x)(explode x))
1512 (t (cdr (explodec x)))))
1513 ; (t (cdr (explodec (print-invert-case x))))))
1515 (defun deriv (e)
1516 (prog (exp z count v)
1517 (cond ((null (cdr e)) (return (stotaldiff (car e))))
1518 ((null (cddr e)) (nconc e '(1.))))
1519 (setq exp (car e) z (setq e (append e nil)))
1520 loop (cond ((or (null derivlist) (member (cadr z) derivlist :test #'equal))
1521 (go doit)))
1522 ;DERIVLIST is set by $EV
1523 (setq z (cdr z))
1524 loop2(cond ((cdr z) (go loop))
1525 ((null (cdr e)) (return exp))
1526 (t (go noun)))
1527 doit (cond ((null (cddr z))
1528 (merror "Wrong number of args to DERIVATIVE"))
1529 ((not (fixnump (setq count (caddr z)))) (go noun))
1530 ((< count 0.)
1531 (merror "Improper count to DIFF: ~M"
1532 count)))
1533 loop1(setq v (cadr z))
1534 (and (fixnump v)
1535 $vect_coords
1536 (> v 0.)
1537 (not (> v $dim))
1538 (setq v
1539 (cond ((atom $vect_coords)
1540 (meval1 (list (list $vect_coords 'simp 'array)
1541 v)))
1542 ((eq (caar $vect_coords) 'mlist)
1543 (cond ((not (< v
1544 (length $vect_coords)))
1545 (merror
1546 "Coordinate list too short for derivative index"))
1547 (t (nth v $vect_coords))))
1548 (t v))))
1549 (cond ((zerop count) (rplacd z (cdddr z)) (go loop2))
1550 ((zerop1 (setq exp (sdiff exp v))) (return 0.)))
1551 (setq count (1- count))
1552 (go loop1)
1553 noun (return (diff%deriv (cons exp (cdr e))))))
1555 (defun chainrule1 (e x) ; --ys 15.02.02
1556 (prog (y)
1557 (cond ((and (atom e) (eq (setq y (car (mget e 'depends)))
1558 (cadr $coord))) (return (subst x y (chainrule e y))))
1559 (t (return (chainrule e x))))))
1561 (defun diffexpt1 (e x)
1562 ;; RETURN: n*v^n*rename(v'/v) where e=v^n
1563 (list '(mtimes) (caddr e) e
1564 ($rename
1565 (list '(mtimes) (list '(mexpt) (cadr e) -1)
1566 (sdiff (cadr e) x)
1572 ;Redefined so that the derivative of any indexed object appends on the
1573 ;coordinate index in sorted order unless the indexed object was declared
1574 ;constant in which case 0 is returned.
1575 (defun sdiff (e x)
1576 (simplifya
1577 (cond ((mnump e) 0.)
1578 ((and (alike1 e x) (not (and (rpobj e) (rpobj x)))) 1.)
1579 ((or (atom e) (member 'array (cdar e) :test #'eq))
1580 (chainrule1 e x))
1581 ((kindp (caar e) '$constant) 0.) ;New line added
1582 ((eq (caar e) 'mrat) (ratdx e x))
1583 ((eq (caar e) 'mplus)
1584 (simplus (cons '(mplus) (sdiffmap (cdr e) x))
1587 ((eq (caar e) 'mequal)
1588 (list (car e) (sdiff (cadr e) x) (sdiff (caddr e) x)))
1589 ((mbagp e) (cons (car e) (sdiffmap (cdr e) x)))
1590 ((eq (caar e) '$matrix)
1591 (cons (car e)
1592 (mapcar
1593 (function (lambda (y)
1594 (cons (car y)
1595 (sdiffmap (cdr y) x))))
1596 (cdr e))))
1597 ((eq (caar e) 'mtimes)
1598 (addn (sdifftimes (cdr e) x) t))
1599 ((eq (caar e) 'mexpt) (diffexpt e x))
1600 ;; ((rpobj e) (diffrpobj e x)) ;New line added
1601 ;; ((and (boundp '$imetric) (eq (caar e) '%determinant);New line added
1602 ;; (eq (cadr e) $imetric))
1603 ;; ((lambda (dummy)
1604 ;; (setq dummy ($idummy))
1605 ;; (cond ((eq dummy x) (setq dummy ($idummy))))
1606 ;; (list '(mtimes simp) 2. e
1607 ;; (list '($ichr2 simp) (cons smlist (list dummy x))
1608 ;; (cons smlist (ncons dummy)))))
1609 ;; nil))
1611 ((and
1612 (boundp '$imetric)
1613 (rpobj x)
1614 (eq (caar e) '%determinant)
1615 (eq (cadr e) $imetric)
1617 (cond
1618 ((and
1619 (eq (caar x) $imetric)
1620 (eql (length (cdadr x)) 0)
1621 (eql (length (cdaddr x)) 2)
1622 (eql (length (cdddr x)) 0)
1624 (list '(mtimes simp)
1626 (list '(%determinant simp) $imetric)
1627 (list (cons $imetric '(simp))
1628 (list '(mlist simp) (nth 0 (cdaddr x)) (nth 1 (cdaddr x)))
1629 '((mlist simp))
1633 ((and
1634 (eq (caar x) $imetric)
1635 (eql (length (cdadr x)) 2)
1636 (eql (length (cdaddr x)) 0)
1637 (eql (length (cdddr x)) 0)
1639 (list '(mtimes simp)
1640 (list '(%determinant simp) $imetric)
1641 (list (cons $imetric '(simp))
1642 '((mlist simp))
1643 (list '(mlist simp) (nth 0 (cdadr x)) (nth 1 (cdadr x)))
1647 (t 0.)
1652 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1653 ;; Differentiation of tensors with respect to tensors ;;
1654 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1656 ((and (rpobj e) (rpobj x)) ; (merror "Not yet..."))
1657 (cond
1659 ( ;; dg([a,b],[])/dg([],[m,n])
1660 (and
1661 (boundp '$imetric)
1662 (eq (caar e) $imetric)
1663 (eq (caar x) $imetric)
1664 (eql (length (cdadr e)) 2)
1665 (eql (length (cdaddr e)) 0)
1666 (eql (length (cdddr e)) 0)
1667 (eql (length (cdadr x)) 0)
1668 (eql (length (cdaddr x)) 2)
1669 (eql (length (cdddr x)) 0)
1671 (list '(mtimes simp)
1673 (list
1674 (cons $imetric '(simp))
1675 (list '(mlist simp) (nth 0 (cdadr e)) (nth 0 (cdaddr x)))
1676 '((mlist simp))
1678 (list
1679 (cons $imetric '(simp))
1680 (list '(mlist simp) (nth 1 (cdadr e)) (nth 1 (cdaddr x)))
1681 '((mlist simp))
1686 ( ;; dg([],[a,b])/dg([m,n],[])
1687 (and
1688 (boundp '$imetric)
1689 (eq (caar e) $imetric)
1690 (eq (caar x) $imetric)
1691 (eql (length (cdadr e)) 0)
1692 (eql (length (cdaddr e)) 2)
1693 (eql (length (cdddr e)) 0)
1694 (eql (length (cdadr x)) 2)
1695 (eql (length (cdaddr x)) 0)
1696 (eql (length (cdddr x)) 0)
1698 (list '(mtimes simp)
1700 (list
1701 (cons $imetric '(simp))
1702 '((mlist simp))
1703 (list '(mlist simp) (nth 0 (cdaddr e)) (nth 0 (cdadr x)))
1705 (list
1706 (cons $imetric '(simp))
1707 '((mlist simp))
1708 (list '(mlist simp) (nth 1 (cdaddr e)) (nth 1 (cdadr x)))
1713 ( ;; dg([a,b],[],y)/dg([],[m,n])
1714 (and
1715 (boundp '$imetric)
1716 (eq (caar e) $imetric)
1717 (eq (caar x) $imetric)
1718 (eql (length (cdadr e)) 2)
1719 (eql (length (cdaddr e)) 0)
1720 (eql (length (cdddr e)) 1)
1721 (eql (length (cdadr x)) 0)
1722 (eql (length (cdaddr x)) 2)
1723 (eql (length (cdddr x)) 0)
1725 (prog (d1 d2)
1726 (setq d1 ($idummy) d2 ($idummy))
1727 (return
1728 (list '(mtimes simp)
1729 (list
1730 (cons $imetric '(simp))
1731 '((mlist simp))
1732 (list '(mlist simp) d1 d2)
1733 (cadddr e)
1735 (list
1736 '(mplus simp)
1737 (list
1738 '(mtimes simp)
1739 (list
1740 (cons $imetric '(simp))
1741 (list
1742 '(mlist simp)
1743 (nth 0 (cdadr e))
1744 (nth 0 (cdaddr x))
1746 '((mlist simp))
1748 (list
1749 (cons $imetric '(simp))
1750 (list '(mlist simp) d1 (nth 1 (cdaddr x)))
1751 '((mlist simp))
1753 (list
1754 (cons $imetric '(simp))
1755 (list '(mlist simp) (nth 1 (cdadr e)) d2)
1756 '((mlist simp))
1759 (list
1760 '(mtimes simp)
1761 (list
1762 (cons $imetric '(simp))
1763 (list '(mlist simp) (nth 0 (cdadr e)) d1)
1764 '((mlist simp))
1766 (list
1767 (cons $imetric '(simp))
1768 (list
1769 '(mlist simp)
1770 (nth 1 (cdadr e))
1771 (nth 0 (cdaddr x))
1773 '((mlist simp))
1775 (list
1776 (cons $imetric '(simp))
1777 (list '(mlist simp) d2 (nth 1 (cdaddr x)))
1778 '((mlist simp))
1787 ( ;; dg([a,b],[],y)/dg([],[m,n],k)
1788 (and
1789 (boundp '$imetric)
1790 (eq (caar e) $imetric)
1791 (eq (caar x) $imetric)
1792 (eql (length (cdadr e)) 2)
1793 (eql (length (cdaddr e)) 0)
1794 (eql (length (cdddr e)) 1)
1795 (eql (length (cdadr x)) 0)
1796 (eql (length (cdaddr x)) 2)
1797 (eql (length (cdddr x)) 1)
1799 (list '(mtimes simp)
1801 (list
1802 (cons $imetric '(simp))
1803 (list '(mlist simp) (nth 0 (cdadr e)) (nth 0 (cdaddr x)))
1804 '((mlist simp))
1806 (list
1807 (cons $imetric '(simp))
1808 (list '(mlist simp) (nth 1 (cdadr e)) (nth 1 (cdaddr x)))
1809 '((mlist simp))
1811 (list
1812 '(%kdelta simp)
1813 (list '(mlist simp) (cadddr e))
1814 (list '(mlist simp) (cadddr x))
1819 ( ;; dg([a,b],[],y,d)/dg([],[m,n])
1820 (and
1821 (boundp '$imetric)
1822 (eq (caar e) $imetric)
1823 (eq (caar x) $imetric)
1824 (eql (length (cdadr e)) 2)
1825 (eql (length (cdaddr e)) 0)
1826 (eql (length (cdddr e)) 2)
1827 (eql (length (cdadr x)) 0)
1828 (eql (length (cdaddr x)) 2)
1829 (eql (length (cdddr x)) 0)
1831 (prog (d1 d2)
1832 (setq d1 ($idummy) d2 ($idummy))
1833 (return
1834 (list '(mtimes simp)
1835 (list
1836 (cons $imetric '(simp))
1837 '((mlist simp))
1838 (list '(mlist simp) d1 d2)
1839 (nth 0 (cdddr e))
1840 (nth 1 (cdddr e))
1842 (list
1843 '(mplus simp)
1844 (list
1845 '(mtimes simp)
1846 (list
1847 (cons $imetric '(simp))
1848 (list
1849 '(mlist simp)
1850 (nth 0 (cdadr e))
1851 (nth 0 (cdaddr x))
1853 '((mlist simp))
1855 (list
1856 (cons $imetric '(simp))
1857 (list '(mlist simp) d1 (nth 1 (cdaddr x)))
1858 '((mlist simp))
1860 (list
1861 (cons $imetric '(simp))
1862 (list '(mlist simp) (nth 1 (cdadr e)) d2)
1863 '((mlist simp))
1866 (list
1867 '(mtimes simp)
1868 (list
1869 (cons $imetric '(simp))
1870 (list '(mlist simp) (nth 0 (cdadr e)) d1)
1871 '((mlist simp))
1873 (list
1874 (cons $imetric '(simp))
1875 (list
1876 '(mlist simp)
1877 (nth 1 (cdadr e))
1878 (nth 0 (cdaddr x))
1880 '((mlist simp))
1882 (list
1883 (cons $imetric '(simp))
1884 (list '(mlist simp) d2 (nth 1 (cdaddr x)))
1885 '((mlist simp))
1894 ( ;; dg([a,b],[],y,d)/dg([],[m,n],k)
1895 (and
1896 (boundp '$imetric)
1897 (eq (caar e) $imetric)
1898 (eq (caar x) $imetric)
1899 (eql (length (cdadr e)) 2)
1900 (eql (length (cdaddr e)) 0)
1901 (eql (length (cdddr e)) 2)
1902 (eql (length (cdadr x)) 0)
1903 (eql (length (cdaddr x)) 2)
1904 (eql (length (cdddr x)) 1)
1906 (prog (d1 d2 d3 d4)
1907 (setq d1 ($idummy) d2 ($idummy) d3 ($idummy) d4 ($idummy))
1908 (return
1909 (list
1910 '(mtimes simp)
1911 (list
1912 '(mplus simp)
1913 (list
1914 '(mtimes simp)
1915 (list
1916 (cons $imetric '(simp))
1917 (list '(mlist simp) (nth 0 (cdadr e)) d3)
1918 '((mlist simp))
1920 (list
1921 (cons $imetric '(simp))
1922 (list '(mlist simp) d2 d4)
1923 '((mlist simp))
1925 (list
1926 (cons $imetric '(simp))
1927 (list '(mlist simp) (nth 1 (cdadr e)) d1)
1928 '((mlist simp))
1931 (list
1932 '(mtimes simp)
1933 (list
1934 (cons $imetric '(simp))
1935 (list '(mlist simp) (nth 0 (cdadr e)) d2)
1936 '((mlist simp))
1938 (list
1939 (cons $imetric '(simp))
1940 (list '(mlist simp) (nth 1 (cdadr e)) d3)
1941 '((mlist simp))
1943 (list
1944 (cons $imetric '(simp))
1945 (list '(mlist simp) d1 d4)
1946 '((mlist simp))
1950 (list
1951 '(mplus simp)
1952 (list
1953 '(mtimes simp)
1954 (list
1955 '(%kdelta simp)
1956 (list '(mlist simp) (nth 0 (cdaddr x)))
1957 (list '(mlist simp) d3)
1959 (list
1960 '(%kdelta simp)
1961 (list '(mlist simp) (nth 1 (cdaddr x)))
1962 (list '(mlist simp) d4)
1964 (list
1965 '(%kdelta simp)
1966 (list '(mlist simp) (nth 1 (cdddr e)))
1967 (list '(mlist simp) (nth 0 (cdddr x)))
1970 (list
1971 (cons $imetric '(simp))
1972 '((mlist simp))
1973 (list '(mlist simp) d2 d1)
1974 (nth 0 (cdddr e))
1977 (list
1978 '(mtimes simp)
1979 (list
1980 '(%kdelta simp)
1981 (list '(mlist simp) (nth 0 (cdaddr x)))
1982 (list '(mlist simp) d2)
1984 (list
1985 '(%kdelta simp)
1986 (list '(mlist simp) (nth 1 (cdaddr x)))
1987 (list '(mlist simp) d1)
1989 (list
1990 '(%kdelta simp)
1991 (list '(mlist simp) (nth 0 (cdddr e)))
1992 (list '(mlist simp) (nth 0 (cdddr x)))
1995 (list
1996 (cons $imetric '(simp))
1997 '((mlist simp))
1998 (list '(mlist simp) d3 d4)
1999 (nth 1 (cdddr e))
2008 ( ;; dg([a,b],[],y,d)/dg([],[m,n],k,l)
2009 (and
2010 (boundp '$imetric)
2011 (eq (caar e) $imetric)
2012 (eq (caar x) $imetric)
2013 (eql (length (cdadr e)) 2)
2014 (eql (length (cdaddr e)) 0)
2015 (eql (length (cdddr e)) 2)
2016 (eql (length (cdadr x)) 0)
2017 (eql (length (cdaddr x)) 2)
2018 (eql (length (cdddr x)) 2)
2020 (list '(mtimes simp)
2022 (list
2023 (cons $imetric '(simp))
2024 (list '(mlist simp) (nth 0 (cdadr e)) (nth 0 (cdaddr x)))
2025 '((mlist simp))
2027 (list
2028 (cons $imetric '(simp))
2029 (list '(mlist simp) (nth 1 (cdadr e)) (nth 1 (cdaddr x)))
2030 '((mlist simp))
2032 (list
2033 '(%kdelta simp)
2034 (list '(mlist simp) (cadddr e))
2035 (list '(mlist simp) (cadddr x))
2037 (list
2038 '(%kdelta simp)
2039 (list '(mlist simp) (nth 1 (cdddr e)))
2040 (list '(mlist simp) (nth 1 (cdddr x)))
2046 ((and
2047 (eq (caar e) (caar x))
2048 (eql (length (cdadr e)) (length (cdadr x)))
2049 (eql (length (cdaddr e)) (length (cdaddr x)))
2050 (eql (length (cdddr e)) (length (cdddr x)))
2052 (cons '(mtimes)
2053 (cons 1
2054 (append
2055 (mapcar
2056 #'(lambda (x y)
2057 (list
2058 '(%kdelta simp)
2059 (list '(mlist simp) x)
2060 (list '(mlist simp) y)
2062 ) (cdadr e) (cdadr x)
2064 (mapcar
2065 #'(lambda (x y)
2066 (list
2067 '(%kdelta simp)
2068 (list '(mlist simp) x)
2069 (list '(mlist simp) y)
2071 ) (cdaddr x) (cdaddr e)
2073 (mapcar
2074 #'(lambda (x y)
2075 (list
2076 '(%kdelta simp)
2077 (list '(mlist simp) x)
2078 (list '(mlist simp) y)
2081 (cdddr e) (cdddr x)
2087 ((or
2088 (and ;; catchall symbols constructed from the metric tensor
2089 (boundp '$imetric)
2090 (eq (caar x) $imetric)
2091 (member
2092 (caar e)
2093 (cons '$icurvature (cons '%icurvature christoffels))
2096 (and ;; d(some covi)/d(cov metric)
2097 (boundp '$imetric)
2098 (not (eq (caar e) $imetric))
2099 (eq (caar x) $imetric)
2100 (eql (length (cdadr x)) 2)
2101 (eql (length (cdaddr x)) 0)
2102 (eql (length (cdddr x)) 0)
2103 (> (+ (length (cdadr e)) (length (cdddr e))) 0)
2105 (and ;; d(some conti)/d(cont metric)
2106 (boundp '$imetric)
2107 (not (eq (caar e) $imetric))
2108 (eq (caar x) $imetric)
2109 (eql (length (cdadr x)) 0)
2110 (eql (length (cdaddr x)) 2)
2111 (eql (length (cdddr x)) 0)
2112 (> (length (cdaddr e)) 0)
2114 (and ;; da([a,b],y)/da([m,n],k) with a+b=m+n, y=k
2115 (depends (caar e) (caar x))
2116 (eql (+ (length (cdadr e)) (length (cdaddr e)))
2117 (+ (length (cdadr x)) (length (cdaddr x))))
2118 (eql (length (cdddr e)) (length (cdddr x)))
2121 (list '(%derivative) e x)
2123 (t 0.)
2126 ;; End of tensor vs. tensor differentiation
2128 ((not (depends e x))
2129 (cond ((fixnump x) (list '(%derivative) e x))
2130 ((atom x) 0.)
2131 (t (list '(%derivative) e x))))
2132 ;This line moved down
2133 ((eq (caar e) 'mnctimes)
2134 (simplus (list '(mplus)
2135 (list '(mnctimes)
2136 (sdiff (cadr e) x)
2137 (caddr e))
2138 (list '(mnctimes)
2139 (cadr e)
2140 (sdiff (caddr e) x)))
2142 nil))
2143 ((eq (caar e) 'mncexpt) (diffncexpt e x))
2144 ((eq (caar e) '%integrate) (diffint e x))
2145 ((eq (caar e) '%derivative)
2146 (cond ((or (atom (cadr e))
2147 (member 'array (cdaadr e) :test #'eq))
2148 (chainrule1 e x))
2149 ((freel (cdr e) x) 0.)
2150 (t (diff%deriv (list e x 1.)))))
2151 ((member (caar e) '(%sum %product) :test #'eq) (diffsumprod e x))
2152 (t (sdiffgrad e x)))
2156 ; VTT: several of these functions have been copied verbatim from comm.lisp and
2157 ; comm2.lisp, in order to implement indicial differentiation as distinct from
2158 ; differentiation with respect to an external variable.
2160 (defun idiffmap (e x) (mapcar #'(lambda (term) (idiff term x)) e))
2162 (defun idifftimes (l x)
2163 (prog (term left out)
2164 loop (setq term (car l) l (cdr l))
2165 (setq out (cons (muln (cons (idiff term x) (append left l)) t) out))
2166 (if (null l) (return out))
2167 (setq left (cons term left))
2168 (go loop)))
2170 (defun idiffexpt1 (e x)
2171 ;; RETURN: n*v^n*rename(v'/v) where e=v^n
2172 (list '(mtimes) (caddr e) e
2173 ;; ($rename
2174 (list '(mtimes) (list '(mexpt) (cadr e) -1)
2175 (idiff (cadr e) x)
2177 ;; )
2181 (defun idiffexpt (e x)
2182 (if (mnump (caddr e))
2183 (mul3 (caddr e) (power (cadr e) (addk (caddr e) -1)) (idiff (cadr e) x))
2184 (mul2 e (add2 (mul3 (power (cadr e) -1) (caddr e) (idiff (cadr e) x))
2185 (mul2 (simplifya (list '(%log) (cadr e)) t)
2186 (idiff (caddr e) x))))))
2188 (defmfun idiffint (e x)
2189 (let (a)
2190 (cond ((null (cdddr e))
2191 (cond ((alike1 x (caddr e)) (cadr e))
2192 ((and (not (atom (caddr e))) (atom x) (not (free (caddr e) x)))
2193 (mul2 (cadr e) (idiff (caddr e) x)))
2194 ((or ($constantp (setq a (idiff (cadr e) x)))
2195 (and (atom (caddr e)) (free a (caddr e))))
2196 (mul2 a (caddr e)))
2197 (t (simplifya (list '(%integrate) a (caddr e)) t))))
2198 ((alike1 x (caddr e)) (addn (idiffint1 (cdr e) x x) t))
2199 (t (addn (cons (if (equal (setq a (idiff (cadr e) x)) 0)
2201 (simplifya (list '(%integrate) a (caddr e)
2202 (cadddr e) (car (cddddr e)))
2204 (idiffint1 (cdr e) x (caddr e)))
2205 t)))))
2207 (defun idiffint1 (e x y)
2208 (let ((u (idiff (cadddr e) x)) (v (idiff (caddr e) x)))
2209 (list (if (pzerop u) 0 (mul2 u (maxima-substitute (cadddr e) y (car e))))
2210 (if (pzerop v) 0 (mul3 v (maxima-substitute (caddr e) y (car e)) -1)))))
2212 (defun idiff%deriv (e)
2213 (declare (special derivflag))
2214 (let (derivflag) (simplifya (cons '(%idiff) e) t)))
2216 (defun ideriv (e)
2217 (prog (exp z count)
2218 (cond ((null e) (wna-err '$idiff))
2219 ((null (cdr e)) (return (stotaldiff (car e))))
2220 ((null (cddr e)) (nconc e '(1))))
2221 (setq exp (car e) z (setq e (copy-list e)))
2222 loop (if (or (null derivlist) (member (cadr z) derivlist :test #'equal)) (go doit))
2223 ; DERIVLIST is set by $EV
2224 (setq z (cdr z))
2225 loop2(cond ((cdr z) (go loop))
2226 ((null (cdr e)) (return exp))
2227 (t (go noun)))
2228 doit (cond ((nonvarcheck (cadr z) '$idiff))
2229 ((null (cddr z)) (wna-err '$idiff))
2230 ((not (fixnump (caddr z))) (go noun))
2231 ((minusp (setq count (caddr z)))
2232 (merror "Improper count to IDIFF:~%~M" count)))
2233 loop1(cond ((zerop count) (rplacd z (cdddr z)) (go loop2))
2234 ((equal (setq exp (idiff exp (cadr z))) 0) (return 0)))
2235 (setq count (f1- count))
2236 (go loop1)
2237 noun (return (idiff%deriv (cons exp (cdr e))))))
2240 (defmfun idiffncexpt (e x)
2241 ((lambda (base* pow)
2242 (cond ((and (mnump pow) (or (not (fixnump pow)) (< pow 0))) ; POW cannot be 0
2243 (idiff%deriv (list e x 1)))
2244 ((and (atom base*) (eq base* x) (free pow base*))
2245 (mul2* pow (list '(mncexpt) base* (add2 pow -1))))
2246 ((fixnump pow)
2247 ((lambda (deriv ans)
2248 (do ((i 0 (f1+ i))) ((= i pow))
2249 (setq ans (cons (list '(mnctimes) (list '(mncexpt) base* i)
2250 (list '(mnctimes) deriv
2251 (list '(mncexpt) base* (f- pow 1 i))))
2252 ans)))
2253 (addn ans nil))
2254 (idiff base* x) nil))
2255 ((and (not (depends pow x)) (or (atom pow) (and (atom base*) (free pow base*))))
2256 ((lambda (deriv index)
2257 (simplifya
2258 (list '(%sum)
2259 (list '(mnctimes) (list '(mncexpt) base* index)
2260 (list '(mnctimes) deriv
2261 (list '(mncexpt) base*
2262 (list '(mplus) pow -1 (list '(mtimes) -1 index)))))
2263 index 0 (list '(mplus) pow -1)) nil))
2264 (idiff base* x) (gensumindex)))
2265 (t (idiff%deriv (list e x 1)))))
2266 (cadr e) (caddr e)))
2268 (defmfun idiffsumprod (e x)
2269 (cond ((or (not (atom x)) (not (free (cadddr e) x)) (not (free (car (cddddr e)) x)))
2270 (idiff%deriv (list e x 1)))
2271 ((eq (caddr e) x) 0)
2272 (t (let ((u (idiff (cadr e) x)))
2273 (setq u (simplifya (list '(%sum)
2274 (if (eq (caar e) '%sum) u (div u (cadr e)))
2275 (caddr e) (cadddr e) (car (cddddr e)))
2277 (if (eq (caar e) '%sum) u (mul2 e u))))))
2279 (defun idiffgrad (e x)
2280 (let ((fun (caar e)) grad args)
2281 (cond ((and (eq fun 'mqapply) (zl-get (caaadr e) 'grad))
2282 (idiffgrad (cons (cons (caaadr e) nil) (append (cdadr e) (cddr e)))
2284 ((or (eq fun 'mqapply) (null (setq grad (zl-get fun 'grad))))
2285 (if (not (depends e x)) 0 (idiff%deriv (list e x 1))))
2286 ((not (= (length (cdr e)) (length (car grad))))
2287 (merror "Wrong number of arguments for ~:M" fun))
2288 (t (setq args (idiffmap (cdr e) x))
2289 (addn (mapcar
2290 #'mul2
2291 (cdr (substitutel
2292 (cdr e) (car grad)
2293 (do ((l1 (cdr grad) (cdr l1))
2294 (args args (cdr args)) (l2))
2295 ((null l1) (cons '(mlist) (nreverse l2)))
2296 (setq l2 (cons (cond ((equal (car args) 0) 0)
2297 (t (car l1)))
2298 l2)))))
2299 args)
2300 t)))))
2302 (defmfun $idiff (&rest args)
2303 (let (derivlist)
2304 (ideriv args)))
2306 (defmfun idiff (e x)
2307 (cond
2308 (($constantp e) 0.)
2309 ((alike1 e x) 1.)
2310 ((or (atom e) (member 'array (cdar e) :test #'eq))
2311 ;; (ichainrule e x))
2312 ;; (idiff%deriv (list e x 1)))
2314 ((kindp (caar e) '$constant) 0.) ;New line added
2315 ((eq (caar e) 'mrat) (ratdx e x))
2316 ((eq (caar e) 'mplus)
2317 (simplus (cons '(mplus) (idiffmap (cdr e) x))
2320 ((eq (caar e) 'mequal)
2321 (list (car e) ($idiff (cadr e) x) ($idiff (caddr e) x)))
2322 ((eq (caar e) '$matrix)
2323 (cons (car e)
2324 (mapcar
2325 (function (lambda (y)
2326 (cons (car y)
2327 (idiffmap (cdr y) x))))
2328 (cdr e))))
2329 ((eq (caar e) 'mtimes)
2330 (addn (idifftimes (cdr e) x) t))
2331 ((eq (caar e) 'mexpt) (idiffexpt1 e x))
2332 ((rpobj e) (diffrpobj e x))
2333 ((and (boundp '$imetric) (eq (caar e) '%determinant)
2334 (eq (cadr e) $imetric))
2335 ((lambda (dummy)
2336 (setq dummy ($idummy))
2337 (cond ((eq dummy x) (setq dummy ($idummy))))
2338 (list '(mtimes simp) 2. e
2339 ;; (list '(($ichr2) simp) (cons smlist (list dummy x))
2340 (list (diffop) (cons smlist (list dummy x))
2341 (cons smlist (ncons dummy)))))
2342 nil))
2343 ((eq (caar e) 'mnctimes)
2344 (simplus (list '(mplus)
2345 (list '(mnctimes)
2346 ($idiff (cadr e) x)
2347 (caddr e))
2348 (list '(mnctimes)
2349 (cadr e)
2350 ($idiff (caddr e) x)))
2352 nil))
2353 ((eq (caar e) 'mncexpt) (idiffncexpt e x))
2354 ((eq (caar e) '%integrate) (idiffint e x))
2355 ((eq (caar e) '%derivative)
2356 (cond ((or (atom (cadr e))
2357 (member 'array (cdaadr e) :test #'eq))
2358 ;; (ichainrule e x))
2359 ;; (idiff%deriv (list e x 1)))
2361 ;; ((freel (cdr e) x) 0.)
2362 (t (idiff%deriv (list e x 1.)))))
2363 ((member (caar e) '(%sum %product) :test #'eq) (idiffsumprod e x))
2364 (t (idiffgrad e x))
2368 (defun diffrpobj (e x) ;Derivative of an indexed object
2369 (cond
2370 ( ; Special case: functions declared with coord()
2371 (and
2372 (member (caar e) $coord :test #'eq) (null (cdadr e))
2373 (equal (length (cdaddr e)) 1) (null (cdddr e))
2375 (delta (ncons x) (cdaddr e))
2377 (t ; Everything else
2378 (nconc
2379 (list (car e) (cadr e) (caddr e))
2380 (cond
2382 (null (cdddr e))
2383 (ncons x)
2385 ( ; Derivative indices do not commute when frames are used
2386 (or $iframe_flag $itorsion_flag)
2387 (append (cdddr e) (ncons x))
2390 (itensor-sort (append (cdddr e) (ncons x)))
2399 (defmfun $lc0 (l1)
2400 (prog (a b c sign)
2401 (setq a (cdr l1))
2402 (ifnot (and a (cdr a)) (return (list '(%levi_civita) l1)))
2403 (setq b a)
2404 loop1(ifnot (fixnump (car a)) (return (list '(%levi_civita) l1)))
2405 (and (setq a (cdr a)) (go loop1))
2406 loop3(setq a (car b) b (cdr b) c b)
2407 loop2(cond ((= (car c) a) (return 0.))
2408 ((< (car c) a) (setq sign (not sign))))
2409 (and (setq c (cdr c)) (go loop2))
2410 (and (cdr b) (go loop3))
2411 (return (cond (sign -1.) (t 1.)))))
2412 (defmfun $levi_civita (l1 &optional (l2 nil))
2413 (cond
2414 ((eq l2 nil) ($lc0 l1))
2415 ((like l1 '((mlist)))
2416 (prog (l) (setq l nil)
2417 (do ((i ($length l2) (1- i))) ((< i 1)) (setq l (cons i l)))
2418 (return (list '($kdelta simp) (cons smlist l) l2))
2420 ((like l2 '((mlist)))
2421 (prog (l) (setq l nil)
2422 (do ((i ($length l1) (1- i))) ((< i 1)) (setq l (cons i l)))
2423 (return (list '($kdelta simp) l1 (cons smlist l)))
2425 (t (merror "Mixed-index Levi-Civita symbols not supported"))
2429 ;; simplification rules for the totally antisymmetric LC symbol
2430 (defun $lc_l (e)
2431 (prog (l1 l2 l nn)
2432 (catch 'match
2433 (cond ((atom e) (matcherr)))
2434 (cond ((atom (car e)) (matcherr)))
2435 (cond ((not (or (eq (caar e) '$levi_civita) (eq (caar e) '%levi_civita))) (matcherr)))
2436 (cond ((not ($listp (setq l1 ($covi e)))) (matcherr)))
2437 (cond ((not (alike1 '((mlist simp)) (setq l2 ($conti e)))) (matcherr)))
2438 (cond ((cdddr e) (matcherr)))
2439 (setq nn ($length l1))
2440 (setq l nil)
2441 (do ((i nn (1- i))) ((< i 1)) (setq l (cons ($idummy) l)))
2442 (return (values (list '(mtimes simp) ($kdelta l1 (cons smlist l))
2443 (list (cons (caar e) '(simp)) (cons smlist l) (ncons smlist))
2444 (list '(mexpt simp) (meval (list 'mfactorial nn)) -1)) t)
2450 (defun $lc_u (e)
2451 (prog (l1 l2 l nn)
2452 (catch 'match
2453 (cond ((atom e) (matcherr)))
2454 (cond ((atom (car e)) (matcherr)))
2455 (cond ((not (or (eq (caar e) '$levi_civita) (eq (caar e) '%levi_civita))) (matcherr)))
2456 (cond ((not (alike1 '((mlist simp)) (setq l1 ($covi e)))) (matcherr)))
2457 (cond ((not ($listp (setq l2 ($conti e)))) (matcherr)))
2458 (cond ((cdddr e) (matcherr)))
2459 (setq nn ($length l2))
2460 (setq l nil)
2461 (do ((i nn (1- i))) ((< i 1)) (setq l (cons ($idummy) l)))
2462 (return (values (list '(mtimes simp) ($kdelta (cons smlist l) l2)
2463 (list (cons (caar e) '(simp)) (ncons smlist) (cons smlist l))
2464 (list '(mexpt simp) (meval (list 'mfactorial nn)) -1)) t)
2470 (add2lnc '$lc_l $rules)
2471 (add2lnc '$lc_u $rules)
2473 (declare-top (special e empty $flipflag))
2475 (setq $flipflag nil empty '((mlist simp) ((mlist simp)) ((mlist simp))))
2477 (defun nonumber (l)
2478 (cond
2479 ((numberp (car l)) (nonumber (cdr l)))
2480 ((eq l nil) ())
2481 (t (cons (car l) (nonumber (cdr l))))
2485 (defun removeindex (e l)
2486 (cond ((null l) nil)
2487 ((atom e)
2488 (cond ((eq e (car l)) (cdr l))
2489 (t (cons (car l) (removeindex e (cdr l))))
2491 (t (removeindex (cdr e) (removeindex (car e) l)))
2495 (defun indices (e)
2496 (prog (top bottom x y p q r)
2497 (setq top nil bottom nil)
2498 (cond
2500 (rpobj e)
2501 (setq top (nonumber (conti e))
2502 bottom (nonumber (append (covi e) (cdddr e))))
2504 ((atom e))
2506 (and (eq (caar e) 'mexpt) (eql (caddr e) -1))
2507 (setq x (indices (cadr e)) bottom (append bottom (car x))
2508 top (append top (cadr x)))
2511 (and (member (caar e) '(%derivative $diff) :test #'eq)
2512 (or (eql (length e) 3) (eql (cadddr e) 1)))
2513 (setq x (indices (cadr e)) bottom (append bottom (cadr x))
2514 top (append top (car x)))
2515 (setq x (indices (caddr e)) bottom (append bottom (car x))
2516 top (append top (cadr x)))
2519 (member (caar e) '(mtimes mnctimes mncexpt) :test #'eq)
2520 (dolist (v (cdr e))
2521 (setq x (indices v) bottom (append bottom (cadr x))
2522 top (append top (car x)))
2526 (member(caar e) '(mplus mequal) :test #'eq)
2527 (setq top (indices (cadr e)) bottom (cadr top) top (car top))
2528 (setq p (intersect top bottom) q (removeindex p bottom)
2529 p (removeindex p top))
2530 (dolist (v (cddr e))
2531 (setq x (indices v) y (cadr x) x (car x))
2532 (setq r (intersect x y) x (removeindex r x) y (removeindex r y))
2533 (when
2534 (not (and (samelists x p) (samelists y q)))
2535 (merror "Improper indices in ~M" v)
2537 (setq top (union top r) bottom (union bottom r))
2541 (member (caar e) '($sum %sum) :test #'eq)
2542 (setq top (list (caddr e)) bottom (list (caddr e)))
2545 (member (caar e) '(%idiff $idiff) :test #'eq)
2546 ;;; This code would count derivative indices as covariant. However, it is
2547 ;;; not needed. If the user wants to count derivative indices, those should
2548 ;;; be part of the tensor expression; if the expression is undiff'd, there
2549 ;;; must be a reason!
2550 ;; (do
2551 ;; ((f (cddr e) (cddr f)))
2552 ;; ((null f))
2553 ;; (do
2554 ;; ((i 1 (1+ i)))
2555 ;; ((> i (cond ((cadr f) (cadr f)) (t 1))))
2556 ;; (setq bottom (cons (car f) bottom))
2557 ;; )
2558 ;; )
2559 (setq x (indices (cadr e)) bottom (append bottom (cadr x))
2560 top (append top (car x)))
2563 (return (list top bottom))
2567 (defmfun $indices (e)
2568 (prog (top bottom x)
2569 ;; (setq top (indices e) bottom (cadr top) top (car top) x (intersect top bottom))
2570 (setq top (indices e) bottom (cadr top) top (car top) x (cond ($flipflag (intersect bottom top)) (t (intersect top bottom))))
2571 (setq top (removeindex x top) bottom (removeindex x bottom))
2572 (return (cons smlist (list (cons smlist (append top bottom)) (cons smlist x))))
2576 (defun samelists (a b) ;"True" if A and B have the same distinct elements
2577 (and (= (length a) (length b))
2578 (do ((l
2580 (cdr l)))
2581 (nil)
2582 (cond ((null l) (return t))
2583 ((member (car l) b :test #'eq))
2584 (t (return nil))))))
2586 (defmfun $flush n ;Replaces the given (as arguments to FLUSH) indexed
2587 (prog (l) ;objects by zero if they have no derivative indices.
2588 (cond ((< n 2) (merror "FLUSH takes at least 2 arguments"))
2589 ((not
2590 (loop for v in (setq l (listify (f- 1 n)))
2591 always (symbolp v)))
2592 ; (apply 'and (mapcar 'symbolp
2593 ; (setq l (listify (f- 1 n))) ))
2594 (merror "All arguments but the first must be names of
2595 indexed objects")) (t (return (flush (arg 1) l t))))))
2597 (defmfun $flushd n ;Replaces the given (as arguments to FLUSHD) indexed
2598 (prog (l) ;objects by zero if they have any derivative indices.
2599 (cond ((< n 2) (merror "FLUSH takes at least 2 arguments"))
2600 ((not
2601 (loop for v in (setq l (listify (f- 1 n)))
2602 always (symbolp v))
2603 ; (apply 'and (mapcar 'symbolp
2604 ; (setq l (listify (f- 1 n)))))
2606 (merror "All arguments but the first must be names of
2607 indexed objects")) (t (return (flush (arg 1) l nil))))))
2609 (defun flush (e l flag)
2610 (cond ((atom e) e)
2611 ((rpobj e)
2612 (cond ((not (member (caar e) l :test #'eq)) e)
2613 ((not (null (cdddr e)))
2614 (cond (flag e)
2615 (t 0)))
2616 (t (cond (flag 0)
2617 (t e)))))
2618 (t (subst0 (cons (ncons (caar e))
2619 (mapcar (function (lambda (q) (flush q l flag)))
2620 (cdr e))) e))))
2622 (defmfun $flushnd (e name n) ;Replaces by zero all indexed objects
2623 (cond ((atom e) e) ;that have n or more derivative indices
2624 ((rpobj e)
2625 (cond ((and (equal (caar e) name)
2626 (> (length (cdddr e)) (1- n)))
2628 (t e)))
2629 (t (subst0 (cons (ncons (caar e))
2630 (mapcar (function
2631 (lambda (q) ($flushnd q name n)))
2632 (cdr e))) e))))
2634 (declare-top (special index n dumx))
2636 (defmfun $rename nargs
2637 (cond ((= nargs 1) (setq index 1)) (t (setq index (arg 2)))) (rename (arg 1)))
2639 (defun rename (e) ;Renames dummy indices consistently
2640 (cond
2641 ((atom e) e)
2642 ((or (rpobj e) (eq (caar e) 'mtimes););If an indexed object or a product
2643 (and (member (caar e) '(%derivative $diff) :test #'eq) ; or a derivative expression
2644 (or (eql (length e) 3) (eql (cadddr e) 1)))
2646 ((lambda (l)
2647 (simptimes (reorder (cond (l (sublis (itensor-cleanup l (setq n index)) e))(t e))) 1 t))
2648 (cdaddr ($indices e)) ;Gets list of dummy indices
2650 (t ;Otherwise map $RENAME on each of the subparts e.g. a sum
2651 (mysubst0 (simplifya (cons (ncons (caar e))
2652 (mapcar 'rename (cdr e)))
2657 (defun reorder (e) ;Reorders contravariant, covariant, derivative indices
2658 (mysubst0 ;Example: F([A,B],[C,D],E,F)
2659 (cons
2660 '(mtimes)
2661 (mapcar
2662 #'(lambda (x)
2663 (cond ((rpobj x)
2664 (setq x ($renorm x))
2665 (nconc (list (car x) ;($f simp)
2666 (cons smlist
2667 (cond ($allsym (itensor-sort (copy-tree (cdadr x))))
2668 (t (cdadr x)))) ;($a $b)
2669 (cons smlist
2670 (cond ($allsym
2671 (itensor-sort (copy-tree (cdaddr x))))
2672 (t (cdaddr x))))) ;($c $d)
2673 (cond ($iframe_flag (cdddr x))
2674 (t (itensor-sort (copy-tree (cdddr x))))))) ;($e $f)
2675 (t x)))
2676 (cond ((eq (caar e) 'mtimes) (cdr e))
2677 (t (ncons e)))))
2680 ;;(defun itensor-cleanup (a n)((lambda (dumx)(cleanup1 a)) nil)) ;Sets DUMX to NIL
2681 (defun itensor-cleanup (a nn) (setq n nn dumx nil) (cleanup1 a))
2683 (defun cleanup1 (a)
2684 (and a (setq dumx (implode (nconc (exploden $idummyx) ;Keep proper order of
2685 (exploden n))) n (1+ n)) ;indices
2686 (cond ((eq dumx (car a)) (cleanup1 (cdr a)))
2687 (t (cons (cons (car a) dumx) (cleanup1 (cdr a)))))))
2688 ;Make list of dotted pairs indicating substitutions i.e. ((a . #1) (b . #2))
2690 (declare-top (unspecial n dumx index))
2692 (defun itensor-sort (l) (cond ((cdr l) (sort l 'less)) (t l)))
2693 ;Sort into ascending order
2695 (defmfun $remcomps (tensor)
2696 (zl-remprop tensor 'expr) (zl-remprop tensor 'carrays)
2697 (zl-remprop tensor 'texprs) (zl-remprop tensor 'indexed)
2698 (zl-remprop tensor 'indexed) (zl-remprop tensor 'tsubr)
2699 (and (functionp tensor) (fmakunbound tensor))
2700 '$done)
2702 (defmfun $indexed_tensor (tensor)
2703 (let (fp new)
2704 (and (zl-get tensor 'expr)
2705 (merror "~M has expr" tensor))
2706 ; (args tensor nil)
2707 (and (setq fp (zl-get tensor 'subr))
2708 (progn (setq new (gensym))(putprop new fp 'subr)
2709 (zl-remprop tensor 'subr)(putprop tensor new 'tsubr)))
2710 (putprop tensor t 'indexed)
2711 (putprop tensor (subst tensor 'g '(lambda nn (tensoreval (quote g)(listify nn)))) 'expr)
2712 (eval (subst tensor 'g (quote (defmfun g nn (tensoreval 'g (listify nn))))))
2713 '$done))
2716 (defun allfixed (l)
2717 (and l (fixnump (car l)) (or (null (cdr l)) (allfixed (cdr l)))))
2719 (defun tensoreval (tensor indxs)
2720 ((lambda (der con)
2721 (and (cdr indxs) (setq con (cdadr indxs) der (cddr indxs)))
2722 (setq tensor (select tensor (cdar indxs) con der))
2723 ) nil nil))
2725 (defmfun $components (tensor comp)
2726 ((lambda (len1 len2 len3 name prop)
2727 (cond ((not (rpobj tensor)) (merror "Improper 1st arg to COMPONENTS: ~M" tensor)))
2728 (setq len1 (length (covi tensor)) len2 (length (conti tensor)) len3 (length (deri tensor)))
2729 (and (not (atom comp))
2730 (eq (caar comp) '$matrix)
2731 (cond ((= (f+ (f+ len1 len2) len3) 2)
2732 (setq name (gensym))
2733 (set name comp)
2734 (setq comp name)
2736 (t (merror "Needs two indices for COMPONENTS from matrix:~%~M" tensor))
2740 (cond ((and (symbolp comp) (> (f+ (f+ len1 len2) len3) 0))
2741 (setq prop 'carrays)
2743 ((samelists (setq name (append (covi tensor) (conti tensor) (deri tensor))) (cdadr ($indices comp)))
2744 (setq prop 'texprs comp (cons comp name))
2746 (t (merror "Args to COMPONENTS do not have the same free indices"))
2748 (setq tensor (caar tensor) len1 (list len1 len2 len3))
2749 (cond ((and (setq name (zl-get tensor prop))
2750 (setq len2 (assoc len1 name :test #'equal))
2752 (rplacd len2 comp)
2754 (t (putprop tensor (cons (cons len1 comp) name) prop))
2756 (or (zl-get tensor 'indexed) ($indexed_tensor tensor))
2757 '$done
2759 nil nil nil nil nil
2763 (defun select (tensor l1 l2 l3)
2764 (prog
2766 (setq l2 (append (minusi l1) l2) l1 (plusi l1))
2767 (return
2769 (lambda
2770 (prop subs idx)
2771 (cond
2773 (and
2774 (allfixed subs)
2775 (setq prop (zl-get tensor 'carrays))
2776 (setq prop (assoc idx prop :test #'equal))
2778 (cond
2780 (alike1
2781 (setq prop (cons (list (cdr prop) 'array) subs))
2782 (setq subs (meval prop))
2786 (t subs)
2790 (setq prop (assoc idx (zl-get tensor 'texprs) :test #'equal))
2791 (sublis
2792 (mapcar #'cons(cddr prop) subs)
2793 ($rename (cadr prop) (cond ((boundp 'n) n) (t 1)))
2797 (setq prop (zl-get tensor 'tsubr))
2798 (apply
2799 prop
2800 (list (cons smlist l1) (cons smlist l2) (cons smlist l3))
2804 (not (eq l3 nil))
2805 (apply '$idiff (select tensor l1 l2 (cdr l3)) (list (car l3)))
2809 (append
2810 (list (list tensor 'simp) (cons smlist l1) (cons smlist l2))
2816 nil (append l1 l2 l3) (list (length l1)(length l2)(length l3))
2823 (defmfun $entertensor nargs
2824 (prog (fun contr cov deriv)
2825 (cond
2827 (> nargs 1)
2828 (merror "ENTERTENSOR takes 0 or 1 arguments only")
2831 (= nargs 0)
2832 (mtell "Enter tensor name: ")
2833 (setq fun (meval (retrieve nil nil)))
2835 ((setq fun (arg 1)))
2837 (mtell "Enter a list of the covariant indices: ")
2838 (setq cov (checkindex (meval (retrieve nil nil)) fun))
2839 (cond ((atom cov) (setq cov (cons smlist (ncons cov)))))
2840 (mtell "Enter a list of the contravariant indices: ")
2841 (setq contr (checkindex (meval (retrieve nil nil)) fun))
2842 (cond ((atom contr) (setq contr (cons smlist (ncons contr)))))
2843 (mtell "Enter a list of the derivative indices: ")
2844 (setq deriv (checkindex (meval (retrieve nil nil)) fun))
2845 (setq deriv
2846 (cond ((atom deriv) (ncons deriv))
2847 (t (cdr deriv))
2850 (cond
2852 (memberl (cdr cov) deriv)
2853 (mtell "Warning: There are indices that are both covariant ~
2854 and derivative%")
2857 (return ($ishow (nconc (list (list fun 'simp) cov contr) deriv)))
2861 (defun checkindex (e f)
2862 (cond ((and (atom e) (not (eq e f))) e)
2863 ((and (eq (caar e) 'mlist)
2864 (loop for v in (cdr e) always (atom v))
2865 ; (apply 'and (mapcar 'atom (cdr e)))
2866 (not (member f e :test #'eq))) e)
2867 (t (merror "Indices must be atoms different from the tensor name"))))
2869 (defun memberl (a b)
2870 (do ((l a (cdr l))
2871 (carl))
2872 ((null l) nil)
2873 (setq carl (car l))
2874 (cond ((and (symbolp carl) (member carl b :test #'equal))
2875 (return t)))))
2877 (defun consmlist (l) (cons smlist l)) ;Converts from Lisp list to Macsyma list
2879 ;$INDICES2 is similar to $INDICES except that here dummy indices are picked off
2880 ;as they first occur in going from left to right through the product or indexed
2881 ;object. Also, $INDICES2 works only on the top level of a product and will
2882 ;miss indices for products of sums (which is used to advantage by $IC_CONVERT).
2884 (defmfun $indices2 (e)
2885 (cond ((atom e) empty)
2886 ((not (or (member (caar e) '(mtimes mnctimes) :test #'eq) (rpobj e)))
2887 ($indices e))
2888 (t ((lambda (indices)
2889 (do ((ind indices) (free) (dummy) (index))
2890 ((null ind)
2891 (consmlist (list (consmlist (nreverse free))
2892 (consmlist (nreverse dummy)))))
2893 (setq index (car ind))
2894 (cond ((member index dummy :test #'equal)
2895 (merror "~M has improper indices"
2896 (ishow e)))
2897 ((member index (cdr ind) :test #'equal)
2898 (setq dummy (cons index dummy)
2899 ind (delete index (copy-tree (cdr ind))
2900 :count 1 :test #'equal)))
2901 (t (setq free (cons index free)
2902 ind (cdr ind))))))
2903 (do ((e (cond ((member (caar e) '(mtimes mnctimes) :test #'eq) (cdr e))
2904 (t (ncons e))) (cdr e))
2905 (a) (l))
2906 ((null e) l)
2907 (setq a (car e))
2908 (and (rpobj a) (setq l (append l (covi a) (conti a)
2909 (cdddr a)))))))))
2911 (defmfun $changename (a b e) ;Change the name of the indexed object A to B in E
2912 (prog (old indspec ncov ncontr) ;INDSPEC is INDex SPECification flag
2913 (cond ((not (or (and (symbolp a) (setq old a))
2914 (and ($listp a) (equal (length (cdr a)) 3)
2915 (symbolp (setq old (cadr a)))
2916 (fixnump (setq ncov (caddr a)))
2917 (fixnump (setq ncontr (cadddr a)))
2918 (setq indspec t))))
2919 (merror "Improper first argument to CHANGENAME: ~M" a))
2920 ((not (symbolp b))
2921 (merror "Second argument to CHANGENAME must be a symbol"))
2922 (t (return (changename old indspec ncov ncontr b e))))))
2924 (defun changename (a indspec ncov ncontr b e)
2925 (cond ((or (atom e) (eq (caar e) 'rat)) e)
2926 ((rpobj e)
2927 (cond ((and (eq (caar e) a)
2928 (cond (indspec (and (equal (length (cdadr e)) ncov)
2929 (equal (length (cdaddr e))
2930 ncontr)))
2931 (t t)))
2932 (cons (cons b (cdar e)) (cdr e)))
2933 (t e)))
2934 (t (mysubst0 (cons (car e)
2935 (mapcar (function
2936 (lambda (q)
2937 (changename a indspec ncov
2938 ncontr b q)))
2939 (cdr e))) e))))
2941 (defmfun $coord n
2942 (do ((l (listify n) (cdr l)) (a))
2943 ((null l) '$done)
2944 (setq a (car l))
2945 (cond ((not (symbolp a))
2946 (merror "~M is not a valid name." a))
2947 (t (add2lnc a $coord)))))
2949 (defmfun $remcoord (&rest args)
2950 (cond ((and (= (length args) 1)
2951 (eq (car args) '$all))
2952 (setq $coord '((mlist)))
2953 '$done)
2954 (t (dolist (c args '$done)
2955 (setq $coord (delete c $coord :test #'eq))))))
2958 ;; Additions on 5/19/2004 -- VTT
2960 (defmfun $listoftens (e)
2961 (itensor-sort (cons smlist (listoftens e))))
2963 (defun listoftens (e)
2964 (cond ((atom e) nil)
2965 ((rpobj e) (list e))
2966 (t (let (l)
2967 (mapcar #'(lambda (x) (setq l (union l (listoftens x) :test #'equal))) (cdr e))
2968 l))))
2970 (defun numlist (&optional (n 1))
2971 (loop for i from n upto $dim collect i))
2973 ;;showcomps(tensor):=block([i1,i2,ind:indices(tensor)[1]],
2974 ;; if length(ind)=0 then ishow(ev(tensor))
2975 ;; else if length(ind)=1 then ishow(makelist(ev(tensor,ind[1]=i1),i1,1,dim))
2976 ;; 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)))
2977 ;; else for i1 thru dim do (showcomps(subst(i1,last(ind),tensor)),if length(ind)=3 and i1<dim then linenum:linenum+1)
2978 ;;);
2979 (defmfun $showcomps (e)
2980 (prog (ind)
2981 (setq ind (cdadr ($indices e)))
2982 (cond ((> 1 (length ind)) ($ishow (meval (list '($ev) e))))
2983 ((> 2 (length ind)) ($ishow (cons smlist (mapcar (lambda (i) (meval (list '($ev) e (list '(mequal) (car ind) i)))) (numlist)))))
2984 ((> 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))))))
2985 (t (mapcar (lambda (i) ($showcomps ($substitute i (car (last ind)) e)) (and (> 4 (length ind)) (< i $dim) (setq $linenum (1+ $linenum)))) (numlist)))
2990 ; Implementation of the Hodge star operator. Based on the following
2991 ; MAXIMA-language implementation:
2993 ; hodge(e):=
2996 ; len:length(indices(e)[1]),
2997 ; idx1:makelist(idummy(),i,len+1,dim),
2998 ; idx2:makelist(idummy(),i,len+1,dim)
2999 ; ],
3000 ; funmake("*",makelist(funmake(imetric,[[idx1[i],idx2[i]]]),i,1,dim-len))*
3001 ; funmake(levi_civita,[[],append(idx1,indices(e)[1])])*e/len!
3002 ; )$
3004 (defmfun $hodge (e)
3005 (prog (len idx1 idx2)
3006 (setq
3007 len ($length (cadr ($indices e)))
3009 (cond ((> len $dim) (return 0)))
3010 (setq
3011 idx1 (do ((i $dim (1- i)) l) ((eq i len) l) (setq l (cons ($idummy) l)))
3012 idx2 (do ((i $dim (1- i)) l) ((eq i len) l) (setq l (cons ($idummy) l)))
3014 (return
3015 (append
3016 (list
3017 '(mtimes)
3019 (list '(rat) 1 (factorial len))
3020 (list
3021 '($levi_civita)
3022 '((mlist simp))
3023 (cons '(mlist simp) (append (reverse idx1) (cdadr ($indices e))))
3028 ((not idx1) l)
3029 (setq l (cons (list (list $imetric)
3030 (cons '(mlist) (list (car idx1) (car idx2)))) l)
3031 idx1 (cdr idx1)
3032 idx2 (cdr idx2)
3040 ; This version of remsym remains silent when an attempt is made to remove
3041 ; non-existent symmetries. Used by $idim below.
3043 (defun remsym (name ncov ncontr)
3044 (declare (special $symmetries))
3045 (let ((tensor (implode (nconc (exploden name) (ncons 45)
3046 (exploden ncov) (ncons 45)
3047 (exploden ncontr)))))
3048 (when (member tensor (cdr $symmetries) :test #'equal)
3049 (setq $symmetries (delete tensor $symmetries :test #'equal))
3050 (zl-remprop tensor '$sym)
3051 (zl-remprop tensor '$anti)
3052 (zl-remprop tensor '$cyc))))
3054 ; This function sets the metric dimensions and Levi-Civita symmetries.
3056 (defmfun $idim (n)
3057 (remsym '%levi_civita $dim 0)
3058 (remsym '%levi_civita 0 $dim)
3059 (remsym '$levi_civita $dim 0)
3060 (remsym '$levi_civita 0 $dim)
3061 (setq $dim n)
3062 (remsym '%levi_civita $dim 0)
3063 (remsym '%levi_civita 0 $dim)
3064 (remsym '$levi_civita $dim 0)
3065 (remsym '$levi_civita 0 $dim)
3066 ($decsym '%levi_civita n 0 '((mlist) (($anti) $all)) '((mlist)))
3067 ($decsym '%levi_civita 0 n '((mlist)) '((mlist) (($anti) $all)))
3068 ($decsym '$levi_civita n 0 '((mlist) (($anti) $all)) '((mlist)))
3069 ($decsym '$levi_civita 0 n '((mlist)) '((mlist) (($anti) $all)))
3072 (defun i-$dependencies (l &aux res)
3073 (dolist (z l)
3074 (cond
3075 ((atom z)
3076 (merror
3077 (intl:gettext
3078 "depends: argument must be a non-atomic expression; found ~M") z))
3079 ((or (eq (caar z) 'mqapply)
3080 (member 'array (cdar z) :test #'eq))
3081 (merror
3082 (intl:gettext
3083 "depends: argument cannot be a subscripted expression; found ~M") z))
3085 (do ((zz z (cdr zz))
3086 (y nil))
3087 ((null zz)
3088 (mputprop (caar z) (setq y (reverse y)) 'depends)
3089 (setq res (push (cons (ncons (caar z)) y) res))
3090 (unless (cdr $dependencies)
3091 (setq $dependencies '((mlist simp))))
3092 (add2lnc (cons (cons (caar z) nil) y) $dependencies))
3093 (cond
3094 ((and (cadr zz)
3095 (not (member (cadr zz) y)))
3096 (setq y (push (cadr zz) y))))))))
3097 (cons '(mlist simp) (reverse res)))
3099 ($load '$ex_calc)
3100 ($load '$lckdt)
3101 ($load '$iframe)