tensor-0.2.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 Nil Source

Constructors

Nil 

Instances

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

(Tensor (Tensor (:|: i (:|: j Nil)) e), ~ * (Index (Tensor (:|: i (:|: j Nil)) e)) (:|: i (:|: j Nil)), Ordinal i, Ordinal j) => Matrix i j (Tensor (:|: i (:|: j Nil)) e) 
(Cardinal Zero, TypeList (:|: e l), DropList Zero l) => DropList Zero (:|: e l) 
(Cardinal Zero, TypeList (:|: e l), TakeList Zero l) => TakeList Zero (:|: e l) 
(Cardinal Zero, MultiIndex (:|: i1 is), MultiIndex (:|: i2 is), Ordinal i1, Ordinal i2, Sum i1 i2, MultiIndex is) => MultiIndexConcat Zero (:|: i1 is) (:|: i2 is) 
(Ordinal i, Sum i i) => SquareMatrix (Tensor (:|: i (:|: i Nil))) 
(Cardinal (Succ n), TypeList (:|: e l), DropList n l) => DropList (Succ n) (:|: e l) 
(Cardinal (Succ n), TypeList (:|: e l), TakeList n l) => TakeList (Succ n) (:|: e l) 
(Cardinal (Succ n), MultiIndex (:|: i js), MultiIndex (:|: i ks), 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) 
(Eq (:|: e l), Ord e, Ord l) => Ord (:|: e l) 
(Ordinal i, MultiIndex is) => Show (:|: i is) 
Generic (:|: a b) 
(Ordinal i, Ordinal j) => Transpose (Tensor (:|: i (:|: j Nil)) e) 
(Cardinal (Card (:|: e l)), Cardinality e, Cardinality l, Cardinal (:*: (Card e) (Card l))) => Cardinality (:|: e l) 
(TypeList (:|: e l), TailRevList l Nil, TailRevList (:|: e l) Nil) => ReverseList (:|: e l) 
(TypeList (:|: e l), TypeList l) => HeadTail (:|: e l) 
TypeList l => TypeList (:|: e l) 
(Ordinal i, Dimensions is) => Dimensions (:|: i is) 
(Dimensions (:|: i is), TypeList (:|: i is), Ordinal i, MultiIndex is) => MultiIndex (:|: i is) 
(TypeList (:|: e l), TailRevList l (:|: e l'), TypeList l') => TailRevList (:|: e l) l' 
(TypeList (:|: e l), TypeList 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

MultiIndex Nil 
(Dimensions (:|: i is), TypeList (:|: i is), Ordinal i, MultiIndex is) => MultiIndex (:|: i is) 

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

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