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

Safe HaskellNone
LanguageHaskell98

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

Arity n => Index Z (S n) Source # 

Methods

getF :: Z -> Fun (S n) a a Source #

putF :: Z -> a -> Fun (S n) a r -> Fun (S n) a r Source #

lensF :: Functor f => Z -> (a -> f a) -> Fun (S n) a r -> Fun (S n) a (f r) Source #

Arity n => Arity (S n) Source # 

Methods

accum :: (forall k. t (S k) -> a -> t k) -> (t Z -> b) -> t (S n) -> Fun (S n) a b Source #

applyFun :: (forall k. t (S k) -> (a, t k)) -> t (S n) -> Fn (S n) a b -> (b, t Z) Source #

applyFunM :: Monad m => (forall k. t (S k) -> m (a, t k)) -> t (S n) -> m (ContVec (S n) a, t Z) Source #

arity :: S n -> Int Source #

reverseF :: Fun (S n) a b -> Fun (S n) a b Source #

uncurryMany :: Fun (Add (S n) k) a b -> Fun (S n) a (Fun k a b) Source #

gunfoldF :: Data a => (forall b x. Data b => c (b -> x) -> c x) -> T_gunfold c r a (S n) -> c r Source #

(NatIso k ((-) n 1), (~) * (ToPeano ((-) n 1)) k, (~) * (ToPeano n) (S k), (~) Nat n ((+) 1 ((-) n 1))) => NatIso (S k) n Source # 
Index k n => Index (S k) (S n) Source # 

Methods

getF :: S k -> Fun (S n) a a Source #

putF :: S k -> a -> Fun (S n) a r -> Fun (S n) a r Source #

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

type Add (S n) k Source # 
type Add (S n) k = S (Add n k)
type Fn (S n) a b Source # 
type Fn (S n) a b = a -> Fn n a b

data Z Source #

Type level zero

Instances

Arity Z Source # 

Methods

accum :: (forall k. t (S k) -> a -> t k) -> (t Z -> b) -> t Z -> Fun Z a b Source #

applyFun :: (forall k. t (S k) -> (a, t k)) -> t Z -> Fn Z a b -> (b, t Z) Source #

applyFunM :: Monad m => (forall k. t (S k) -> m (a, t k)) -> t Z -> m (ContVec Z a, t Z) Source #

arity :: Z -> Int Source #

reverseF :: Fun Z a b -> Fun Z a b Source #

uncurryMany :: Fun (Add Z k) a b -> Fun Z a (Fun k a b) Source #

gunfoldF :: Data a => (forall b x. Data b => c (b -> x) -> c x) -> T_gunfold c r a Z -> c r Source #

NatIso Z 0 Source # 
Arity n => Index Z (S n) Source # 

Methods

getF :: Z -> Fun (S n) a a Source #

putF :: Z -> a -> Fun (S n) a r -> Fun (S n) a r Source #

lensF :: Functor f => Z -> (a -> f a) -> Fun (S n) a r -> Fun (S n) a (f r) Source #

type Add Z n Source # 
type Add Z n = n
type Fn Z a b Source # 
type Fn Z a b = b

type family Add n m :: * Source #

Type family for sum of unary natural numbers.

Instances

type Add Z n Source # 
type Add Z n = n
type Add (S n) k Source # 
type Add (S n) k = S (Add n k)

Isomorphism between Peano number and Nats

It's only become possible to define isomorphism between Peano number and built-in Nat number in GHC 7.8. It's however impossible to define their properties inductively. So Peano number are used everywhere.

class (ToNat a ~ b, ToPeano b ~ a) => NatIso a b Source #

Isomorphism between two representations of natural numbers

Instances

NatIso Z 0 Source # 
(NatIso k ((-) n 1), (~) * (ToPeano ((-) n 1)) k, (~) * (ToPeano n) (S k), (~) Nat n ((+) 1 ((-) n 1))) => NatIso (S k) n Source # 

type family ToPeano (b :: Nat) :: * where ... Source #

Convert Nat number to Peano represenation

Equations

ToPeano 0 = Z 
ToPeano n = S (ToPeano (n - 1)) 

type family ToNat (a :: *) :: Nat where ... Source #

Convert Peano number to Nat

Equations

ToNat Z = 0 
ToNat (S k) = 1 + ToNat k 

Synonyms for small numerals

type N1 = S Z Source #

type N2 = S N1 Source #

type N3 = S N2 Source #

type N4 = S N3 Source #

type N5 = S N4 Source #

type N6 = S N5 Source #

N-ary functions

type family Fn n a b Source #

Type family for n-ary functions.

Instances

type Fn Z a b Source # 
type Fn Z a b = b
type Fn (S n) a b Source # 
type Fn (S n) a b = a -> Fn n a b

newtype Fun n a b Source #

Newtype wrapper which is used to make Fn injective. It's also a reader monad.

Constructors

Fun 

Fields

Instances

Arity n => Monad (Fun n a) Source # 

Methods

(>>=) :: Fun n a a -> (a -> Fun n a b) -> Fun n a b #

(>>) :: Fun n a a -> Fun n a b -> Fun n a b #

return :: a -> Fun n a a #

fail :: String -> Fun n a a #

Arity n => Functor (Fun n a) Source # 

Methods

fmap :: (a -> b) -> Fun n a a -> Fun n a b #

(<$) :: a -> Fun n a b -> Fun n a a #

Arity n => Applicative (Fun n a) Source # 

Methods

pure :: a -> Fun n a a #

(<*>) :: Fun n a (a -> b) -> Fun n a a -> Fun n a b #

(*>) :: Fun n a a -> Fun n a b -> Fun n a b #

(<*) :: Fun n a a -> Fun n a b -> Fun n a a #

class Arity n where Source #

Type class for handling n-ary functions.

Minimal complete definition

accum, applyFun, applyFunM, arity, reverseF, uncurryMany, gunfoldF

Methods

accum :: (forall k. t (S k) -> a -> t k) -> (t Z -> b) -> t n -> Fun n a b Source #

Left fold over n elements exposed as n-ary function. These elements are supplied as arguments to the function.

applyFun :: (forall k. t (S k) -> (a, t k)) -> t n -> Fn n a b -> (b, t Z) Source #

Apply all parameters to the function.

applyFunM :: Monad m => (forall k. t (S k) -> m (a, t k)) -> t n -> m (ContVec n a, t Z) Source #

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 -> Int Source #

Arity of function.

reverseF :: Fun n a b -> Fun n a b Source #

Reverse order of parameters.

uncurryMany :: Fun (Add n k) a b -> Fun n a (Fun k a b) Source #

Uncurry n first parameters of n-ary function

gunfoldF :: Data a => (forall b x. Data b => c (b -> x) -> c x) -> T_gunfold c r a n -> c r Source #

Worker function for gunfold

Instances

Arity Z Source # 

Methods

accum :: (forall k. t (S k) -> a -> t k) -> (t Z -> b) -> t Z -> Fun Z a b Source #

applyFun :: (forall k. t (S k) -> (a, t k)) -> t Z -> Fn Z a b -> (b, t Z) Source #

applyFunM :: Monad m => (forall k. t (S k) -> m (a, t k)) -> t Z -> m (ContVec Z a, t Z) Source #

arity :: Z -> Int Source #

reverseF :: Fun Z a b -> Fun Z a b Source #

uncurryMany :: Fun (Add Z k) a b -> Fun Z a (Fun k a b) Source #

gunfoldF :: Data a => (forall b x. Data b => c (b -> x) -> c x) -> T_gunfold c r a Z -> c r Source #

Arity n => Arity (S n) Source # 

Methods

accum :: (forall k. t (S k) -> a -> t k) -> (t Z -> b) -> t (S n) -> Fun (S n) a b Source #

applyFun :: (forall k. t (S k) -> (a, t k)) -> t (S n) -> Fn (S n) a b -> (b, t Z) Source #

applyFunM :: Monad m => (forall k. t (S k) -> m (a, t k)) -> t (S n) -> m (ContVec (S n) a, t Z) Source #

arity :: S n -> Int Source #

reverseF :: Fun (S n) a b -> Fun (S n) a b Source #

uncurryMany :: Fun (Add (S n) k) a b -> Fun (S n) a (Fun k a b) Source #

gunfoldF :: Data a => (forall b x. Data b => c (b -> x) -> c x) -> T_gunfold c r a (S n) -> c r Source #

apply Source #

Arguments

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

Get value to apply to function

-> t n

Initial value

-> ContVec n a

N-ary function

Apply all parameters to the function.

applyM Source #

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

constFun :: Fun n a b -> Fun (S n) a b Source #

Prepend ignored parameter to function

curryFirst :: Fun (S n) a b -> a -> Fun n a b Source #

Curry first parameter of n-ary function

uncurryFirst :: (a -> Fun n a b) -> Fun (S n) a b Source #

Uncurry first parameter of n-ary function

curryLast :: Arity n => Fun (S n) a b -> Fun n a (a -> b) Source #

Curry last parameter of n-ary function

curryMany :: forall n k a b. Arity n => Fun (Add n k) a b -> Fun n a (Fun k a b) Source #

Curry n first parameters of n-ary function

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

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

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

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

withFun :: (Fun n a b -> Fun n a b) -> Fun (S n) a b -> Fun (S n) a b Source #

Recursive step for the function

Vector type class

type family Dim (v :: * -> *) Source #

Size of vector expressed as type-level natural.

Instances

type Dim Complex Source # 
type Dim Complex = N2
type Dim Empty Source # 
type Dim Empty = Z
type Dim Only Source # 
type Dim Only = S Z
type Dim ((,) a) Source # 
type Dim ((,) a) = N2
type Dim (Proxy *) Source # 
type Dim (Proxy *) = Z
type Dim (ContVec n) Source # 
type Dim (ContVec n) = n
type Dim (VecList n) Source # 
type Dim (VecList n) = n
type Dim (Vec n) Source # 
type Dim (Vec n) = n
type Dim (Vec n) Source # 
type Dim (Vec n) = n
type Dim (Vec n) Source # 
type Dim (Vec n) = n
type Dim (Vec n) Source # 
type Dim (Vec n) = n
type Dim ((,,) a b) Source # 
type Dim ((,,) a b) = N3
type Dim ((,,,) a b c) Source # 
type Dim ((,,,) a b c) = N4
type Dim ((,,,,) a b c d) Source # 
type Dim ((,,,,) a b c d) = N5
type Dim ((,,,,,) a b c d e) Source # 
type Dim ((,,,,,) a b c d e) = N6
type Dim ((,,,,,,) a b c d e f) Source # 
type Dim ((,,,,,,) a b c d e f) = S N6

class Arity (Dim v) => Vector v a where Source #

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

Minimal complete definition

construct, inspect

Methods

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

N-ary function for creation of vectors.

inspect :: v a -> Fun (Dim v) a b -> b Source #

Deconstruction of vector.

basicIndex :: v a -> Int -> a Source #

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

Instances

RealFloat a => Vector Complex a Source # 

Methods

construct :: Fun (Dim Complex) a (Complex a) Source #

inspect :: Complex a -> Fun (Dim Complex) a b -> b Source #

basicIndex :: Complex a -> Int -> a Source #

Vector Empty a Source # 

Methods

construct :: Fun (Dim Empty) a (Empty a) Source #

inspect :: Empty a -> Fun (Dim Empty) a b -> b Source #

basicIndex :: Empty a -> Int -> a Source #

Vector Only a Source # 

Methods

construct :: Fun (Dim Only) a (Only a) Source #

inspect :: Only a -> Fun (Dim Only) a b -> b Source #

basicIndex :: Only a -> Int -> a Source #

(~) * b a => Vector ((,) b) a Source #

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.

Methods

construct :: Fun (Dim ((,) b)) a (b, a) Source #

inspect :: (b, a) -> Fun (Dim ((,) b)) a b -> b Source #

basicIndex :: (b, a) -> Int -> a Source #

Vector (Proxy *) a Source # 

Methods

construct :: Fun (Dim (Proxy *)) a (Proxy * a) Source #

inspect :: Proxy * a -> Fun (Dim (Proxy *)) a b -> b Source #

basicIndex :: Proxy * a -> Int -> a Source #

Arity n => Vector (ContVec n) a Source # 

Methods

construct :: Fun (Dim (ContVec n)) a (ContVec n a) Source #

inspect :: ContVec n a -> Fun (Dim (ContVec n)) a b -> b Source #

basicIndex :: ContVec n a -> Int -> a Source #

Arity n => Vector (VecList n) a Source # 

Methods

construct :: Fun (Dim (VecList n)) a (VecList n a) Source #

inspect :: VecList n a -> Fun (Dim (VecList n)) a b -> b Source #

basicIndex :: VecList n a -> Int -> a Source #

Arity n => Vector (Vec n) a Source # 

Methods

construct :: Fun (Dim (Vec n)) a (Vec n a) Source #

inspect :: Vec n a -> Fun (Dim (Vec n)) a b -> b Source #

basicIndex :: Vec n a -> Int -> a Source #

(Arity n, Prim a) => Vector (Vec n) a Source # 

Methods

construct :: Fun (Dim (Vec n)) a (Vec n a) Source #

inspect :: Vec n a -> Fun (Dim (Vec n)) a b -> b Source #

basicIndex :: Vec n a -> Int -> a Source #

(Arity n, Storable a) => Vector (Vec n) a Source # 

Methods

construct :: Fun (Dim (Vec n)) a (Vec n a) Source #

inspect :: Vec n a -> Fun (Dim (Vec n)) a b -> b Source #

basicIndex :: Vec n a -> Int -> a Source #

Unbox n a => Vector (Vec n) a Source # 

Methods

construct :: Fun (Dim (Vec n)) a (Vec n a) Source #

inspect :: Vec n a -> Fun (Dim (Vec n)) a b -> b Source #

basicIndex :: Vec n a -> Int -> a Source #

((~) * b a, (~) * c a) => Vector ((,,) b c) a Source # 

Methods

construct :: Fun (Dim ((,,) b c)) a (b, c, a) Source #

inspect :: (b, c, a) -> Fun (Dim ((,,) b c)) a b -> b Source #

basicIndex :: (b, c, a) -> Int -> a Source #

((~) * b a, (~) * c a, (~) * d a) => Vector ((,,,) b c d) a Source # 

Methods

construct :: Fun (Dim ((,,,) b c d)) a (b, c, d, a) Source #

inspect :: (b, c, d, a) -> Fun (Dim ((,,,) b c d)) a b -> b Source #

basicIndex :: (b, c, d, a) -> Int -> a Source #

((~) * b a, (~) * c a, (~) * d a, (~) * e a) => Vector ((,,,,) b c d e) a Source # 

Methods

construct :: Fun (Dim ((,,,,) b c d e)) a (b, c, d, e, a) Source #

inspect :: (b, c, d, e, a) -> Fun (Dim ((,,,,) b c d e)) a b -> b Source #

basicIndex :: (b, c, d, e, a) -> Int -> a Source #

((~) * b a, (~) * c a, (~) * d a, (~) * e a, (~) * f a) => Vector ((,,,,,) b c d e f) a Source # 

Methods

construct :: Fun (Dim ((,,,,,) b c d e f)) a (b, c, d, e, f, a) Source #

inspect :: (b, c, d, e, f, a) -> Fun (Dim ((,,,,,) b c d e f)) a b -> b Source #

basicIndex :: (b, c, d, e, f, a) -> Int -> a Source #

((~) * b a, (~) * c a, (~) * d a, (~) * e a, (~) * f a, (~) * g a) => Vector ((,,,,,,) b c d e f g) a Source # 

Methods

construct :: Fun (Dim ((,,,,,,) b c d e f g)) a (b, c, d, e, f, g, a) Source #

inspect :: (b, c, d, e, f, g, a) -> Fun (Dim ((,,,,,,) b c d e f g)) a b -> b Source #

basicIndex :: (b, c, d, e, f, g, a) -> Int -> a Source #

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

length :: forall v a. Arity (Dim v) => v a -> Int Source #

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

class Index k n where Source #

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

Minimal complete definition

getF, putF, lensF

Methods

getF :: k -> Fun n a a Source #

putF :: k -> a -> Fun n a r -> Fun n a r Source #

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

Instances

Arity n => Index Z (S n) Source # 

Methods

getF :: Z -> Fun (S n) a a Source #

putF :: Z -> a -> Fun (S n) a r -> Fun (S n) a r Source #

lensF :: Functor f => Z -> (a -> f a) -> Fun (S n) a r -> Fun (S n) a (f r) Source #

Index k n => Index (S k) (S n) Source # 

Methods

getF :: S k -> Fun (S n) a a Source #

putF :: S k -> a -> Fun (S n) a r -> Fun (S n) a r Source #

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

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 Source # 
Arity n => Make n a (ContVec n a) Source # 

Methods

make :: (ContVec Z a -> ContVec n a) -> ContVec n a

Arity n => Functor (ContVec n) Source # 

Methods

fmap :: (a -> b) -> ContVec n a -> ContVec n b #

(<$) :: a -> ContVec n b -> ContVec n a #

Arity n => Applicative (ContVec n) Source # 

Methods

pure :: a -> ContVec n a #

(<*>) :: ContVec n (a -> b) -> ContVec n a -> ContVec n b #

(*>) :: ContVec n a -> ContVec n b -> ContVec n b #

(<*) :: ContVec n a -> ContVec n b -> ContVec n a #

Arity n => Foldable (ContVec n) Source # 

Methods

fold :: Monoid m => ContVec n m -> m #

foldMap :: Monoid m => (a -> m) -> ContVec n a -> m #

foldr :: (a -> b -> b) -> b -> ContVec n a -> b #

foldr' :: (a -> b -> b) -> b -> ContVec n a -> b #

foldl :: (b -> a -> b) -> b -> ContVec n a -> b #

foldl' :: (b -> a -> b) -> b -> ContVec n a -> b #

foldr1 :: (a -> a -> a) -> ContVec n a -> a #

foldl1 :: (a -> a -> a) -> ContVec n a -> a #

toList :: ContVec n a -> [a] #

null :: ContVec n a -> Bool #

length :: ContVec n a -> Int #

elem :: Eq a => a -> ContVec n a -> Bool #

maximum :: Ord a => ContVec n a -> a #

minimum :: Ord a => ContVec n a -> a #

sum :: Num a => ContVec n a -> a #

product :: Num a => ContVec n a -> a #

Arity n => Traversable (ContVec n) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ContVec n a -> f (ContVec n b) #

sequenceA :: Applicative f => ContVec n (f a) -> f (ContVec n a) #

mapM :: Monad m => (a -> m b) -> ContVec n a -> m (ContVec n b) #

sequence :: Monad m => ContVec n (m a) -> m (ContVec n a) #

Arity n => Vector (ContVec n) a Source # 

Methods

construct :: Fun (Dim (ContVec n)) a (ContVec n a) Source #

inspect :: ContVec n a -> Fun (Dim (ContVec n)) a b -> b Source #

basicIndex :: ContVec n a -> Int -> a Source #

type Dim (ContVec n) Source # 
type Dim (ContVec n) = n

Construction of ContVec

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

Convert regular vector to continuation based one.

fromList :: Arity n => [a] -> ContVec n a Source #

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 a Source #

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 :: Arity n => a -> ContVec n a Source #

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

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

Execute monadic action for every element of vector.

generate :: Arity n => (Int -> a) -> ContVec n a Source #

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

generateM :: (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 :: Arity n => (b -> (a, b)) -> b -> ContVec n a Source #

Unfold vector.

basis :: (Num a, Arity n) => Int -> ContVec n a Source #

Unit vector along Nth axis.

Constructors

empty :: ContVec Z a Source #

Create empty vector.

cons :: a -> ContVec n a -> ContVec (S n) a Source #

O(1) Prepend element to vector

consV :: ContVec (S Z) a -> ContVec n a -> ContVec (S n) a Source #

Prepend single element vector to another vector.

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

O(1) Append element to vector

concat :: (Arity n, Arity k, Arity (Add n k)) => ContVec n a -> ContVec k a -> ContVec (Add n k) a Source #

Concatenate vector

mk1 :: a -> ContVec N1 a Source #

mk2 :: a -> a -> ContVec N2 a Source #

mk3 :: a -> a -> a -> ContVec N3 a Source #

mk4 :: a -> a -> a -> a -> ContVec N4 a Source #

mk5 :: a -> a -> a -> a -> a -> ContVec N5 a Source #

Transformations

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

Map over vector. Synonym for fmap

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

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.

scanl :: Arity n => (b -> a -> b) -> b -> ContVec n a -> ContVec (S n) b Source #

Left scan over vector

scanl1 :: Arity n => (a -> a -> a) -> ContVec n a -> ContVec n a Source #

Left scan over vector

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 :: (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 :: (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 a Source #

O(1) Tail of vector.

reverse :: Arity n => ContVec n a -> ContVec n a Source #

Reverse order of elements in the vector

Zips

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

Zip two vector together using function.

zipWith3 :: Arity n => (a -> b -> c -> d) -> ContVec n a -> ContVec n b -> ContVec n c -> ContVec n d Source #

Zip three vectors together

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

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

izipWith3 :: Arity n => (Int -> a -> b -> c -> d) -> ContVec n a -> ContVec n b -> ContVec n c -> ContVec n d Source #

Zip three vectors together

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.

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

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..

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

Running ContVec

runContVec :: Fun n a r -> ContVec n a -> r Source #

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

Getters

head :: Arity (S n) => ContVec (S n) a -> a Source #

Finalizer function for getting head of the vector.

index :: Arity n => Int -> ContVec n a -> a Source #

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 a Source #

Convert continuation to the vector.

Folds

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

Left fold over continuation vector.

foldl1 :: Arity (S n) => (a -> a -> a) -> ContVec (S n) a -> a Source #

Left fold.

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

Right fold over continuation vector

ifoldl :: Arity n => (b -> Int -> a -> b) -> b -> ContVec n a -> b Source #

Left fold over continuation vector.

ifoldr :: Arity n => (Int -> a -> b -> b) -> b -> ContVec n a -> b Source #

Right fold over continuation vector

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

Monadic left fold over continuation vector.

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

Monadic left fold over continuation vector.

Special folds

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

Sum all elements in the vector.

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

Minimal element of vector.

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

Maximal element of vector.

and :: Arity n => ContVec n Bool -> Bool Source #

Conjunction of elements of a vector.

or :: Arity n => ContVec n Bool -> Bool Source #

Disjunction of all elements of a vector.

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

Determines whether all elements of vector satisfy predicate.

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

Determines whether any of element of vector satisfy predicate.

find :: Arity n => (a -> Bool) -> ContVec n a -> Maybe a Source #

The find function takes a predicate and a vector and returns the leftmost element of the vector matching the predicate, or Nothing if there is no such element.

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.