free-vector-spaces-0.1.2.0: Instantiate the classes from the vector-space package with types from linear

Copyright(c) Justus Sagemüller 2016
LicenseGPL v3
Maintainer(@) sagemueller $ geo.uni-koeln.de
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.VectorSpace.Free

Contents

Description

 

Synopsis

Supported types

Fixed low dimension

These come from the linear package.

data V0 a :: * -> *

A 0-dimensional vector

>>> pure 1 :: V0 Int
V0
>>> V0 + V0
V0

Instances

Monad V0 
Functor V0 
MonadFix V0 
Applicative V0 
Foldable V0 
Traversable V0 
Generic1 V0 
MonadZip V0 
Representable V0 
Affine V0 
Metric V0 
Additive V0 
Eq1 V0 
Ord1 V0 
Read1 V0 
Show1 V0 
Serial1 V0 
Distributive V0 
Bind V0 
Apply V0 
Vector Vector (V0 a) 
MVector MVector (V0 a) 
Bounded (V0 a) 
Enum (V0 a) 
Eq (V0 a) 
Floating (V0 a) 
Fractional (V0 a) 
Data a => Data (V0 a) 
Num (V0 a) 
Ord (V0 a) 
Read (V0 a) 
Show (V0 a) 
Ix (V0 a) 
Generic (V0 a) 
Storable (V0 a) 
Binary (V0 a) 
NFData (V0 a) 
Hashable (V0 a) 
Epsilon (V0 a) 
Unbox (V0 a) 
Serialize (V0 a) 
Serial (V0 a) 
Ixed (V0 a) 
Num s => FiniteFreeSpace (V0 s) Source 
TraversableWithIndex (E V0) V0 
FunctorWithIndex (E V0) V0 
FoldableWithIndex (E V0) V0 
Each (V0 a) (V0 b) a b 
type Rep1 V0 = D1 D1V0 (C1 C1_0V0 U1) 
type Diff V0 = V0 
type Rep V0 = E V0 
data MVector s (V0 a) = MV_V0 Int 
type Rep (V0 a) = D1 D1V0 (C1 C1_0V0 U1) 
data Vector (V0 a) = V_V0 Int 
type Diff (V0 s) = V0 s 
type Basis (V0 s) = E V0 
type Scalar (V0 s) = s 
data (:->:) (E V0) = V0T (V0 a) 
type IxValue (V0 a) = a 
type Index (V0 a) = E V0 
type Diff (Point V0 s) = V0 s 

data V1 a :: * -> *

A 1-dimensional vector

>>> pure 1 :: V1 Int
V1 1
>>> V1 2 + V1 3
V1 5
>>> V1 2 * V1 3
V1 6
>>> sum (V1 2)
2

Instances

Monad V1 
Functor V1 
MonadFix V1 
Applicative V1 
Foldable V1 
Traversable V1 
Generic1 V1 
MonadZip V1 
Representable V1 
Affine V1 
R1 V1 
Metric V1 
Additive V1 
Eq1 V1 
Ord1 V1 
Read1 V1 
Show1 V1 
Serial1 V1 
Distributive V1 
Bind V1 
Apply V1 
Traversable1 V1 
Foldable1 V1 
Unbox a => Vector Vector (V1 a) 
Unbox a => MVector MVector (V1 a) 
Bounded a => Bounded (V1 a) 
Eq a => Eq (V1 a) 
Floating a => Floating (V1 a) 
Fractional a => Fractional (V1 a) 
Data a => Data (V1 a) 
Num a => Num (V1 a) 
Ord a => Ord (V1 a) 
Read a => Read (V1 a) 
Show a => Show (V1 a) 
Ix a => Ix (V1 a) 
Generic (V1 a) 
Storable a => Storable (V1 a) 
Binary a => Binary (V1 a) 
NFData a => NFData (V1 a) 
Hashable a => Hashable (V1 a) 
Epsilon a => Epsilon (V1 a) 
Unbox a => Unbox (V1 a) 
Serialize a => Serialize (V1 a) 
Serial a => Serial (V1 a) 
Ixed (V1 a) 
Num s => FiniteFreeSpace (V1 s) Source 
(Eq r, Fractional r) => OneDimensional (V1 r) Source 
TraversableWithIndex (E V1) V1 
FunctorWithIndex (E V1) V1 
FoldableWithIndex (E V1) V1 
Each (V1 a) (V1 b) a b 
type Rep1 V1 = D1 D1V1 (C1 C1_0V1 (S1 NoSelector Par1)) 
type Diff V1 = V1 
type Rep V1 = E V1 
data MVector s (V1 a) = MV_V1 (MVector s a) 
type Rep (V1 a) = D1 D1V1 (C1 C1_0V1 (S1 NoSelector (Rec0 a))) 
data Vector (V1 a) = V_V1 (Vector a) 
type Diff (V1 s) = V1 s 
type Basis (V1 s) = E V1 
type Scalar (V1 s) = s 
data (:->:) (E V1) = V1T (V1 a) 
type IxValue (V1 a) = a 
type Index (V1 a) = E V1 
type Diff (Point V1 s) = V1 s 

data V2 a :: * -> *

A 2-dimensional vector

>>> pure 1 :: V2 Int
V2 1 1
>>> V2 1 2 + V2 3 4
V2 4 6
>>> V2 1 2 * V2 3 4
V2 3 8
>>> sum (V2 1 2)
3

Instances

Monad V2 
Functor V2 
MonadFix V2 
Applicative V2 
Foldable V2 
Traversable V2 
Generic1 V2 
MonadZip V2 
Representable V2 
Affine V2 
R2 V2 
R1 V2 
Metric V2 
Additive V2 
Eq1 V2 
Ord1 V2 
Read1 V2 
Show1 V2 
Serial1 V2 
Distributive V2 
Bind V2 
Apply V2 
Traversable1 V2 
Foldable1 V2 
Unbox a => Vector Vector (V2 a) 
Unbox a => MVector MVector (V2 a) 
Bounded a => Bounded (V2 a) 
Eq a => Eq (V2 a) 
Floating a => Floating (V2 a) 
Fractional a => Fractional (V2 a) 
Data a => Data (V2 a) 
Num a => Num (V2 a) 
Ord a => Ord (V2 a) 
Read a => Read (V2 a) 
Show a => Show (V2 a) 
Ix a => Ix (V2 a) 
Generic (V2 a) 
Storable a => Storable (V2 a) 
Binary a => Binary (V2 a) 
NFData a => NFData (V2 a) 
Hashable a => Hashable (V2 a) 
Epsilon a => Epsilon (V2 a) 
Unbox a => Unbox (V2 a) 
Serialize a => Serialize (V2 a) 
Serial a => Serial (V2 a) 
Ixed (V2 a) 
Num s => FiniteFreeSpace (V2 s) Source 
TraversableWithIndex (E V2) V2 
FunctorWithIndex (E V2) V2 
FoldableWithIndex (E V2) V2 
Each (V2 a) (V2 b) a b 
type Rep1 V2 = D1 D1V2 (C1 C1_0V2 ((:*:) (S1 NoSelector Par1) (S1 NoSelector Par1))) 
type Diff V2 = V2 
type Rep V2 = E V2 
data MVector s (V2 a) = MV_V2 !Int !(MVector s a) 
type Rep (V2 a) = D1 D1V2 (C1 C1_0V2 ((:*:) (S1 NoSelector (Rec0 a)) (S1 NoSelector (Rec0 a)))) 
data Vector (V2 a) = V_V2 !Int !(Vector a) 
type Diff (V2 s) = V2 s 
type Basis (V2 s) = E V2 
type Scalar (V2 s) = s 
data (:->:) (E V2) = V2T (V2 a) 
type IxValue (V2 a) = a 
type Index (V2 a) = E V2 
type Diff (Point V2 s) = V2 s 

data V3 a :: * -> *

A 3-dimensional vector

Instances

Monad V3 
Functor V3 
MonadFix V3 
Applicative V3 
Foldable V3 
Traversable V3 
Generic1 V3 
MonadZip V3 
Representable V3 
Affine V3 
R3 V3 
R2 V3 
R1 V3 
Metric V3 
Additive V3 
Eq1 V3 
Ord1 V3 
Read1 V3 
Show1 V3 
Serial1 V3 
Distributive V3 
Bind V3 
Apply V3 
Traversable1 V3 
Foldable1 V3 
Unbox a => Vector Vector (V3 a) 
Unbox a => MVector MVector (V3 a) 
Bounded a => Bounded (V3 a) 
Eq a => Eq (V3 a) 
Floating a => Floating (V3 a) 
Fractional a => Fractional (V3 a) 
Data a => Data (V3 a) 
Num a => Num (V3 a) 
Ord a => Ord (V3 a) 
Read a => Read (V3 a) 
Show a => Show (V3 a) 
Ix a => Ix (V3 a) 
Generic (V3 a) 
Storable a => Storable (V3 a) 
Binary a => Binary (V3 a) 
NFData a => NFData (V3 a) 
Hashable a => Hashable (V3 a) 
Epsilon a => Epsilon (V3 a) 
Unbox a => Unbox (V3 a) 
Serialize a => Serialize (V3 a) 
Serial a => Serial (V3 a) 
Ixed (V3 a) 
Num s => FiniteFreeSpace (V3 s) Source 
TraversableWithIndex (E V3) V3 
FunctorWithIndex (E V3) V3 
FoldableWithIndex (E V3) V3 
Each (V3 a) (V3 b) a b 
type Rep1 V3 = D1 D1V3 (C1 C1_0V3 ((:*:) (S1 NoSelector Par1) ((:*:) (S1 NoSelector Par1) (S1 NoSelector Par1)))) 
type Diff V3 = V3 
type Rep V3 = E V3 
data MVector s (V3 a) = MV_V3 !Int !(MVector s a) 
type Rep (V3 a) = D1 D1V3 (C1 C1_0V3 ((:*:) (S1 NoSelector (Rec0 a)) ((:*:) (S1 NoSelector (Rec0 a)) (S1 NoSelector (Rec0 a))))) 
data Vector (V3 a) = V_V3 !Int !(Vector a) 
type Diff (V3 s) = V3 s 
type Basis (V3 s) = E V3 
type Scalar (V3 s) = s 
data (:->:) (E V3) = V3T (V3 a) 
type IxValue (V3 a) = a 
type Index (V3 a) = E V3 
type Diff (Point V3 s) = V3 s 

data V4 a :: * -> *

A 4-dimensional vector.

Instances

Monad V4 
Functor V4 
MonadFix V4 
Applicative V4 
Foldable V4 
Traversable V4 
Generic1 V4 
MonadZip V4 
Representable V4 
Affine V4 
R4 V4 
R3 V4 
R2 V4 
R1 V4 
Metric V4 
Additive V4 
Eq1 V4 
Ord1 V4 
Read1 V4 
Show1 V4 
Serial1 V4 
Distributive V4 
Bind V4 
Apply V4 
Traversable1 V4 
Foldable1 V4 
Unbox a => Vector Vector (V4 a) 
Unbox a => MVector MVector (V4 a) 
Bounded a => Bounded (V4 a) 
Eq a => Eq (V4 a) 
Floating a => Floating (V4 a) 
Fractional a => Fractional (V4 a) 
Data a => Data (V4 a) 
Num a => Num (V4 a) 
Ord a => Ord (V4 a) 
Read a => Read (V4 a) 
Show a => Show (V4 a) 
Ix a => Ix (V4 a) 
Generic (V4 a) 
Storable a => Storable (V4 a) 
Binary a => Binary (V4 a) 
NFData a => NFData (V4 a) 
Hashable a => Hashable (V4 a) 
Epsilon a => Epsilon (V4 a) 
Unbox a => Unbox (V4 a) 
Serialize a => Serialize (V4 a) 
Serial a => Serial (V4 a) 
Ixed (V4 a) 
Num s => FiniteFreeSpace (V4 s) Source 
TraversableWithIndex (E V4) V4 
FunctorWithIndex (E V4) V4 
FoldableWithIndex (E V4) V4 
Each (V4 a) (V4 b) a b 
type Rep1 V4 = D1 D1V4 (C1 C1_0V4 ((:*:) ((:*:) (S1 NoSelector Par1) (S1 NoSelector Par1)) ((:*:) (S1 NoSelector Par1) (S1 NoSelector Par1)))) 
type Diff V4 = V4 
type Rep V4 = E V4 
data MVector s (V4 a) = MV_V4 !Int !(MVector s a) 
type Rep (V4 a) = D1 D1V4 (C1 C1_0V4 ((:*:) ((:*:) (S1 NoSelector (Rec0 a)) (S1 NoSelector (Rec0 a))) ((:*:) (S1 NoSelector (Rec0 a)) (S1 NoSelector (Rec0 a))))) 
data Vector (V4 a) = V_V4 !Int !(Vector a) 
type Diff (V4 s) = V4 s 
type Basis (V4 s) = E V4 
type Scalar (V4 s) = s 
data (:->:) (E V4) = V4T (V4 a) 
type IxValue (V4 a) = a 
type Index (V4 a) = E V4 
type Diff (Point V4 s) = V4 s 

Arbitrary dimension

data FinSuppSeq n Source

The space of finitely-supported sequences is an infinite-dimensional space. An vector of length l is here understood as an infinite sequence that begins with l nonzero values, and continues with infinite zeroes.

You may also consider this as the type that languages like Octave/Matlab (as well as Haskell's hmatrix library) approximate with their “vectors”, with one important difference: there is no such thing as a dimensional-mismatch error, since we consider all these vectors as elements of the same infinite-dimensional space. Adding two different-size vectors will simply zero-pad the shorter, and unlike in Matlab this behaviour extends consequently to matrix multiplication etc. (defined in linearmap-category)

Of course it can make sense to constrain the dimension, but for this the type system should be used, not runtime checks.

(This is the same behaviour that the linear library gives to the standard list and vector types, but the problem there is that it can't use unboxed arrays as these are not functors, but unboxing is crucial for performance.)

The vector-space type classes

General

These come from the vector-space package.

class AdditiveGroup (Diff p) => AffineSpace p where

Associated Types

type Diff p :: *

Associated vector space

Methods

(.-.) :: p -> p -> Diff p infix 6

Subtract points

(.+^) :: p -> Diff p -> p infixl 6

Point plus vector

class AdditiveGroup v where

Additive group v.

Minimal complete definition

zeroV, (^+^), negateV

Methods

zeroV :: v

The zero element: identity for '(^+^)'

(^+^) :: v -> v -> v infixl 6

Add vectors

negateV :: v -> v

Additive inverse

(^-^) :: v -> v -> v infixl 6

Group subtraction

class AdditiveGroup v => VectorSpace v where

Vector space v.

Associated Types

type Scalar v :: *

Methods

(*^) :: Scalar v -> v -> v infixr 7

Scale a vector

Instances

class (VectorSpace v, AdditiveGroup (Scalar v)) => InnerSpace v where

Adds inner (dot) products.

Methods

(<.>) :: v -> v -> Scalar v infixr 7

Inner/dot product

Instances

class VectorSpace v => HasBasis v where

Associated Types

type Basis v :: *

Representation of the canonical basis for v

Methods

basisValue :: Basis v -> v

Interpret basis rep as a vector

decompose :: v -> [(Basis v, Scalar v)]

Extract coordinates

decompose' :: v -> Basis v -> Scalar v

Experimental version. More elegant definitions, and friendly to infinite-dimensional vector spaces.

Instances

HasBasis Double 
HasBasis Float 
HasBasis CFloat 
HasBasis CDouble 
Integral a => HasBasis (Ratio a) 
(Num n, Unbox n) => HasBasis (FinSuppSeq n) 
(Num n, Unbox n) => HasBasis (Sequence n) 
(HasBasis u, (~) * s (Scalar u), HasBasis v, (~) * s (Scalar v)) => HasBasis (u, v) 
(HasBasis u, (~) * s (Scalar u), HasBasis v, (~) * s (Scalar v), HasBasis w, (~) * s (Scalar w)) => HasBasis (u, v, w) 

Small

class (VectorSpace v, Fractional (Scalar v)) => OneDimensional v where Source

Minimal complete definition

(^/^)

Methods

(^/^) :: v -> v -> Maybe (Scalar v) infixr 7 Source

Compare the (directed) length of two vectors.

(^/!) :: v -> v -> Scalar v infixr 7 Source

Unsafe version of ^/^.

Free