Copyright | (c) Nils Alex 2020 |
---|---|
License | MIT |
Maintainer | nils.alex@fau.de |
Safe Haskell | None |
Language | Haskell2010 |
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
- data T :: Type -> Type where
- type Label = Demote Symbol
- type Dimension = Demote Nat
- type RankT = Demote Rank
- rankT :: T v -> RankT
- scalarT :: v -> T v
- zeroT :: MonadError String m => RankT -> m (T v)
- toListT :: T v -> [([Int], v)]
- fromListT :: MonadError String m => RankT -> [([Int], v)] -> m (T v)
- removeZerosT :: (Eq v, Num v) => T v -> T v
- (.*) :: (Num v, MonadError String m) => T v -> T v -> m (T v)
- (.+) :: (Eq v, Num v, MonadError String m) => T v -> T v -> m (T v)
- (.-) :: (Eq v, Num v, MonadError String m) => T v -> T v -> m (T v)
- (.°) :: Num v => v -> T v -> T v
- contractT :: (Num v, Eq v) => T v -> T v
- transposeT :: MonadError String m => VSpace Label Dimension -> Ix Label -> Ix Label -> T v -> m (T v)
- transposeMultT :: MonadError String m => VSpace Label Dimension -> [(Label, Label)] -> [(Label, Label)] -> T v -> m (T v)
- relabelT :: MonadError String m => VSpace Label Dimension -> [(Label, Label)] -> T v -> m (T v)
- conRank :: (MonadError String m, Integral a, Ord s, Ord n, Num n) => s -> a -> [s] -> m (GRank s n)
- covRank :: (MonadError String m, Integral a, Ord s, Ord n, Num n) => s -> a -> [s] -> m (GRank s n)
- conCovRank :: (MonadError String m, Integral a, Ord s, Ord n, Num n) => s -> a -> [s] -> [s] -> m (GRank s n)
Existentially quantified tensor
Wrapping a
in a Tensor
r v
allows to define tensor operations like
additions or multiplications without any constraints on the generalized ranks
of the operands.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.
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.
Special tensors
of given value. Result is pure
because there is only one possible rank: Scalar
'[]
zeroT :: MonadError String m => RankT -> m (T v) Source #
of given rank ZeroTensor
r
. Throws an
error if
.Sane
r ~ 'False
Conversion from and to lists
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
(.+) :: (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 '(&-)'
.
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.