Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | Nicola Squartini <tensor5@gmail.com> |
Safe Haskell | Safe-Inferred |
- class Tensor t where
- replicate :: Tensor t => Elem t -> t
- replicateM :: (Monad m, Tensor t) => m (Elem t) -> m t
- elemMap :: (Tensor t1, Tensor t2, Index t1 ~ Index t2) => (Elem t1 -> Elem t2) -> t1 -> t2
- indexMap :: (Tensor t1, Tensor t2, Elem t1 ~ Elem t2) => (Index t1 -> Index t2) -> t2 -> t1
- class FromList t where
- fromList :: [e] -> t e
- class DirectSum n t1 t2 where
- class Transpose t where
- type TransposeSpace t
- transpose :: t -> TransposeSpace t
- class Sliceable i j t where
Documentation
(!) :: t -> Index t -> Elem tSource
returns the dimensions of the dims
. In any
instance of Tensor
Tensor
should be independent of its
argument and work on dims
.
| Returns the undefined
ent of Elem
t
corresponding to
.
Index
t
generate :: (Index t -> Elem t) -> tSource
Generates a
according to the given function.
Tensor
generateM :: Monad m => (Index t -> m (Elem t)) -> m tSource
(MultiIndex is, Ordinal n, Tensor (Tensor is e), Tensor (Tensor (:|: n is) e), ~ * e (Elem (Tensor is e)), ~ * is (Index (Tensor is e)), ~ * e (Elem (Tensor (:|: n is) e)), ~ * (Index (Tensor (:|: n is) e)) (:|: n is)) => Tensor (Tensor (:|: (Succ n) is) e) | |
(MultiIndex is, Tensor (Tensor is e), ~ * e (Elem (Tensor is e)), ~ * is (Index (Tensor is e))) => Tensor (Tensor (:|: One is) e) | |
Tensor (Tensor Nil e) | |
MultiIndex i => Tensor (Tensor i e) |
replicateM :: (Monad m, Tensor t) => m (Elem t) -> m tSource
class DirectSum n t1 t2 whereSource
(Cardinal n, MultiIndex i, MultiIndex j, MultiIndexConcat n i j) => DirectSum n (Tensor i e) (Tensor j e) |
type TransposeSpace t Source
transpose :: t -> TransposeSpace tSource
class Sliceable i j t whereSource
Slices the Tensor
t
by dropping i
at the beginning of its
and Index
j
at the end. The result has type
.
Slice
i j t
slice :: i -> j -> t -> Slice i j tSource
Extracts the
of Slice
t
for the given initial and final
indices i
and j
.
(MultiIndex i, MultiIndex j, Extend i l, ReverseList j, ReverseList (Ext i l), Extend (Reverse j) (Reverse (Ext i l)), ReverseList (Ext (Reverse j) (Reverse (Ext i l)))) => Sliceable i j (Tensor l e) |