fixed-vector-0.4.2.0: Generic vectors with statically known size.

Safe HaskellNone

Data.Vector.Fixed.Cont

Contents

Description

Continuations-based API

Synopsis

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. Instance should provide two functions: one to create vector and another for vector deconstruction. They must obey following law:

 inspect v construct = v

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.

basicIndex :: v a -> Int -> aSource

Optional more efficient implementation of indexing. Shouldn't be used directly, use ! instead.

Instances

RealFloat a => Vector Complex a 
Vector Only 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 
(~ * b a, ~ * c a, ~ * d a, ~ * e a, ~ * f a) => Vector ((,,,,,) b c d e f) a 
(~ * b a, ~ * c a, ~ * d a, ~ * e a, ~ * f a, ~ * g a) => Vector ((,,,,,,) b c d e f g) 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.

Vector as continuation

newtype ContVecT m n a Source

Vector represented as continuation.

Constructors

ContVecT (forall r. Fun n a (m r) -> m r) 

Instances

Arity n => Functor (ContVecT m n) 
Arity n => Applicative (ContVecT m n) 

type ContVec = ContVecT IdSource

Vector as continuation without monadic context.

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

Construction of ContVec

cvec :: (Vector v a, Dim v ~ n, Monad m) => v a -> ContVecT m n aSource

Convert regular vector to continuation

empty :: ContVecT m Z aSource

Create empty vector.

fromList :: forall m n a. Arity n => [a] -> ContVecT m n aSource

Convert list to continuation-based vector. Will throw error if list is shorter than resulting vector.

fromList' :: forall m n a. Arity n => [a] -> ContVecT m n aSource

Same as fromList bu throws error is list doesn't have same length as vector.

fromListM :: forall n a. Arity n => [a] -> ContVecT Maybe n aSource

Convert list to continuation-based vector. Will fail with Nothing if list doesn't have right length.

replicate :: forall m n a. Arity n => a -> ContVecT m n aSource

Execute monadic action for every element of vector. Synonym for pure.

replicateM :: forall m n a. (Arity n, Monad m) => m a -> ContVecT m n aSource

Execute monadic action for every element of vector.

generate :: forall m n a. Arity n => (Int -> a) -> ContVecT m n aSource

Generate vector from function which maps element's index to its value.

generateM :: forall m n a. (Monad m, Arity n) => (Int -> m a) -> ContVecT m n aSource

Generate vector from monadic function which maps element's index to its value.

unfoldr :: forall m n b a. Arity n => (b -> (a, b)) -> b -> ContVecT m n aSource

Unfold vector.

basis :: forall m n a. (Num a, Arity n) => Int -> ContVecT m n aSource

Unit vector along Nth axis.

Constructors

mk1 :: a -> ContVecT m N1 aSource

mk2 :: a -> a -> ContVecT m N2 aSource

mk3 :: a -> a -> a -> ContVecT m N3 aSource

mk4 :: a -> a -> a -> a -> ContVecT m N4 aSource

mk5 :: a -> a -> a -> a -> a -> ContVecT m N5 aSource

Transformations

map :: Arity n => (a -> b) -> ContVecT m n a -> ContVecT m n bSource

Map over vector. Synonym for fmap

imap :: Arity n => (Int -> a -> b) -> ContVecT m n a -> ContVecT m n bSource

Apply function to every element of the vector and its index.

mapM :: (Arity n, Monad m) => (a -> m b) -> ContVecT m n a -> ContVecT m n bSource

Monadic map over vector.

imapM :: (Arity n, Monad m) => (Int -> a -> m b) -> ContVecT m n a -> ContVecT m n bSource

Apply monadic function to every element of the vector and its index.

tail :: ContVecT m (S n) a -> ContVecT m n aSource

O(1) Tail of vector.

cons :: a -> ContVecT m n a -> ContVecT m (S n) aSource

O(1) Prepend element to vector

changeMonadSource

Arguments

:: (Monad p, Arity n) 
=> (forall x. p x -> x)

Function to extract result from monad

-> ContVecT p n a 
-> ContVecT m n a 

Change monad type for the continuation vector.

Zips

zipWith :: Arity n => (a -> b -> c) -> ContVecT m n a -> ContVecT m n b -> ContVecT m n cSource

Zip two vector together using function.

izipWith :: Arity n => (Int -> a -> b -> c) -> ContVecT m n a -> ContVecT m n b -> ContVecT m n cSource

Zip two vector together using function which takes element index as well.

zipWithM :: (Arity n, Monad m) => (a -> b -> m c) -> ContVecT m n a -> ContVecT m n b -> ContVecT m n cSource

Zip two vector together using monadic function.

izipWithM :: (Arity n, Monad m) => (Int -> a -> b -> m c) -> ContVecT m n a -> ContVecT m n b -> ContVecT m n cSource

Zip two vector together using monadic function which takes element index as well..

Running ContVec

Only way to get result from continuation vector is to apply finalizer function to them using runContVecT, runContVecM or runContVec. Getters and folds are defined as such finalizer functions.

runContVecTSource

Arguments

:: (Monad m, Arity n) 
=> Fun n a r

finalizer function

-> ContVecT m n a

vector

-> m r 

Run continuation vector using non-monadic finalizer.

runContVecMSource

Arguments

:: Arity n 
=> Fun n a (m r)

finalizer function

-> ContVecT m n a

vector

-> m r 

Run continuation vector using monadic finalizer.

runContVec :: Arity n => Fun n a r -> ContVec n a -> rSource

Run continuation vector.

Getters

head :: forall n a. Arity (S n) => Fun (S n) a aSource

Finalizer function for getting head of the vector.

index :: forall n a. Arity n => Int -> Fun n a aSource

O(n) Get value at specified index.

Vector construction

vector :: (Vector v a, Dim v ~ n) => ContVec n a -> v aSource

Convert continuation to the vector.

vectorM :: (Vector v a, Dim v ~ n, Monad m) => ContVecT m n a -> m (v a)Source

Convert continuation to the vector.

Folds

foldl :: forall n a b. Arity n => (b -> a -> b) -> b -> Fun n a bSource

Left fold over continuation vector.

foldl1 :: forall n a. Arity (S n) => (a -> a -> a) -> Fun (S n) a aSource

Left fold.

foldr :: forall n a b. Arity n => (a -> b -> b) -> b -> Fun n a bSource

Right fold over continuation vector

ifoldl :: forall n a b. Arity n => (b -> Int -> a -> b) -> b -> Fun n a bSource

Left fold over continuation vector.

ifoldr :: forall n a b. Arity n => (Int -> a -> b -> b) -> b -> Fun n a bSource

Right fold over continuation vector

foldM :: forall n m a b. (Arity n, Monad m) => (b -> a -> m b) -> b -> Fun n a (m b)Source

Monadic left fold over continuation vector.

ifoldM :: forall n m a b. (Arity n, Monad m) => (b -> Int -> a -> m b) -> b -> Fun n a (m b)Source

Monadic left fold over continuation vector.

Special folds

sum :: (Num a, Arity n) => Fun n a aSource

Sum all elements in the vector.

minimum :: (Ord a, Arity (S n)) => Fun (S n) a aSource

Minimal element of vector.

maximum :: (Ord a, Arity (S n)) => Fun (S n) a aSource

Maximal element of vector.

and :: Arity n => Fun n Bool BoolSource

Conjunction of elements of a vector.

or :: Arity n => Fun n Bool BoolSource

Disjunction of all elements of a vector.

all :: Arity n => (a -> Bool) -> Fun n a BoolSource

Determines whether all elements of vector satisfy predicate.

any :: Arity n => (a -> Bool) -> Fun n a BoolSource

Determines whether any of element of vector satisfy predicate.