tensor-0.3.0: A completely type-safe library for linear algebra

Safe HaskellSafe-Inferred

Data.Tensor

Synopsis

Documentation

class Tensor t whereSource

A Tensor is a map from an Index type (which should be a MultiIndex) to an Element type.

Associated Types

type Index t Source

type Elem t Source

Methods

(!) :: t -> Index t -> Elem tSource

dims returns the dimensions of the Tensor. In any instance of Tensor dims should be independent of its argument and work on undefined. | Returns the Element of t corresponding to Index t.

generate :: (Index t -> Elem t) -> tSource

Generates a Tensor according to the given function.

generateM :: Monad m => (Index t -> m (Elem t)) -> m tSource

Instances

(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) 

replicate :: Tensor t => Elem t -> tSource

Generates a Tensor consisting of the same Element repeated.

replicateM :: (Monad m, Tensor t) => m (Elem t) -> m tSource

elemMap :: (Tensor t1, Tensor t2, Index t1 ~ Index t2) => (Elem t1 -> Elem t2) -> t1 -> t2Source

elemMap f t applies f to every Element of t.

indexMap :: (Tensor t1, Tensor t2, Elem t1 ~ Elem t2) => (Index t1 -> Index t2) -> t2 -> t1Source

In indexMap f t, the Element corresponding to the Index i is the Element that t assignes to the Index f i.

class FromList t whereSource

Methods

fromList :: [e] -> t eSource

Instances

class DirectSum n t1 t2 whereSource

Associated Types

type SumSpace n t1 t2 Source

Methods

directSum :: n -> t1 -> t2 -> SumSpace n t1 t2Source

split :: n -> SumSpace n t1 t2 -> (t1, t2)Source

Instances

class Transpose t whereSource

Associated Types

type TransposeSpace t Source

Instances

(Ordinal i, Ordinal j) => Transpose (Tensor (:|: i (:|: j Nil)) e) 

class Sliceable i j t whereSource

Slices the Tensor t by dropping i at the beginning of its Index and j at the end. The result has type Slice i j t.

Associated Types

type Slice i j t Source

Methods

slice :: i -> j -> t -> Slice i j tSource

Extracts the Slice of t for the given initial and final indices i and j.

Instances

(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)