Copyright | (c) 2019 Tobias Reinhart and Nils Alex |
---|---|
License | MIT |
Maintainer | tobi.reinhart@fau.de, nils.alex@fau.de |
Safe Haskell | None |
Language | Haskell2010 |
This module supplements the sparse-tensor package with the functionality of constructing bases of the space of Lorentz invariant tensors of arbitrary rank and symmetry.
It can be shown that all \( SO(3,1) \) invariant tensors must be given by expressions that are solely composed of the Minkowski metric \(\eta_{ab} \), its inverse \(\eta^{ab} \) and the covariant and contravariant Levi-Civita symbols \( \epsilon_{abcd}\) and \( \epsilon^{abcd} \). Any such an expression can be written as a sum of products of these tensors, with the individual products containing the appropriate number of factors ensuring the required rank of the expression and the sum further enforcing the required symmetry. In the following such an expression is simply called an ansatz. Thus the goal of the following functions is the computation of a set of ansätze of given rank and symmetry that are linear independent and allow one to express any further Lorentz invariant tensor with the same rank and symmetry as appropriate linear combination of them.
Considering tensors with 4
contravariant spacetime indices \(T^{abcd} \) that further satisfy the symmetry property \( T^{abcd} = T^{cdab} = T^{bacd} \) as an example, there only exist two linear independent ansätze namely:
- \( \eta^{ab} \eta^{cd}\)
- \( \eta^{c(a} \eta^{b)d} \).
If the tensors are required to have 6
contravariant spacetime indices \( Q^{abcdpq} \) and satisfy the symmetry property \(Q^{abcdpq} = Q^{cdabpq} = - Q^{bacdpq} = Q^{abcdqp} \) there exist three linear independent ansätze:
- \( \eta^{ac}\eta^{bd}\eta^{pq} - \eta^{ad}\eta^{bc}\eta^{pq} \)
- \( \eta^{ac}\eta^{bp}\eta^{dq} + \eta^{ac}\eta^{bq}\eta^{dp} - \eta^{bc}\eta^{ap}\eta^{dq} - \eta^{bc}\eta^{aq}\eta^{dp} - \eta^{ad}\eta^{bp}\eta^{cq} - \eta^{ad}\eta^{bq}\eta^{cp} + \eta^{bd}\eta^{ap}\eta^{cq} + \eta^{bd}\eta^{aq}\eta^{cp} \)
- \( \epsilon^{abcd}\eta^{pq} \).
One can further show that any Lorentz invariant tensor must include in each of its individual products either exactly one or no Levi-Civita symbol. Further there exist no linear dependencies between those ansätze that contain an \(\epsilon^{abcd}\) or \(\epsilon_{abcd}\) and those that do not. Hence the problem actually decouples into two sub problems, the construction of all linear independent ansätze that do not contain an Levi-Civita symbol and the construction of all those linear independent ansätze that do contain exactly one Levi-Civita symbol.
This module specifically defines data types
and AnsatzForestEta
that are internally implemented as ordered expression tailored towards linear combinations of the two types of ansätze.AnsatzForestEpsilon
Currently the computation of ansatz bases is limited to the case where all indices are contravariant spacetime indices. Minor changes should nevertheless also allow the computation of ansatz bases for arbitrary mixed rank spacetime tensors and even bases for tensors that are invariant under the action of any \(\mathrm{SO}(p,q)\), i.e. in arbitrary dimension and for arbitrary signature of the inner product.
Synopsis
- data Eta = Eta !Int !Int
- data Epsilon = Epsilon !Int !Int !Int !Int
- data Var = Var !Int !Int
- type AnsatzForestEpsilon = Map Epsilon AnsatzForestEta
- data AnsatzForestEta
- = ForestEta (Map Eta AnsatzForestEta)
- | Leaf !Var
- | EmptyForest
- flattenForest :: AnsatzForestEta -> [([Eta], Var)]
- flattenForestEpsilon :: AnsatzForestEpsilon -> [(Epsilon, [Eta], Var)]
- forestEtaList :: AnsatzForestEta -> [[Eta]]
- forestEpsList :: AnsatzForestEpsilon -> [(Epsilon, [Eta])]
- forestEtaListLatex :: AnsatzForestEta -> String -> Char -> String
- forestEpsListLatex :: AnsatzForestEpsilon -> String -> Char -> String
- drawAnsatzEta :: AnsatzForestEta -> String
- drawAnsatzEpsilon :: AnsatzForestEpsilon -> String
- getForestLabels :: AnsatzForestEta -> [Int]
- getForestLabelsEpsilon :: AnsatzForestEpsilon -> [Int]
- removeVarsEta :: [Int] -> AnsatzForestEta -> AnsatzForestEta
- removeVarsEps :: [Int] -> AnsatzForestEpsilon -> AnsatzForestEpsilon
- relabelAnsatzForest :: Int -> AnsatzForestEta -> AnsatzForestEta
- relabelAnsatzForestEpsilon :: Int -> AnsatzForestEpsilon -> AnsatzForestEpsilon
- mapVars :: (Var -> Var) -> AnsatzForestEta -> AnsatzForestEta
- mapVarsEpsilon :: (Var -> Var) -> AnsatzForestEpsilon -> AnsatzForestEpsilon
- ansatzRank :: AnsatzForestEta -> Int
- ansatzRankEpsilon :: AnsatzForestEpsilon -> Int
- encodeAnsatzForestEta :: AnsatzForestEta -> ByteString
- encodeAnsatzForestEpsilon :: AnsatzForestEpsilon -> ByteString
- decodeAnsatzForestEta :: ByteString -> AnsatzForestEta
- decodeAnsatzForestEpsilon :: ByteString -> AnsatzForestEpsilon
- mkAnsatzTensorFastSym :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> [[Int]] -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR)
- mkAnsatzTensorFast :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> [[Int]] -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR)
- mkAnsatzTensorFastAbs :: Int -> Symmetry -> [([Int], Int, [IndTupleAbs n1 0 n2 0 n3 0])] -> (AnsatzForestEta, AnsatzForestEpsilon, ATens n1 0 n2 0 n3 0 AnsVarR)
- mkAnsatzTensorFastSym' :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR)
- mkAnsatzTensorFast' :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR)
- mkAnsatzTensorIncrementalSym :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> [[Int]] -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR)
- mkAnsatzTensorIncremental :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> [[Int]] -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR)
- mkAnsatzTensorIncrementalAbs :: Int -> Symmetry -> [([Int], Int, [IndTupleAbs n1 0 n2 0 n3 0])] -> (AnsatzForestEta, AnsatzForestEpsilon, ATens n1 0 n2 0 n3 0 AnsVarR)
- mkAnsatzTensorIncrementalSym' :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR)
- mkAnsatzTensorIncremental' :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR)
- type Symmetry = ([(Int, Int)], [(Int, Int)], [([Int], [Int])], [[Int]], [[[Int]]])
- areaList4 :: [([Int], Int, [IndTupleAbs 1 0 0 0 0 0])]
- areaList6 :: [([Int], Int, [IndTupleAbs 1 0 1 0 0 0])]
- areaList8 :: [([Int], Int, [IndTupleAbs 2 0 0 0 0 0])]
- areaList10_1 :: [([Int], Int, [IndTupleAbs 2 0 0 0 2 0])]
- areaList10_2 :: [([Int], Int, [IndTupleAbs 2 0 1 0 0 0])]
- areaList12 :: [([Int], Int, [IndTupleAbs 3 0 0 0 0 0])]
- areaList14_1 :: [([Int], Int, [IndTupleAbs 3 0 0 0 2 0])]
- areaList14_2 :: [([Int], Int, [IndTupleAbs 3 0 1 0 0 0])]
- metricList2 :: [([Int], Int, [IndTupleAbs 0 0 1 0 0 0])]
- metricList4_1 :: [([Int], Int, [IndTupleAbs 0 0 2 0 0 0])]
- metricList4_2 :: [([Int], Int, [IndTupleAbs 0 0 2 0 0 0])]
- metricList6_1 :: [([Int], Int, [IndTupleAbs 0 0 2 0 2 0])]
- metricList6_2 :: [([Int], Int, [IndTupleAbs 0 0 3 0 0 0])]
- metricList6_3 :: [([Int], Int, [IndTupleAbs 0 0 3 0 0 0])]
- metricList8_1 :: [([Int], Int, [IndTupleAbs 0 0 3 0 2 0])]
- metricList8_2 :: [([Int], Int, [IndTupleAbs 0 0 4 0 0 0])]
- symList4 :: Symmetry
- symList6 :: Symmetry
- symList8 :: Symmetry
- symList10_1 :: Symmetry
- symList10_2 :: Symmetry
- symList12 :: Symmetry
- symList14_1 :: Symmetry
- symList14_2 :: Symmetry
- metricsymList2 :: Symmetry
- metricsymList4_1 :: Symmetry
- metricsymList4_2 :: Symmetry
- metricsymList6_1 :: Symmetry
- metricsymList6_2 :: Symmetry
- metricsymList6_3 :: Symmetry
- metricsymList8_1 :: Symmetry
- metricsymList8_2 :: Symmetry
- symList16_1 :: Symmetry
- areaList16_1 :: [([Int], Int, [IndTupleAbs 3 0 1 0 2 0])]
Expression Forest Data Types
Node Types
Data type that represents the individual \(\eta^{ab}\) tensor. The indices are labeled not by characters but by integers.
Instances
Eq Eta Source # | |
Ord Eta Source # | |
Read Eta Source # | |
Show Eta Source # | |
Generic Eta Source # | |
NFData Eta Source # | |
Defined in Math.Tensor.LorentzGenerator | |
Serialize Eta Source # | |
Defined in Math.Tensor.LorentzGenerator | |
type Rep Eta Source # | |
Defined in Math.Tensor.LorentzGenerator type Rep Eta = D1 (MetaData "Eta" "Math.Tensor.LorentzGenerator" "sparse-tensor-0.2-inplace" False) (C1 (MetaCons "Eta" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int))) |
Data type that represents the individual \(\epsilon^{abcd}\) tensor. The indices are labeled not by characters but by integers.
Instances
Eq Epsilon Source # | |
Ord Epsilon Source # | |
Defined in Math.Tensor.LorentzGenerator | |
Read Epsilon Source # | |
Show Epsilon Source # | |
Generic Epsilon Source # | |
NFData Epsilon Source # | |
Defined in Math.Tensor.LorentzGenerator | |
Serialize Epsilon Source # | |
Defined in Math.Tensor.LorentzGenerator | |
type Rep Epsilon Source # | |
Defined in Math.Tensor.LorentzGenerator type Rep Epsilon = D1 (MetaData "Epsilon" "Math.Tensor.LorentzGenerator" "sparse-tensor-0.2-inplace" False) (C1 (MetaCons "Epsilon" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)))) |
Data type that represents variables that multiply the individual ansätze to form a general linear combination. The 2nd
argument labels the variables the first Int
is a factor that multiplies the variable.Int
Instances
Eq Var Source # | |
Ord Var Source # | |
Read Var Source # | |
Show Var Source # | |
Generic Var Source # | |
NFData Var Source # | |
Defined in Math.Tensor.LorentzGenerator | |
Serialize Var Source # | |
Defined in Math.Tensor.LorentzGenerator | |
type Rep Var Source # | |
Defined in Math.Tensor.LorentzGenerator type Rep Var = D1 (MetaData "Var" "Math.Tensor.LorentzGenerator" "sparse-tensor-0.2-inplace" False) (C1 (MetaCons "Var" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int))) |
Forest types
type AnsatzForestEpsilon = Map Epsilon AnsatzForestEta Source #
Data type that represents a general linear combination of ansätze that involve one \(\epsilon^{abcd}\) in each individual product.
data AnsatzForestEta Source #
Data type that represents a general linear combination of ansätze that involve no \(\epsilon^{abcd}\).
Instances
Conversions of AnsatzForests
List of Branches
flattenForest :: AnsatzForestEta -> [([Eta], Var)] Source #
Flatten an
to a list that contains the individual branches.AnsatzForestEta
flattenForestEpsilon :: AnsatzForestEpsilon -> [(Epsilon, [Eta], Var)] Source #
Flatten an
to a list that contains the individual branches.AnsatzForestEpsilon
forestEtaList :: AnsatzForestEta -> [[Eta]] Source #
Return one representative, i.e. one individual product for each of the basis ansätze in an
. The function thus returns the contained individual ansätze without
their explicit symmetrization.AnsatzForestEta
forestEpsList :: AnsatzForestEpsilon -> [(Epsilon, [Eta])] Source #
Return one representative, i.e. one individual product for each of the basis ansätze in an
. The function thus returns the contained individual ansätze without
their explicit symmetrization.AnsatzForestEpsilon
forestEtaListLatex :: AnsatzForestEta -> String -> Char -> String Source #
Outputs the
in \( \LaTeX \) format. The forestEtaList
argument is used to label the individual indices.String
forestEpsListLatex :: AnsatzForestEpsilon -> String -> Char -> String Source #
Outputs the
in \( \LaTeX \) format. The forestEpsList
argument is used to label the individual indices.String
ASCII drawing
drawAnsatzEta :: AnsatzForestEta -> String Source #
Returns an ASCII drawing of the
in the fashion explained in Data.Tree.
The ansatz \( x_1 \cdot 8 \{ \eta^{ac}\eta^{bd}\eta^{pq} - \eta^{ad}\eta^{bc}\eta^{pq} \} + x_2 \cdot 2 \{\eta^{ac}\eta^{bp}\eta^{dq} + \eta^{ac}\eta^{bq}\eta^{dp} - \eta^{bc}\eta^{ap}\eta^{dq} - \eta^{bc}\eta^{aq}\eta^{dp} - \eta^{ad}\eta^{bp}\eta^{cq} - \eta^{ad}\eta^{bq}\eta^{cp} + \eta^{bd}\eta^{ap}\eta^{cq} + \eta^{bd}\eta^{aq}\eta^{cp} \} \) is drawn toAnsatzForestEta
(1,3) | +---- (2,4) | | | `---- (5,6) * (8) * x[1] | +---- (2,5) | | | `---- (4,6) * (2) * x[2] | `---- (2,6) | `---- (4,5) * (2) * x[2] (1,4) | +---- (2,3) | | | `---- (5,6) * (-8) * x[1] | +---- (2,5) | | | `---- (3,6) * (-2) * x[2] | `---- (2,6) | `---- (3,5) * (-2) * x[2] (1,5) | +---- (2,3) | | | `---- (4,6) * (-2) * x[2] | `---- (2,4) | `---- (3,6) * (2) * x[2] (1,6) | +---- (2,3) | | | `---- (4,5) * (-2) * x[2] | `---- (2,4) | `---- (3,5) * (2) * x[2]
drawAnsatzEpsilon :: AnsatzForestEpsilon -> String Source #
Returns an ASCII drawing of the
in the fashion explained in Data.Tree.
The ansatz \( x_3 \cdot 16 \epsilon^{abcd}\eta^{pq} \) is drawn as:AnsatzForestEpsilon
(1,2,3,4) | `---- (5,6) * (16) * x[3]
Utility functions
Modifying Variables
getForestLabels :: AnsatzForestEta -> [Int] Source #
Return a list of the labels of all variables that are contained in the
.AnsatzForestEta
getForestLabelsEpsilon :: AnsatzForestEpsilon -> [Int] Source #
Return a list of the labels of all variables that are contained in the
.AnsatzForestEpsilon
removeVarsEta :: [Int] -> AnsatzForestEta -> AnsatzForestEta Source #
Remove the branches with variable label contained in the argument
list from the Int
.AnsatzForestEta
removeVarsEps :: [Int] -> AnsatzForestEpsilon -> AnsatzForestEpsilon Source #
Remove the branches with variable label contained in the argument
list from the Int
.AnsatzForestEpsilon
relabelAnsatzForest :: Int -> AnsatzForestEta -> AnsatzForestEta Source #
Shift the variable labels of all variables that are contained in the
by the amount specified.AnsatzForestEta
relabelAnsatzForestEpsilon :: Int -> AnsatzForestEpsilon -> AnsatzForestEpsilon Source #
Shift the variable labels of all variables that are contained in the
by the amount specified.AnsatzForestEpsilon
mapVars :: (Var -> Var) -> AnsatzForestEta -> AnsatzForestEta Source #
Map a general function over all variables that are contained in the
.AnsatzForestEta
mapVarsEpsilon :: (Var -> Var) -> AnsatzForestEpsilon -> AnsatzForestEpsilon Source #
Map a general function over all variables that are contained in the
.AnsatzForestEpsilon
Ansatz Rank
ansatzRank :: AnsatzForestEta -> Int Source #
Return the rank, i.e. the number of different variables that is contained in the
.AnsatzForestEta
ansatzRankEpsilon :: AnsatzForestEpsilon -> Int Source #
Return the rank, i.e. the number of different variables that is contained in the
.AnsatzForestEpsilon
Saving and Loading
encodeAnsatzForestEta :: AnsatzForestEta -> ByteString Source #
Encode an
employing the AnsatzForestEta
instance.Serialize
encodeAnsatzForestEpsilon :: AnsatzForestEpsilon -> ByteString Source #
Encode an
employing the AnsatzForestEpsilon
instance.Serialize
decodeAnsatzForestEta :: ByteString -> AnsatzForestEta Source #
Decode an
employing the AnsatzForestEta
instance.Serialize
decodeAnsatzForestEpsilon :: ByteString -> AnsatzForestEpsilon Source #
Decode an
employing the AnsatzForestEpsilon
instance.Serialize
Construction of Ansatz Bases
The Fast Way
The following functions construct the basis of Lorentz invariant tensors of given rank and symmetry by using an algorithm that is optimized towards fast computation times. This is achieved at the cost of memory swelling of intermediate results.
The output of each of the following functions is given by a triplet that consists of (
.
The AnsatzForestEta
, AnsatzForestEpsilon
, Tensor
AnsVarR
)
is obtained by explicitly providing the the components of the ansätze with individual ansätze given by individual variables of type Tensor
.AnsVar
mkAnsatzTensorFastSym :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> [[Int]] -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR) Source #
The function computes all linear independent ansätze that have rank specified by the first integer argument and further satisfy the symmetry specified by the
value.
The additional argument of type Symmetry
[[
is used to provide the information of all (by means of the symmetry at hand) independent components of the ansätze.
Explicit examples how this information can be computed are provided by the functions for Int
]]
, ... and also by areaList4
, ... .
The output is given as spacetime tensor metricList2
and is explicitly symmetrized.STTens
mkAnsatzTensorFast :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> [[Int]] -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR) Source #
This function provides the same functionality as
but without explicit symmetrization of the result. In other words from each symmetrization sum only the first
summand is returned. This is advantageous as for large expressions explicit symmetrization might be expensive and further is sometime simply not needed as the result might for instance be contracted against
a symmetric object, which thus enforces the symmetry, in further steps of the computation.mkAnsatzTensorFast
mkAnsatzTensorFastAbs :: Int -> Symmetry -> [([Int], Int, [IndTupleAbs n1 0 n2 0 n3 0])] -> (AnsatzForestEta, AnsatzForestEpsilon, ATens n1 0 n2 0 n3 0 AnsVarR) Source #
This function provides the same functionality as
but returns the result as tensor of type mkAnsatzTensorFast
. This is achieved by explicitly providing not only
the list of individual index combinations but also their representation using more abstract index types as input. The input list consists of triplets where the first element
as before labels the independent index combinations, the second element labels the corresponding multiplicity under the present symmetry. The multiplicity simply encodes how many different combinations of spacetime indices
correspond to the same abstract index tuple. The last element of the input triplets labels the individual abstract index combinations that then correspond to the provided spacetime indices. If some of the initial symmetries
are still present when using abstract indices this last element might consists of more then one index combination. The appropriate value that is retrieved from the two ansatz forests is then written to each of the provided index combinations.ATens
AnsVarR
mkAnsatzTensorFastSym' :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR) Source #
Provides the same functionality as
with the difference that the list of independent index combinations is automatically computed form the present symmetry.
Note that this yields slightly higher computation costs.mkAnsatzTensorFastSym
mkAnsatzTensorFast' :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR) Source #
Provides the same functionality as
with the difference that the list of independent index combinations is automatically computed form the present symmetry.
Note that this yields slightly higher computation costs.mkAnsatzTensorFast
The Memory Optimized Way
mkAnsatzTensorIncrementalSym :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> [[Int]] -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR) Source #
The function is similar to
yet it uses an algorithm that prioritizes memory usage over fast computation times.mkAnsatzTensorFastSym
mkAnsatzTensorIncremental :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> [[Int]] -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR) Source #
The function is similar to
yet it uses an algorithm that prioritizes memory usage over fast computation times.mkAnsatzTensorFast
mkAnsatzTensorIncrementalAbs :: Int -> Symmetry -> [([Int], Int, [IndTupleAbs n1 0 n2 0 n3 0])] -> (AnsatzForestEta, AnsatzForestEpsilon, ATens n1 0 n2 0 n3 0 AnsVarR) Source #
The function is similar to
yet it uses an algorithm that prioritizes memory usage over fast computation times.mkAnsatzTensorFastAbs
mkAnsatzTensorIncrementalSym' :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR) Source #
The function is similar to
yet it uses an algorithm that prioritizes memory usage over fast computation times.mkAnsatzTensorFastSym'
mkAnsatzTensorIncremental' :: forall (n :: Nat). KnownNat n => Int -> Symmetry -> (AnsatzForestEta, AnsatzForestEpsilon, STTens n 0 AnsVarR) Source #
The function is similar to
yet it uses an algorithm that prioritizes memory usage over fast computation times.mkAnsatzTensorFast'
Specifying Additional Data
Symmetry Type
Evaluation Lists
Area Metric
The following provides an example of evaluation lists.
areaList8 :: [([Int], Int, [IndTupleAbs 2 0 0 0 0 0])] Source #
Evaluation list for \(a^{A B}\). Note that also when using the abstract indices this ansatz still features the \( A \leftrightarrow B \) symmetry.
areaList10_1 :: [([Int], Int, [IndTupleAbs 2 0 0 0 2 0])] Source #
Evaluation list for \(a^{Ap Bq}\). Note that also when using the abstract indices this ansatz still features the \( (Ap) \leftrightarrow (Bq) \) symmetry.
areaList10_2 :: [([Int], Int, [IndTupleAbs 2 0 1 0 0 0])] Source #
Evaluation list for \(a^{ABI} \).
areaList12 :: [([Int], Int, [IndTupleAbs 3 0 0 0 0 0])] Source #
Evaluation list for \(a^{ABC} \). Note that also when using the abstract indices this ansatz still features the symmetry under arbitrary permutations of \( ABC\).
areaList14_1 :: [([Int], Int, [IndTupleAbs 3 0 0 0 2 0])] Source #
Evaluation list for \(a^{ABp Cq}\). Note that also when using the abstract indices this ansatz still features the \( (Bp) \leftrightarrow (Cq) \) symmetry.
areaList14_2 :: [([Int], Int, [IndTupleAbs 3 0 1 0 0 0])] Source #
Evaluation list for \(a^{A B C I}\). Note that also when using the abstract indices this ansatz still features the \( (A) \leftrightarrow (B) \) symmetry.
Metric
In the documentation of the following further provided exemplary evaluation lists index labels \(A, B, C, ...\) also refers to indices of type
.Ind9
metricList2 :: [([Int], Int, [IndTupleAbs 0 0 1 0 0 0])] Source #
Evaluation list for \(a^{A} \).
metricList4_1 :: [([Int], Int, [IndTupleAbs 0 0 2 0 0 0])] Source #
Evaluation list for \(a^{AI} \).
metricList4_2 :: [([Int], Int, [IndTupleAbs 0 0 2 0 0 0])] Source #
Evaluation list for \(a^{A B}\). Note that also when using the abstract indices this ansatz still features the \( A \leftrightarrow B \) symmetry.
metricList6_1 :: [([Int], Int, [IndTupleAbs 0 0 2 0 2 0])] Source #
Evaluation list for \(a^{Ap Bq}\). Note that also when using the abstract indices this ansatz still features the \( (Ap) \leftrightarrow (Bq) \) symmetry.
metricList6_2 :: [([Int], Int, [IndTupleAbs 0 0 3 0 0 0])] Source #
Evaluation list for \(a^{ABI} \).
metricList6_3 :: [([Int], Int, [IndTupleAbs 0 0 3 0 0 0])] Source #
Evaluation list for \(a^{ABC} \). Note that also when using the abstract indices this ansatz still features the symmetry under arbitrary permutations of \( ABC\).
metricList8_1 :: [([Int], Int, [IndTupleAbs 0 0 3 0 2 0])] Source #
Evaluation list for \(a^{ABp Cq}\). Note that also when using the abstract indices this ansatz still features the \( (Bp) \leftrightarrow (Cq) \) symmetry.
metricList8_2 :: [([Int], Int, [IndTupleAbs 0 0 4 0 0 0])] Source #
Evaluation list for \(a^{A B C I}\). Note that also when using the abstract indices this ansatz still features the \( (A) \leftrightarrow (B) \) symmetry.
Symmetry Lists
Area Metric
The following are examples of symmetry lists.
symList10_1 :: Symmetry Source #
Symmetry list for
.areaList10_1
symList10_2 :: Symmetry Source #
Symmetry list for
.areaList10_2
symList12 :: Symmetry Source #
Symmetry list for
.areaList12
symList14_1 :: Symmetry Source #
Symmetry list for
.areaList14_1
symList14_2 :: Symmetry Source #
Symmetry list for
.areaList14_2
Metric
The following are examples of symmetry lists.
metricsymList2 :: Symmetry Source #
Symmetry list for
.metricList2
metricsymList4_1 :: Symmetry Source #
Symmetry list for
.metricList4_1
metricsymList4_2 :: Symmetry Source #
Symmetry list for
.metricList4_2
metricsymList6_1 :: Symmetry Source #
Symmetry list for
.metricList6_1
metricsymList6_2 :: Symmetry Source #
Symmetry list for
.metricList6_2
metricsymList6_3 :: Symmetry Source #
Symmetry list for
.metricList6_3
metricsymList8_1 :: Symmetry Source #
Symmetry list for
.metricList8_1
metricsymList8_2 :: Symmetry Source #
Symmetry list for
.metricList8_2
areaList16_1 :: [([Int], Int, [IndTupleAbs 3 0 1 0 2 0])] Source #