safe-tensor-0.2.1.0: Dependently typed tensor algebra
Copyright(c) Nils Alex 2020
LicenseMIT
Maintainernils.alex@fau.de
Safe HaskellNone
LanguageHaskell2010

Math.Tensor.Basic.Epsilon

Description

Definitions of covariant and contravariant epsilon tensor densities like \(\epsilon_{abc}\).

Synopsis

Epsilon tensor densities

epsilon' :: forall (id :: Symbol) (n :: Nat) (is :: NonEmpty Symbol) (r :: Rank) v. (KnownNat n, Num v, EpsilonRank id n is ~ 'Just r, SingI r) => Sing id -> Sing n -> Sing is -> Tensor r v Source #

Totally antisymmetric covariant tensor density of weight -1 such that

\[ \epsilon_{12\dots n} = 1. \]

Vector space label, vector space dimension and index labels are passed as singletons.

someEpsilon :: forall v m. (Num v, MonadError String m) => Demote Symbol -> Demote Nat -> [Demote Symbol] -> m (T v) Source #

Totally antisymmetric covariant tensor density of weight -1 such that

\[ \epsilon_{12\dots n} = 1. \]

Vector space label, vector space dimension and index labels are passed as values. Result is existentially quantified.

epsilonInv' :: forall (id :: Symbol) (n :: Nat) (is :: NonEmpty Symbol) (r :: Rank) v. (KnownNat n, Num v, EpsilonInvRank id n is ~ 'Just r, SingI r) => Sing id -> Sing n -> Sing is -> Tensor r v Source #

Totally antisymmetric contravariant tensor density of weight +1 such that

\[ \epsilon^{12\dots n} = 1. \]

Vector space label, vector space dimension and index labels are passed as singletons.

someEpsilonInv :: forall v m. (Num v, MonadError String m) => Demote Symbol -> Demote Nat -> [Demote Symbol] -> m (T v) Source #

Totally antisymmetric contravariant tensor density of weight +1 such that

\[ \epsilon^{12\dots n} = 1. \]

Vector space label, vector space dimension and index labels are passed as values. Result is existentially quantified.

Internals

permSign :: (Num v, Ord a) => [a] -> v Source #

Sign of a permutation:

  permSign [1,2,3] = 1
  permSign [2,1,3] = -1