Safe Haskell | None |
---|
Data.Vector.Fixed.Internal
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/
- data Z
- data S n
- type family Fn n a b
- newtype Fun n a b = Fun (Fn n a b)
- class Arity n where
- accum :: (forall k. t (S k) -> a -> t k) -> (t Z -> b) -> t n -> Fn n a b
- accumM :: Monad m => (forall k. t (S k) -> a -> m (t k)) -> (t Z -> m b) -> m (t n) -> Fn n a (m b)
- apply :: (forall k. t (S k) -> (a, t k)) -> t n -> Fn n a b -> b
- applyM :: Monad m => (forall k. t (S k) -> m (a, t k)) -> t n -> Fn n a b -> m b
- arity :: n -> Int
- type family Dim v
- class Arity (Dim v) => Vector v a where
- class (Vector (v n) a, Dim (v n) ~ n) => VectorN v n a
- length :: forall v a. Arity (Dim v) => v a -> Int
- newtype Cont n a = Cont (forall r. Fun n a r -> r)
- create :: (Arity (Dim v), Vector v a) => Cont (Dim v) a -> v a
- inspectV :: (Arity (Dim v), Vector v a) => v a -> Fun (Dim v) a b -> b
Type-level naturals
N-ary functions
Newtype wrapper which is used to make Fn
injective.
Type class for handling n-ary functions.
Methods
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.
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.
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.
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 of function.
Vector type class
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.
Continuation with arbitrary result.