fixed-vector-0.1.2: Generic vectors with fixed length

Safe HaskellNone

Data.Vector.Fixed.Internal

Contents

Description

Type classes for generic vectors. This module exposes type classes and auxiliary functions needed to write generic functions not present in the module Data.Vector.Fixed.

Implementation is based on http://unlines.wordpress.com/2010/11/15/generics-for-small-fixed-size-vectors/

Synopsis

Type-level naturals

data Z Source

Type level zero

Instances

data S n Source

Successor of n

Instances

Arity n => Arity (S n) 

N-ary functions

type family Fn n a b Source

Type family for n-ary functions.

newtype Fun n a b Source

Newtype wrapper which is used to make Fn injective.

Constructors

Fun (Fn n a b) 

Instances

Arity n => Functor (Fun n a) 

class Arity n whereSource

Type class for handling n-ary functions.

Methods

accumSource

Arguments

:: (forall k. t (S k) -> a -> t k)

Fold function

-> (t Z -> b)

Extract result of fold

-> t n

Initial value

-> Fn n a b

Reduction function

Left fold over n elements exposed as n-ary function.

accumMSource

Arguments

:: Monad m 
=> (forall k. t (S k) -> a -> m (t k))

Fold function

-> (t Z -> m b)

Extract result of fold

-> m (t n)

Initial value

-> Fn n a (m b)

Reduction function

Monadic left fold.

applySource

Arguments

:: (forall k. t (S k) -> (a, t k))

Get value to apply to function

-> t n

Initial value

-> Fn n a b

N-ary function

-> b 

Apply all parameters to the function.

applyMSource

Arguments

:: Monad m 
=> (forall k. t (S k) -> m (a, t k))

Get value to apply to function

-> t n

Initial value

-> Fn n a b

N-ary function

-> m b 

Monadic apply

arity :: n -> IntSource

Arity of function.

Instances

Arity Z 
Arity n => Arity (S n) 

Vector type class

type family Dim v Source

Size of vector expressed as type-level natural.

class Arity (Dim v) => Vector v a whereSource

Type class for vectors with fixed length.

Methods

construct :: Fun (Dim v) a (v a)Source

N-ary function for creation of vectors.

inspect :: v a -> Fun (Dim v) a b -> bSource

Deconstruction of vector.

Instances

(Arity (Dim Complex), RealFloat a) => Vector Complex a 
(Arity (Dim (VecList n)), Arity n) => Vector (VecList n) a 
(Arity (Dim (Vec n)), Arity n) => Vector (Vec n) a 
(Arity (Dim (Vec n)), Arity n, Prim a) => Vector (Vec n) a 
(Arity (Dim (Vec n)), Unbox n a) => Vector (Vec n) a 
(Arity (Dim (Vec n)), Arity n, Storable a) => Vector (Vec n) a 

class (Vector (v n) a, Dim (v n) ~ n) => VectorN v n a Source

Vector parametrized by length. In ideal world it should be:

 forall n. (Arity n, Vector (v n) a, Dim (v n) ~ n) => VectorN v a

Alas polymorphic constraints aren't allowed in haskell.

Instances

(Vector (VecList n) a, ~ * (Dim (VecList n)) n, Arity n) => VectorN VecList n a 
(Vector (Vec n) a, ~ * (Dim (Vec n)) n, Arity n) => VectorN Vec n a 
(Vector (Vec n) a, ~ * (Dim (Vec n)) n, Arity n, Prim a) => VectorN Vec n a 
(Vector (Vec n) a, ~ * (Dim (Vec n)) n, Unbox n a) => VectorN Vec n a 
(Vector (Vec n) a, ~ * (Dim (Vec n)) n, Arity n, Storable a) => VectorN Vec n a 

length :: forall v a. Arity (Dim v) => v a -> IntSource

Length of vector. Function doesn't evaluate its argument.

Deforestation

Explicit deforestation is less important for ADT based vectors since GHC is able to eliminate intermediate data structures. But it cannot do so for array-based ones so intermediate vector have to be removed with RULES. Following identity is used. Of course f must be polymorphic in continuation result type.

 inspect (f construct) g = f g

But construct function is located somewhere deep in function application stack so it cannot be matched using rule. Function create is needed to move construct to the top.

As a rule function which are subject to deforestation should be written using create and inspectV functions.

newtype Cont n a Source

Continuation with arbitrary result.

Constructors

Cont (forall r. Fun n a r -> r) 

create :: (Arity (Dim v), Vector v a) => Cont (Dim v) a -> v aSource

Construct vector. It should be used instead of construct to get deforestation. Example of usage:

 cont1 $ cont2 $ construct

becomes

 create $ Cont $ cont1 . cont2

inspectV :: (Arity (Dim v), Vector v a) => v a -> Fun (Dim v) a b -> bSource

Wrapper for inspect. It's inlined later and is needed in order to give deforestation rule chance to fire.