Maxima Program

Riemann.mac (v1.22)

  • Version note

  • In this version, some private library functions are moved to separate files:

    mylib_list_v1_00_pub.mac, mylib_matrix_v1_10_pub.mac, mylib_dict_v1_00_pub.mac

    These files should be put in the same directory as the main file.

  • General note

  • In the version 1.21 and later, the internal definition of the data type "dict" is changed. The new "dict" has the following structure:

    • dict = [[ item, ...]]
    • item = ( [tag]=data )

    Here, data must have the structure of list. It can be a dict-type again. Because it is a list in reality, each data corresponding to a tag cannot be referred to as "dict[tag]" like the table or hashed array. Instead, dict can be handled by some special functions as

    • getdict( dict, [tag]) ⇒ data
    • adddict( dict, item ) ⇒ addition of item
    • repldict( dict, item) ⇒ replacement of the data for the tag of the item.
    • remdict(dict, item) ⇒ remove item from dict.
    • dicttaglist( dict) ⇒ the list of tag in dict.
    • showdict (dict) ⇒ display dict in the form [ [tag]=data, ...]

  • General information

  • When you use this package, you have to prepare a coordinate name list 'varlist' and a metric 'ds2' expressed as an equation quadratic in the differential of the coordinate names. For example, for the Schwarzschild spacetime,

  • varlist:=[t, r, theta, phi],
  • ds2 := -(1-2*M/r)*dt^2+dr^2/(1-2*M/r)+r^2*(dtheta^2+dphi^2*sin(theta)^2)
  • Global variables

  • _u, _d : symbols representing the tensor index position.
  • p : global array variable used in the dict function "searchdict".
  • Common abbreviation

  • dim = the dimension of the space(time) under consideration.
  • T::tensordict = tensor T expressed by a dict with the structure
  • dict [ ["dim"]=[dim], ["indextype"]=indextype, ["value"]=Tval ]
  • dim = the space(-time) dimension, say dim=4.
  • indextype = a list specifying the index positions, e.g. [_u, _d, _d] for a type (1,2) tensor,
  • Tval = dict describing the component values of the tensor with the structure dict [ [1,1,1]=[T[1,1,1]], ...].
  • The component values can be obtained by
  • Tval : getdict(T, ["value"])$

    getdict(Tval, [1,1,2])[1]; ⇒ T[1,1,2]

  • varlist = a coordinate name list
  • dvarlist = the list of the differential of the coordinate names
  • ds2 = the metric expressed as an equation quadratic in dvarlist
  • Gdata = a special dict carrying the informaion on the geometry, such as the metric, Christoffel symbol and curvatures. See "Riemann" for detail.
  • Central procedures

  • Riemann( varlist, ds2[, sw]) ⇒ Gdata
  • calculates the connection coefficients, Riemann curvature tensors, Weyl tensor, Ricci tensor, Ricci scalar and Einstein tensor for a given metric.
  • sw=0 ⇒ no message (default)
  • sw=1 ⇒ diplaying progress messages
  • sw=2 ⇒ displaying some results with progress messages
  • Gdata = a dict of the geometrical data corresponding to the following tags:
  • "varlist", "dvarlist", "dim", "metric", "Ch", "Riem13", "Riem04", "Riem22", "Weyl04", "Ric02", "Ric11", "RS", "ET02", "ET11"

  • Here, the data for each tag are
  • ["varlist"] = varlist : the coordinate variable list,
  • ["dim"] = [dim] : the spacetime dimension,
  • ["metric"] = [G] : G is the matrix (G[i,j]) representing the spacetime metric,
  • ["Ch"] = Ch: Ch is the dict [ [1,1,1]=[Gamma^1_(11)],...] for the Christoffel symbol,
  • ["Riem13"]=Riem13: Riem13 is the dict for the Riemann tensor of type (1,3)
  • of the structure [[1,1,1,2]=[Riem^1_(112)],...],
  • ["Riem04"]=Riem04 : Riem04 is the dict for the Riemann tensor of type (0,4),
  • [ "Riem22"]=Riem04 : Riem04 is the dict for the Riemann tensor of type (2,2),
  • ["Weyl04"]=Weyl04 : Weyl04 is the dict for Weyl tensor of type (0,4),
  • ["Ric02"]=[Ric02] : Ric02 is the matrix representing the Ricci tensor of type (0,2),
  • [, "Ric11"]=[Ric11] : Ric11 is the matrix representing the Ricci tensor of type (1,1),
  • ["RS"]=[RS] : RS is the scalar curvature ,
  • [ "ET02"]=[ET02] : ET02 is the matrix representing the Einstein tensor of type (0,2),
  • ["ET11"]=[ET11] : ET11 is the matrix representing the Einstein tensor of type (1,1),
  • e.g.

    ds2 : -(1-2*M/r)*dt^2 + dr^2/(1-2*M/r) + r^2*(dtheta^2+sin(theta)^2dphi^2)$

    varpst : [ t, r, theta, phi]$

    Gdata : Riemann(varpst, ds2)$

    Riem13 : getdict(Gdata, ["Riem13"])$

    factor( getdict(Riem13, [1,2,1,2])[1] );

    ⇒ 2*M/(r^2*(r-2*M))

  • Printing procedures

  • The following are procedures to show the data in Gdata on the monitor.

  • printCh( Gdata ) ⇒ sum(sum(Ch[a,b,c]*dx[b]*dx[c],b,1,dim),c,1,dim)
  • printRiem( Gdata, Ttype ) ⇒ Riem04/Riem13/Riem22/Weyl04[*,*,*,*] ≠ 0
  • Ttype = "Riem13", "Riem04", "Riem22", "Weyl04"
  • printRic( Gdata, Ttype ) ⇒ Ric02/Ric11/ET02/ET11[*,*] ≠ 0
  • Ttype = "Ric02", "Ric11", "ET02", "ET11"
  • printTensor( T::tensordict ) ⇒ T[*,*,..] ≠ 0
  • displays all non-vanishing components of a given tensordict T of any type.
  • Special procedures

  • Kretschmann( Gdata ) ⇒ the Kretschmann invariant K
  • K = R^(abcd)R_(abcd)
  • KretschmannS( Gdata ) ⇒ (K1,K2) [only for a static metric]
  • K1 = 4 R^(1i1j)R_(1i1j), K2 = R^(ijkl)R_(ijkl)
  • NPC( Gdata, NullTetrad[, sw] ) ⇒ NPCdict [dim=4 only!!]
  • calculates the spin coefficients and the Newman-Penrose coefficients for the Weyl curvature and the Ricci curvature w.r.t. a given null frame in four space dimensions.
  • NullTetrad = a list of null basis vectors

    [NB[1]=k_*, NB[2]=l_*, NB[3]=m_*, NB[4]=conjugate(m_*)]

  • where k, l, m, conjugate(m) are a linearly independent null 1-forms reprensenting a null tetrad normalized as g(k,k)=g(l,l)=g(m,m)=0, g(k.l)=-1, g(m,conjugate(m))=1.
  • NPCdict= dict ["SCNP"=SCNP, "WeylNP"=WeylNP, "RicNP"=RicNP, "NullTetrad"=NullTerad, "dim"=dim, "varlist"=varlist, "metric"=G]
  • SCNP = dict of the NP spin coefficients [["alpha"]=[alpha], ...]
  • WeylNP = dict of the NP coefficients Psi[0], , , Psi[4] for the Weyl tensor [["Psi[0]"]=[Psi[0]], ...]
  • RicNP = dict of the NP coefficients Phi[0,0],, .,Phi[2,2] for the Ricci tensor [["Phi[00]"]=[Phi[00]], ...]
  • sw=0 ⇒ no output display
  • sw=1 ⇒ display some results
  • General frame

  • CBtoFBT( T::tensordict, varlist, FormBasis[,sw] ) ⇒ T1::tensordict w.r.t. the frame specified by FormBasis
  • transforms the tensor T from the coord basis to a general basis.
  • T = a tensordict with components in the coordinate basis
  • FormBasis = list [FB[1]=theta[1], ..., FB[dim]=theta[m]]
  • where theta[i]'s are linearly independent 1-forms defining a covector basis.
  • sw=0 ⇒ no message
  • sw=1 ⇒ displaying progress messages
  • Connection and curvature forms

  • ConnectionForm( FormBasis, Gdata[, sw] ) ⇒ CFM=matrix(omega[a,b])
  • calculates the matrix CFM whose component omega[a,b] is the connection form w.r.t. the FormBasis
  • FormBasis = [FB[1]=theta[1],..,FB[dim]=theta[dim]]
  • theta[a]= sum(theta[a,mu]*dx[mu], mu, 1, dim)
  • sw=0 ⇒ omega[a,b]=sum(omega[a,b][mu]*dx[mu], mu, 1, dim)
  • sw=1 ⇒ omega[a,b]=sum(omega[a,b][c]*FB[c],c, 1, dim)
  • RiemForm( FormBasis, Gdata[, sw] ) ⇒ RFM= matrix ( RF[a,b])
  • calculates the curvature form RFa,b] w.r.t. the FormBasis
  • sw=0 ⇒ RF[a,b]=(1/2)sum(sum(Riem13[a,b mu nu]*FB[dx[mu],dx[nu]], mu,1. dim), nu, 1. dim)
  • sw=1 ⇒ RF[a,b]=(1/2)sum(sum(Riem13[a,b c d]*FB[c,d], c,1,dim),d,1,dim)
  • where mu and nu refer to coordinate labels and a,b,c,d refer to frame labels of the FormBasis.
  • Covariant derivative of tensors

  • Covder( T,[a[1],...,a[n]], [b, c, ...], Gdata ) ⇒ (D_a[1] ... D_a[n] T)[b,c,,...]
  • calculates each component of the n-th covariant derivative of a tensor T.
  • T = a tensordict or a scalar
  • CovDT( T:: tensordict, Gdata ) ⇒ DT
  • constructs a tensordict DT correspoinding to the covariant derivative of the given tensordict T.
  • CovnDT( T::tensordict, n::positive integer, Gdata ) ⇒ DnT
  • constructs a tensordict DnT correspoinding to the n-the covariant derivative of the given tensordict T.
  • Laplacian( T::tensordict, [a[1],...,a[n]], Gdata ) ⇒ (∆ T)[a[1],..a[n]]
  • DV( X, Y, Gdata ) ⇒ D_X Y ::list
  • calculates the covariant derivative of two vectors X and Y.
  • X, Y = vectors/covectors/lists.
  • The output D_X Y is given in the form of list.
  • Div( T::tensordict, [a[1],...], Gdata[, k] )
  • ⇒ sum((DT)[... a[k-1],b, a[k],...],b, 1, dim)
  • k= the sum index poosition (default value =1)
  • DivT( T::tensordict, Gdata[, k] )⇒ tensordict DivTval
  • k= the sum index poosition (default value =1)
  • DivTval[a[1],...]=Div(T, [a[1],...], Gdata, k)
  • Algebraic procedures

  • ContractT( T::tensordict, [a,b], Gdata[, sw] ) ⇒ CT::tensordict
  • constructs a tensordict CT with two rank down from a tensordict T by contracting the specified indicies.
  • [a,b] = the index positions to contract
  • IP( V, W, Gdata ) ⇒ val::scalar
  • calculates the inner product of two tensors/vectors/covectors of the same rank.
  • V,W:: tensordicts/vectors/covectors