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

Safe HaskellSafe-Inferred

Data.TypeList.MultiIndex

Description

We define the a multidimensional array of indices called MultiIndex. The canonical implementation of a MultiIndex is an heterogeneous list of Ordinals. Below we illustrate some example of MultiIndex types and the elements they contain.

Three :|: Nil = {(1),(2),(3)}

Three :|: (Two :|: Nil) = {(1,1),(1,2),(2,1),(2,2),(3,1),(3,2)}

Three :|: (Two :|: (Two :|: Nil)) = {(1,1,1),(1,1,2),(1,2,1),(1,2,2),(2,1,1),(2,1,2),(2,2,1),(2,2,2),(3,1,1),(3,1,2),(3,2,1),(3,2,2)}

Synopsis

Documentation

data a :|: b Source

This is the constructor for heterogeneous lists, equivalent to : for standard lists. Nil is used to end the lists, just like '[]'.

Constructors

a :|: b 

Instances

(Ordinal i, Ordinal j) => Matrix i j (Tensor (:|: i (:|: j Nil)) e) 
DropList Zero l => DropList Zero (:|: e l) 
TakeList Zero l => TakeList Zero (:|: e l) 
(Ordinal i1, Ordinal i2, Sum i1 i2, MultiIndex is) => MultiIndexConcat Zero (:|: i1 is) (:|: i2 is) 
(MultiIndex is, Ordinal n, Functor (Tensor is), Functor (Tensor (:|: n is))) => Functor (Tensor (:|: (Succ n) is)) 
(MultiIndex is, Functor (Tensor is)) => Functor (Tensor (:|: One is)) 
(MultiIndex is, Ordinal n, Applicative (Tensor is), Applicative (Tensor (:|: n is))) => Applicative (Tensor (:|: (Succ n) is)) 
(MultiIndex is, Applicative (Tensor is)) => Applicative (Tensor (:|: One is)) 
(FromList (Tensor is), FromList (Tensor (:|: n is)), Ordinal n, MultiIndex is) => FromList (Tensor (:|: (Succ n) is)) 
(FromList (Tensor is), MultiIndex is) => FromList (Tensor (:|: One is)) 
(Ordinal i, Sum i i) => SquareMatrix (Tensor (:|: i (:|: i Nil))) 
DropList n l => DropList (Succ n) (:|: e l) 
TakeList n l => TakeList (Succ n) (:|: e l) 
(Cardinal n, Ordinal i, MultiIndex js, MultiIndex ks, MultiIndexConcat n js ks) => MultiIndexConcat (Succ n) (:|: i js) (:|: i ks) 
(Bounded e, Bounded l) => Bounded (:|: e l) 
(Eq a, Eq b) => Eq (:|: a b) 
(MultiIndex is, Ordinal n, Eq (Tensor is e), Eq (Tensor (:|: n is) e)) => Eq (Tensor (:|: (Succ n) is) e) 
(MultiIndex is, Eq (Tensor is e)) => Eq (Tensor (:|: One is) e) 
(Ordinal i, MultiIndex is) => Show (:|: i is) 
(MultiIndex is, Ordinal n, Show (Tensor is e), Show (Tensor (:|: n is) e)) => Show (Tensor (:|: (Succ n) is) e) 
(MultiIndex is, Show (Tensor is e)) => Show (Tensor (:|: One is) e) 
Generic (:|: a b) 
(Random e, Random l) => Random (:|: e l) 
(Ordinal i, Ordinal j) => Transpose (Tensor (:|: i (:|: j Nil)) e) 
(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) 
(Cardinality e, Cardinality l, Cardinal (:*: (Card e) (Card l))) => Cardinality (:|: e l) 
(TailRevList l Nil, TailRevList (:|: e l) Nil) => ReverseList (:|: e l) 
TypeList l => HeadTail (:|: e l) 
TypeList l => TypeList (:|: e l) 
(Ordinal i, Dimensions is) => Dimensions (:|: i is) 
Dimensions (Tensor (:|: n is) e) => Dimensions (Tensor (:|: (Succ n) is) e) 
Dimensions (Tensor is e) => Dimensions (Tensor (:|: One is) e) 
(Ordinal i, MultiIndex is) => MultiIndex (:|: i is) 
(TailRevList l (:|: e l'), TypeList l') => TailRevList (:|: e l) l' 
AppendList l l' => AppendList (:|: e l) l' 
Extend l l' => Extend (:|: e l) (:|: e l') 
(Eq e, Fractional e, Ordinal i, Ordinal j) => LinearSystem (Tensor (:|: i (:|: j Nil)) e) (Tensor (:|: i Nil) e) 
(Eq e, Fractional e, Ordinal i, Ordinal j, Ordinal k, Sum j k) => LinearSystem (Tensor (:|: i (:|: j Nil)) e) (Tensor (:|: i (:|: k Nil)) e) 

class (Dimensions i, TypeList i) => MultiIndex i whereSource

Methods

fromMultiIndex :: Num n => i -> [n]Source

toMultiIndex :: (Eq n, Num n) => [n] -> iSource

Instances

class Dimensions i whereSource

Class for types having multiple dimensions, like MultiIndexes or Tensors.

Methods

dimensions :: Num n => i -> [n]Source

Returns the dimensions list. It should always be independent on its argument and work on undefined.

Instances

class (Cardinal n, MultiIndex is, MultiIndex js) => MultiIndexConcat n is js Source

Associated Types

type Concat n is js Source

Instances

(Ordinal i1, Ordinal i2, Sum i1 i2, MultiIndex is) => MultiIndexConcat Zero (:|: i1 is) (:|: i2 is) 
(Cardinal n, Ordinal i, MultiIndex js, MultiIndex ks, MultiIndexConcat n js ks) => MultiIndexConcat (Succ n) (:|: i js) (:|: i ks)