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

Safe HaskellNone

Data.Vector.Fixed.Cont

Contents

Description

API for Church-encoded vectors. Implementation of function from Data.Vector.Fixed module uses these function internally in order to provide shortcut fusion.

Synopsis

Type-level numbers

data S n Source

Successor of n

Instances

Typeable1 S 
Arity n => Index Z (S n) 
Arity n => Arity (S n) 
Index k n => Index (S k) (S n) 

data Z Source

Type level zero

Instances

Typeable Z 
Arity Z 
Arity n => Index Z (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. It's also a reader monad.

Constructors

Fun 

Fields

unFun :: Fn n a b
 

Instances

Arity n => Monad (Fun n a) 
Arity n => Functor (Fun n a) 
Arity n => Applicative (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. These elements are supplied as arguments to the function.

applyFunSource

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, t Z) 

Apply all parameters to the function.

applyFunMSource

Arguments

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

Get value to apply to function

-> t n

Initial value

-> m (ContVec n a, t Z) 

Apply all parameters to the function using monadic actions. Note that for identity monad it's same as applyFun. Ignoring newtypes:

 forall b. Fn n a b -> b  ~ ContVecn n a

arity :: n -> IntSource

Arity of function.

reverseF :: Fun n a b -> Fun n a bSource

Reverse order of parameters.

gunfoldF :: (Arity n, Data a) => (forall b x. Data b => c (b -> x) -> c x) -> T_gunfold c r a n -> c rSource

Worker function for gunfold

Instances

Arity Z 
Arity n => Arity (S n) 

applySource

Arguments

:: Arity n 
=> (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, Arity n) 
=> (forall k. t (S k) -> m (a, t k))

Get value to apply to function

-> t n

Initial value

-> m (ContVec n a) 

Apply all parameters to the function using monadic actions.

Combinators

apFun :: Fun (S n) a b -> a -> Fun n a bSource

Apply single parameter to function

apLast :: Arity n => Fun (S n) a b -> a -> Fun n a bSource

Apply last parameter to function. Unlike apFun we need to traverse all parameters but last hence Arity constraint.

constFun :: Fun n a b -> Fun (S n) a bSource

Add one parameter to function which is ignored.

hideLast :: forall n a b. Arity n => Fun (S n) a b -> Fun n a (a -> b)Source

Move last parameter into function result

shuffleFun :: forall n a b r. Arity n => (b -> Fun n a r) -> Fun n a (b -> r)Source

Move function parameter to the result of N-ary function.

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 Empty a 
Vector Only a 
~ * b a => Vector ((,) b) a

Note this instance (and other instances for tuples) is essentially monomorphic in element type. Vector type v of 2 element tuple (Int,Int) is (,) Int so it will only work with elements of type Int.

Arity n => Vector (ContVec n) 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 ContVec n a 
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.

class Index k n whereSource

Type class for indexing of vector when index value is known at compile time.

Methods

getF :: k -> Fun n a aSource

lensF :: Functor f => k -> (a -> f a) -> Fun n a r -> Fun n a (f r)Source

Instances

Arity n => Index Z (S n) 
Index k n => Index (S k) (S n) 

Vector as continuation

newtype ContVec n a Source

Vector represented as continuation. Alternative wording: it's Church encoded N-element vector.

Constructors

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

Instances

Arity n => VectorN ContVec n a 
Arity n => Make n a (ContVec n a) 
Arity n => Functor (ContVec n) 
Arity n => Applicative (ContVec n) 
Arity n => Foldable (ContVec n) 
Arity n => Traversable (ContVec n) 
Arity n => Vector (ContVec n) a 

Construction of ContVec

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

Convert regular vector to continuation based one.

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

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

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

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

fromListM :: forall n a. Arity n => [a] -> Maybe (ContVec n a)Source

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

toList :: Arity n => ContVec n a -> [a]Source

Convert vector to the list

replicate :: forall n a. Arity n => a -> ContVec n aSource

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

replicateM :: forall m n a. (Arity n, Monad m) => m a -> m (ContVec n a)Source

Execute monadic action for every element of vector.

generate :: forall n a. Arity n => (Int -> a) -> ContVec 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) -> m (ContVec n a)Source

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

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

Unfold vector.

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

Unit vector along Nth axis.

Constructors

empty :: ContVec Z aSource

Create empty vector.

cons :: a -> ContVec n a -> ContVec (S n) aSource

O(1) Prepend element to vector

consV :: forall n a. ContVec (S Z) a -> ContVec n a -> ContVec (S n) aSource

Prepend single element to vector.

snoc :: Arity n => a -> ContVec n a -> ContVec (S n) aSource

O(1) Append element to vector

mk1 :: a -> ContVec N1 aSource

mk2 :: a -> a -> ContVec N2 aSource

mk3 :: a -> a -> a -> ContVec N3 aSource

mk4 :: a -> a -> a -> a -> ContVec N4 aSource

mk5 :: a -> a -> a -> a -> a -> ContVec N5 aSource

Transformations

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

Map over vector. Synonym for fmap

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

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

mapM :: (Arity n, Monad m) => (a -> m b) -> ContVec n a -> m (ContVec n b)Source

Monadic map over vector.

imapM :: (Arity n, Monad m) => (Int -> a -> m b) -> ContVec n a -> m (ContVec n b)Source

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

mapM_ :: (Arity n, Monad m) => (a -> m b) -> ContVec n a -> m ()Source

Apply monadic action to each element of vector and ignore result.

imapM_ :: (Arity n, Monad m) => (Int -> a -> m b) -> ContVec n a -> m ()Source

Apply monadic action to each element of vector and its index and ignore result.

sequence :: (Arity n, Monad m) => ContVec n (m a) -> m (ContVec n a)Source

Evaluate every action in the vector from left to right.

sequence_ :: (Arity n, Monad m) => ContVec n (m a) -> m ()Source

Evaluate every action in the vector from left to right and ignore result.

distribute :: forall f n a. (Functor f, Arity n) => f (ContVec n a) -> ContVec n (f a)Source

The dual of sequenceA

collect :: (Functor f, Arity n) => (a -> ContVec n b) -> f a -> ContVec n (f b)Source

distributeM :: forall m n a. (Monad m, Arity n) => m (ContVec n a) -> ContVec n (m a)Source

The dual of sequence

collectM :: (Monad m, Arity n) => (a -> ContVec n b) -> m a -> ContVec n (m b)Source

tail :: ContVec (S n) a -> ContVec n aSource

O(1) Tail of vector.

reverse :: Arity n => ContVec n a -> ContVec n aSource

Reverse order of elements in the vector

Zips

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

Zip two vector together using function.

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

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

zipWithM :: (Arity n, Monad m) => (a -> b -> m c) -> ContVec n a -> ContVec n b -> m (ContVec n c)Source

Zip two vector together using monadic function.

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

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

Running ContVec

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

Run continuation vector. It's same as inspect but with arguments flipped.

Getters

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

Finalizer function for getting head of the vector.

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

O(n) Get value at specified index.

element :: (Arity n, Functor f) => Int -> (a -> f a) -> ContVec n a -> f (ContVec n a)Source

Twan van Laarhoven lens for continuation based vector

elementTy :: (Arity n, Index k n, Functor f) => k -> (a -> f a) -> ContVec n a -> f (ContVec n a)Source

Twan van Laarhoven's lens for element of vector with statically known index.

Vector construction

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

Convert continuation to the vector.

Folds

foldl :: Arity n => (b -> a -> b) -> b -> ContVec n a -> bSource

Left fold over continuation vector.

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

Left fold.

foldr :: Arity n => (a -> b -> b) -> b -> ContVec n a -> bSource

Right fold over continuation vector

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

Left fold over continuation vector.

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

Right fold over continuation vector

foldM :: (Arity n, Monad m) => (b -> a -> m b) -> b -> ContVec n a -> m bSource

Monadic left fold over continuation vector.

ifoldM :: (Arity n, Monad m) => (b -> Int -> a -> m b) -> b -> ContVec n a -> m bSource

Monadic left fold over continuation vector.

Special folds

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

Sum all elements in the vector.

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

Minimal element of vector.

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

Maximal element of vector.

and :: Arity n => ContVec n Bool -> BoolSource

Conjunction of elements of a vector.

or :: Arity n => ContVec n Bool -> BoolSource

Disjunction of all elements of a vector.

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

Determines whether all elements of vector satisfy predicate.

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

Determines whether any of element of vector satisfy predicate.

Data.Data.Data

gfoldl :: forall c v a. (Vector v a, Data a) => (forall x y. Data x => c (x -> y) -> x -> c y) -> (forall x. x -> c x) -> v a -> c (v a)Source

Generic gfoldl which could work with any vector.

gunfold :: forall con c v a. (Vector v a, Data a) => (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> con -> c (v a)Source

Generic gunfoldl which could work with any vector. Since vector can only have one constructor argument for constructor is ignored.