fixed-vector-0.2.0.0: Generic vectors with fixed length

Safe HaskellSafe-Inferred

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) 

Synonyms for small numerals

type N1 = S ZSource

type N2 = S N1Source

type N3 = S N2Source

type N4 = S N3Source

type N5 = S N4Source

type N6 = S N5Source

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 (m 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

RealFloat a => Vector Complex a 
~ * b a => Vector ((,) b) a 
Arity n => Vector (VecList n) a 
Arity n => Vector (Vec n) a 
(Arity n, Prim a) => Vector (Vec n) a 
Unbox n a => Vector (Vec n) a 
(Arity n, Storable a) => Vector (Vec n) a 
(~ * b a, ~ * c a) => Vector ((,,) b c) a 
(~ * b a, ~ * c a, ~ * d a) => Vector ((,,,) b c d) a 
(~ * b a, ~ * c a, ~ * d a, ~ * e a) => Vector ((,,,,) b c d e) 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

Arity n => VectorN VecList n a 
Arity n => VectorN Vec n a 
(Arity n, Prim a) => VectorN Vec n a 
Unbox n a => VectorN Vec n a 
(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.

newtype Id a Source

Strict identity monad

Constructors

Id 

Fields

runID :: a
 

Instances