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

Math.Tensor

Description

Existentially quantified wrapper around the safe interface from Math.Tensor.Safe. In contrast to the safe interface, all tensor operations are fair game, but potentially illegal operations take place in the Error monad Control.Monad.Except and may fail with an error message.

For usage examples, see https://github.com/nilsalex/safe-tensor/#readme.

For the documentation on generalized tensor ranks, see Math.Tensor.Safe.

Synopsis

Existentially quantified tensor

Wrapping a Tensor r v in a T v allows to define tensor operations like additions or multiplications without any constraints on the generalized ranks of the operands.

data T :: Type -> Type where Source #

T wraps around Tensor and exposes only the value type v.

Constructors

T :: forall (r :: Rank) v. SingI r => Tensor r v -> T v 

Instances

Instances details
Functor T Source # 
Instance details

Defined in Math.Tensor

Methods

fmap :: (a -> b) -> T a -> T b #

(<$) :: a -> T b -> T a #

Show v => Show (T v) Source # 
Instance details

Defined in Math.Tensor

Methods

showsPrec :: Int -> T v -> ShowS #

show :: T v -> String #

showList :: [T v] -> ShowS #

NFData v => NFData (T v) Source # 
Instance details

Defined in Math.Tensor

Methods

rnf :: T v -> () #

Unrefined rank types

These unrefined versions of the types used to parameterise generalized tensor ranks are used in functions producing or manipulating existentially quantified tensors.

type Label = Demote Symbol Source #

The unrefined type of labels.

 Demote Symbol ~ Text

type Dimension = Demote Nat Source #

The unrefined type of dimensions.

 Demote Nat ~ Natural

type RankT = Demote Rank Source #

The unrefined type of generalized tensor ranks.

 Demote Rank ~ GRank Label Dimension ~ [(VSpace Label Dimension, IList Dimension)]

Tensor operations

The existentially quantified versions of tensor operations from Math.Tensor.Safe. Some operations are always safe and therefore pure. The unsafe operations take place in the Error monad Control.Monad.Except.

rankT :: T v -> RankT Source #

Hidden rank over which T quantifies. Possible because of the SingI r constraint.

Special tensors

scalarT :: v -> T v Source #

Scalar of given value. Result is pure because there is only one possible rank: '[]

zeroT :: MonadError String m => RankT -> m (T v) Source #

ZeroTensor of given rank r. Throws an error if Sane r ~ 'False.

Conversion from and to lists

toListT :: T v -> [([Int], v)] Source #

Assocs list of the tensor.

fromListT :: MonadError String m => RankT -> [([Int], v)] -> m (T v) Source #

Constructs a tensor from a rank and an assocs list. Throws an error for illegal ranks or incompatible assocs lists.

removeZerosT :: (Eq v, Num v) => T v -> T v Source #

Pure function removing all zeros from a tensor. Wraps around removeZeros.

Tensor algebra

(.*) :: (Num v, MonadError String m) => T v -> T v -> m (T v) infixl 7 Source #

Tensor product. Throws an error if ranks overlap, i.e. MergeR r1 r2 ~ 'Nothing. Wraps around (&*).

(.+) :: (Eq v, Num v, MonadError String m) => T v -> T v -> m (T v) infixl 6 Source #

Tensor addition. Throws an error if summand ranks do not coincide. Wraps around (&+).

(.-) :: (Eq v, Num v, MonadError String m) => T v -> T v -> m (T v) Source #

Tensor subtraction. Throws an error if summand ranks do not coincide. Wraps around (&-).

(.°) :: Num v => v -> T v -> T v infixl 7 Source #

Scalar multiplication of a tensor.

Other operations

contractT :: (Num v, Eq v) => T v -> T v Source #

Tensor contraction. Pure function, because a tensor of any rank can be contracted. Wraps around contract.

transposeT :: MonadError String m => VSpace Label Dimension -> Ix Label -> Ix Label -> T v -> m (T v) Source #

Tensor transposition. Throws an error if given indices cannot be transposed. Wraps around transpose.

transposeMultT :: MonadError String m => VSpace Label Dimension -> [(Label, Label)] -> [(Label, Label)] -> T v -> m (T v) Source #

Transposition of multiple indices. Throws an error if given indices cannot be transposed. Wraps around transposeMult.

relabelT :: MonadError String m => VSpace Label Dimension -> [(Label, Label)] -> T v -> m (T v) Source #

Relabelling of tensor indices. Throws an error if given relabellings are not allowed. Wraps around relabel.

Rank construction

conRank :: (MonadError String m, Integral a, Ord s, Ord n, Num n) => s -> a -> [s] -> m (GRank s n) Source #

Contravariant rank from vector space label, vector space dimension, and list of index labels. Throws an error for illegal ranks.

covRank :: (MonadError String m, Integral a, Ord s, Ord n, Num n) => s -> a -> [s] -> m (GRank s n) Source #

Covariant rank from vector space label, vector space dimension, and list of index labels. Throws an error for illegal ranks.

conCovRank :: (MonadError String m, Integral a, Ord s, Ord n, Num n) => s -> a -> [s] -> [s] -> m (GRank s n) Source #

Mixed rank from vector space label, vector space dimension, and lists of index labels. Throws an error for illegal ranks.