| Copyright | (c) 2019 Tobias Reinhart and Nils Alex | 
|---|---|
| License | MIT | 
| Maintainer | tobi.reinhart@fau.de, nils.alex@fau.de | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Math.Tensor.Examples.Gravity
Description
This module provides a variety of Tensor
Amongst many standard tensor from differential geometry and classical field theories such as Kronecker deltas \(\delta^a_b \) in multiple different dimensions, the Levi-Civita symbol \(\epsilon^{abcd} \) and the Minkowski metric \(\eta_{ab}\) and its inverse \(\eta^{ab}\), most included tensors were implemented during the initial use of the sparse-tensor package, the perturbative construction of generalized gravity theories. Thus many of the included tensors stem from this area of research.
Additionally to providing basic predefined TensorTensor
The majority of the tensors in this module are defined as type ATensInd20Ind9Ind3Ind20ind3ATens m n r s p q
Synopsis
- delta3 :: STTens 1 1 (SField Rational)
- delta9 :: ATens 0 0 1 1 0 0 (SField Rational)
- delta20 :: ATens 1 1 0 0 0 0 (SField Rational)
- delta3A :: ATens 0 0 0 0 1 1 (SField Rational)
- eta :: STTens 0 2 (SField Rational)
- invEta :: STTens 2 0 (SField Rational)
- etaA :: ATens 0 0 0 0 0 2 (SField Rational)
- invEtaA :: ATens 0 0 0 0 2 0 (SField Rational)
- etaAbs :: ATens 0 0 0 1 0 0 (SField Rational)
- epsilon :: STTens 0 4 (SField Rational)
- epsilonInv :: STTens 4 0 (SField Rational)
- epsilonA :: ATens 0 0 0 0 0 4 (SField Rational)
- epsilonInvA :: ATens 0 0 0 0 4 0 (SField Rational)
- lorentzJ1 :: ATens 0 0 0 0 1 1 (SField Rational)
- lorentzJ2 :: ATens 0 0 0 0 1 1 (SField Rational)
- lorentzJ3 :: ATens 0 0 0 0 1 1 (SField Rational)
- lorentzK1 :: ATens 0 0 0 0 1 1 (SField Rational)
- lorentzK2 :: ATens 0 0 0 0 1 1 (SField Rational)
- lorentzK3 :: ATens 0 0 0 0 1 1 (SField Rational)
- flatArea :: ATens 0 1 0 0 0 0 (SField Rational)
- interI2 :: ATens 0 0 1 0 0 2 (SField Rational)
- interJ2 :: ATens 0 0 0 1 2 0 (SField Rational)
- interIArea :: ATens 1 0 0 0 0 4 (SField Rational)
- interJArea :: ATens 0 1 0 0 4 0 (SField Rational)
- interArea :: ATens 1 1 0 0 1 1 (SField Rational)
- interMetric :: ATens 0 0 1 1 1 1 (SField Rational)
- flatInterMetric :: ATens 0 0 0 1 1 1 (SField Rational)
- flatInter :: ATens 0 1 0 0 1 1 (SField Rational)
- interEqn2 :: ATens 1 1 0 0 2 2 (SField Rational)
- interEqn3 :: ATens 1 1 1 1 1 1 (SField Rational)
- interEqn4 :: ATens 1 1 0 1 3 1 (SField Rational)
- interEqn5 :: ATens 1 1 0 1 3 1 (SField Rational)
- interEqn2Metric :: ATens 0 0 1 1 2 2 (SField Rational)
- interEqn3Metric :: ATens 0 0 2 2 1 1 (SField Rational)
- interEqn4Metric :: ATens 0 0 1 2 3 1 (SField Rational)
- interEqn5Metric :: ATens 0 0 1 2 3 1 (SField Rational)
- randArea :: IO (ATens 0 1 0 0 0 0 (SField Rational))
- randFlatArea :: IO (ATens 0 1 0 0 0 0 (SField Rational))
- randAreaDerivative1 :: IO (ATens 0 1 0 0 0 1 (SField Rational))
- randAreaDerivative2 :: IO (ATens 0 1 0 1 0 0 (SField Rational))
- randMetric :: IO (ATens 0 0 0 1 0 0 (SField Rational))
- randAxon :: IO (ATens 0 1 0 0 0 0 (SField Rational))
- generic4Ansatz :: ATens 1 0 0 0 0 0 (AnsVar (SField Rational))
- generic5Ansatz :: ATens 1 0 0 0 1 0 (AnsVar (SField Rational))
- generic6Ansatz :: ATens 1 0 1 0 0 0 (AnsVar (SField Rational))
- generic8Ansatz :: ATens 2 0 0 0 0 0 (AnsVar (SField Rational))
- generic9Ansatz :: ATens 2 0 0 0 1 0 (AnsVar (SField Rational))
- generic10_1Ansatz :: ATens 2 0 0 0 2 0 (AnsVar (SField Rational))
- generic10_2Ansatz :: ATens 2 0 1 0 0 0 (AnsVar (SField Rational))
- generic11Ansatz :: ATens 2 0 1 0 1 0 (AnsVar (SField Rational))
- generic12_1Ansatz :: ATens 2 0 2 0 0 0 (AnsVar (SField Rational))
Standard Tensors
Kronecker Delta
Minkowski Metric
eta :: STTens 0 2 (SField Rational) Source #
Spacetime Minkowski metric \(\eta_{ab}\) as ATens 0 0 0 0 0 2 (SField Rational)STTens 0 2 (SField Rational)
eta = fromListT2 map (\(x,y,z) -> ((Empty,Append (Ind3 x) $ Append (Ind3 y) Empty),SField z)) [(0,0,-1),(1,1,1),(2,2,1),(3,3,1)]
invEta :: STTens 2 0 (SField Rational) Source #
Inverse spacetime Minkowski metric \(\eta^{ab}\) as ATens 0 0 0 0 2 0 (SField Rational)STTens 2 0 (SField Rational)
invEta = fromListT2 $ map (\(x,y,z) -> ((Append (Ind3 x) $ Append (Ind3 y) Empty,Empty),SField z)) [(0,0,-1),(1,1,1),(2,2,1),(3,3,1)]
etaAbs :: ATens 0 0 0 1 0 0 (SField Rational) Source #
The tensor \(\eta_I\) provides an equivalent version of the Minkowski metric that uses an index of type Ind910 different values of the symmetric spacetime index pair.
Levi-Civita Symbol
epsilonA :: ATens 0 0 0 0 0 4 (SField Rational) Source #
Covariant Levi-Civita symbol lifted to ATens
epsilonInvA :: ATens 0 0 0 0 4 0 (SField Rational) Source #
Contravariant Levi-Civita symbol lifted to ATens
Generators of the Lorentz Group
The following six tensors are a choice of generators of the Lorentz group \( \mathrm{SO}(3,1)\), i.e. they constitute a basis of the corresponding Lie algebra \( \mathrm{so}(3,1)\).
The Lie algebra \( \mathrm{so}(3,1)\) is isomorphic to the algebra of \(\eta_{ab}\) anti symmetric matrices. Thus the following six tensors \( (K_i)^a_b \) for \( i = 1,...,6 \) all satisfy \( (K_i)^a_{b} \eta_{ca} = - (K_i)^a_{c} \eta_{ba} \).
The six generators are obtained by \(2 (K_1)^a_b = \eta_{b0} \delta^ a_{1} - \eta_{b0} \delta^ a_{1} \), and similar for
 the remaining 5 independent components of the anti symmetric index pair.
Area Metric
flatArea :: ATens 0 1 0 0 0 0 (SField Rational) Source #
Flat area metric tensor. Can be obtained via the interJArea
Constructive Gravity Specific Tensors
Intertwiners
The following tensors are used to relate the abstract indices of type Ind9Ind3
The following tensors are used to relate the abstract indices of type Ind204 spacetime indices \( (abcd)\) of type Ind3
Infinitesimal Diffeomorphisms
The following two tensors \(C^{Am}_{Bn} \) and \(K^{Im}_{Jn}\) encode the infinitesimal transformation behavior of tensors of type ATens 0 0 0 1 0 0ATens 0 1 0 0 0 0
interArea :: ATens 1 1 0 0 1 1 (SField Rational) Source #
Can be obtained as: \(C^{Am}_{Bn} = -4 \cdot I^A_{nbcd} J_B^{mbcd} \)
interArea = SField (-4 :: Rational) &. contrATens3 (1,1) (contrATens3 (2,2) $ contrATens3 (3,3) $ interIArea &* interJArea
interMetric :: ATens 0 0 1 1 1 1 (SField Rational) Source #
Can be obtained as : \(K^{Im}_{Jn} = -2 \cdot I^I_{nb} J_J^{mb} \)
interMetric = SField (-2 :: Rational) &. contrATens3 (0,0) (interI2 &* interJ2)
Further such Tensors
flatInterMetric :: ATens 0 0 0 1 1 1 (SField Rational) Source #
Is given by: \( K^m_{Jn} = K^{Im}_{Jn} \eta_I\)
flatInterMetric = contrATens2 (0,1) $ interMetric &* etaAbs
flatInter :: ATens 0 1 0 0 1 1 (SField Rational) Source #
Is given by: \( C^m_{Bn} = C^{Am}_{Bn} N_A \)
flatInter = contrATens1 (0,1) $ interArea &* flatArea
interEqn2 :: ATens 1 1 0 0 2 2 (SField Rational) Source #
Is given by: \( C_{An}^{Bm} \delta_p^q - \delta_A^B \delta_p^m \delta_n^q \)
interEqn3 :: ATens 1 1 1 1 1 1 (SField Rational) Source #
Is given by: \( C_{An}^{Bm} \delta_I^J + \delta_A^B K^{Im}_{Jn}\)
interEqn4 :: ATens 1 1 0 1 3 1 (SField Rational) Source #
Is given by: \( C_{An}^{B(m\vert} 2 J_I^{\vert p) q} - \delta^B_A J_I ^{pm} \delta_n^q \)
interEqn5 :: ATens 1 1 0 1 3 1 (SField Rational) Source #
Is given by: \( C_{An}^{B(m\vert} J_I^{\vert p q )} \)
interEqn2Metric :: ATens 0 0 1 1 2 2 (SField Rational) Source #
Is given by: \( K_{In}^{Jm} \delta_p^q - \delta_I^J \delta_p^m \delta_n^q \)
interEqn3Metric :: ATens 0 0 2 2 1 1 (SField Rational) Source #
Is given by: \( K_{In}^{Jm} \delta_K^L + \delta_I^J K^{Km}_{Ln}\)
interEqn4Metric :: ATens 0 0 1 2 3 1 (SField Rational) Source #
Is given by: \( K_{In}^{J(m\vert} 2 J_L^{\vert p) q} - \delta^I_J J_L ^{pm} \delta_n^q \)
interEqn5Metric :: ATens 0 0 1 2 3 1 (SField Rational) Source #
Is given by: \( K_{In}^{J(m\vert} J_L^{\vert p q )} \)
Random Tensor
The following tensors are filled with random components. They can for instance be used to test ranks of tensorial equations.
Unknown Tensors
generic4Ansatz :: ATens 1 0 0 0 0 0 (AnsVar (SField Rational)) Source #
tensorRank6' generic4Ansatz = 21
generic5Ansatz :: ATens 1 0 0 0 1 0 (AnsVar (SField Rational)) Source #
tensorRank6' generic5Ansatz = 21*4
generic6Ansatz :: ATens 1 0 1 0 0 0 (AnsVar (SField Rational)) Source #
tensorRank6' generic5Ansatz = 21*10
generic8Ansatz :: ATens 2 0 0 0 0 0 (AnsVar (SField Rational)) Source #
tensorRank6' generic8Ansatz = 21*22/2
generic9Ansatz :: ATens 2 0 0 0 1 0 (AnsVar (SField Rational)) Source #
tensorRank6' generic21Ansatz = 21*21*4
generic10_1Ansatz :: ATens 2 0 0 0 2 0 (AnsVar (SField Rational)) Source #
tensorRank6' generic5Ansatz = 84*85/2
generic10_2Ansatz :: ATens 2 0 1 0 0 0 (AnsVar (SField Rational)) Source #
tensorRank6' generic5Ansatz = 21*21*10