sparse-tensor-0.2.1.4: typesafe tensor algebra library

Copyright(c) 2019 Tobias Reinhart and Nils Alex
LicenseMIT
Maintainertobi.reinhart@fau.de, nils.alex@fau.de
Safe HaskellNone
LanguageHaskell2010

Math.Tensor.Examples.Gravity

Contents

Description

This module provides a variety of Tensors that are currently predefined in the sparse-tensor package.

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 Tensors for further computations this module also nicely illustrates how the construction of Tensors is achieved.

The majority of the tensors in this module are defined as type ATens which describes a tensor that takes the three different index types Ind20, Ind9, Ind3 each one appearing in contravariant and covariant position. If in the following expression that are formed from such tensors are additionally explained via their algebraic expression using appropriate symbols for the individual tensors we label indices of type Ind20 by \(A,B,C,D,...\), indices of type \(I,J,K,L,...\) and spacetime indices of type ind3 are labeled by \(a,b,c,d,...\). Hence a general such tensor is displayed as \(T^{A_1...A_m I_1...I_r a_1...a_p}_{B_1...B_n J_1...J_s b_1...b_s} \). Such a tensor then has the type ATens m n r s p q.

Synopsis

Standard Tensors

Kronecker Delta

delta3 :: STTens 1 1 (SField Rational) Source #

Standard spacetime Kronecker delta \(\delta^a_b\) as STTens 1 1 (SField Rational).

delta3 = fromListT2 $ zip [(singletonInd (Ind3 i),singletonInd (Ind3 i)) | i <- [0..3]] (repeat $ SField 1)

delta9 :: ATens 0 0 1 1 0 0 (SField Rational) Source #

Standard Kronecker delta for the Ind9 index type \(\delta^I_J\) as ATens 0 0 1 1 0 0 (SField Rational).

delta9 = fromListT6 $ zip [(Empty, Empty, singletonInd (Ind9 i),singletonInd (Ind9 i), Empty, Empty) | i <- [0..9]] (repeat $ SField 1)

delta20 :: ATens 1 1 0 0 0 0 (SField Rational) Source #

Standard Kronecker delta for the Ind20 index type \(\delta^A_B\) as ATens 1 1 0 0 0 0 (SField Rational).

delta20 = fromListT6 $ zip [(singletonInd (Ind20 i),singletonInd (Ind20 i), Empty, Empty, Empty, Empty) | i <- [0..20]] (repeat $ SField 1)

delta3A :: ATens 0 0 0 0 1 1 (SField Rational) Source #

Spacetime Kronecker delta as ATens.

Minkowski Metric

eta :: STTens 0 2 (SField Rational) Source #

Spacetime Minkowski metric \(\eta_{ab}\) as ATens 0 0 0 0 0 2 (SField Rational). The Minkowski metric could also be defined as STTens 0 2 (SField Rational) in similar fashion.

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). The inverse Minkowski metric could also be defined as STTens 2 0 (SField Rational) in similar fashion.

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)]

etaA :: ATens 0 0 0 0 0 2 (SField Rational) Source #

Minkowski metric lifted to ATens.

invEtaA :: ATens 0 0 0 0 2 0 (SField Rational) Source #

Inverse Minkowski metric lifted to ATens.

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 Ind9 to label the 10 different values of the symmetric spacetime index pair.

Levi-Civita Symbol

epsilon :: STTens 0 4 (SField Rational) Source #

Covariant spacetime Levi-Civita symbol \(\epsilon_{abcd}\) as type ATTens 0 4 (SField Rational).

epsilonInv :: STTens 4 0 (SField Rational) Source #

Contravariant spacetime Levi-Civita symbol \(\epsilon^{abcd}\) as type STTens4 0 (SField Rational). T

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 intertwiner \( J_A^{abcd}\) as: \( N_A = J_A^{abcd} \left ( \eta_{ac} \eta_{bd} - \eta_{ad} \eta_{bc} - \epsilon_{abcd} \right ) \).

Constructive Gravity Specific Tensors

Intertwiners

The following tensors are used to relate the abstract indices of type Ind9 to symmetric pairs of spacetime indices of type Ind3.

interI2 :: ATens 0 0 1 0 0 2 (SField Rational) Source #

The tensor \(I^I_{ab} \) maps between covariant Ind9 indices and symmetric pairs of covariant Ind3 indices.

interJ2 :: ATens 0 0 0 1 2 0 (SField Rational) Source #

The tensor \(J_I^{ab} \) maps between covariant Ind9 indices and pairs of covariant Ind3 indices.

The following tensors are used to relate the abstract indices of type Ind20 to blocks of 4 spacetime indices \( (abcd)\) of type Ind3, that are anti symmetric in \( a \leftrightarrow b \), anti symmetric in \( c \leftrightarrow d \) and further symmetric w.r.t. \( (ab) \leftrightarrow (cd) \).

interIArea :: ATens 1 0 0 0 0 4 (SField Rational) Source #

The tensor \( I^A_{abcd}\) maps between covariant Ind20 indices and blocks of 4 of covariant Ind3 indices.

interJArea :: ATens 0 1 0 0 4 0 (SField Rational) Source #

The tensor \( J_A^{abcd}\) maps between contravariant Ind20 indices and blocks of 4 of contravariant Ind3 indices.

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 0 and tensors of type ATens 0 1 0 0 0 0 respectively under spacetime diffeomorphisms. They are related to the Lie derivative via \(\mathscr{L}_{\xi}G_A = \partial_m G_A \cdot \xi^m + C^{Bm}_{An} G_B \cdot \partial_m \xi ^n \).

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.

randArea :: IO (ATens 0 1 0 0 0 0 (SField Rational)) Source #

randAxon :: IO (ATens 0 1 0 0 0 0 (SField Rational)) Source #

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

generic11Ansatz :: ATens 2 0 1 0 1 0 (AnsVar (SField Rational)) Source #

tensorRank6' generic5Ansatz = 21*21*10*4

generic12_1Ansatz :: ATens 2 0 2 0 0 0 (AnsVar (SField Rational)) Source #

tensorRank6' generic5Ansatz = 210*211/2