fixed-vector-1.2.1.0: Generic vectors with statically known size.
Safe HaskellNone
LanguageHaskell2010

Data.Vector.Fixed.Cont

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

Peano numbers. Since type level naturals don't support induction we have to convert type nats to Peano representation first and work with it,

Constructors

Z 
S PeanoNum 

type family Peano (n :: Nat) :: PeanoNum where ... Source #

Convert type level natural to Peano representation

Equations

Peano 0 = 'Z 
Peano n = 'S (Peano (n - 1)) 

type family Add (n :: PeanoNum) (m :: PeanoNum) :: PeanoNum where ... Source #

Type family for sum of unary natural numbers.

Equations

Add 'Z n = n 
Add ('S n) k = 'S (Add n k) 

N-ary functions

type family Fn (n :: PeanoNum) (a :: *) (b :: *) where ... Source #

Type family for n-ary functions. n is number of parameters of type a and b is result type.

Equations

Fn 'Z a b = b 
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

Instances details
ArityPeano n => Monad (Fun n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

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

return :: a0 -> Fun n a a0 #

ArityPeano n => Functor (Fun n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

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

ArityPeano n => Applicative (Fun n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

pure :: a0 -> Fun n a a0 #

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

liftA2 :: (a0 -> b -> c) -> Fun n a a0 -> Fun n a b -> Fun n a c #

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

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

type Arity n = (ArityPeano (Peano n), KnownNat n, Peano (n + 1) ~ 'S (Peano n)) Source #

Type class for type level number for which we can defined operations over N-ary functions.

class ArityPeano n where Source #

Type class for handling n-ary functions.

Methods

accum Source #

Arguments

:: (forall k. t ('S k) -> a -> t k)

Fold function

-> (t 'Z -> b)

Extract result of fold

-> t n

Initial value

-> Fun n a b

Reduction function

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

applyFun Source #

Arguments

:: (forall k. t ('S k) -> (a, t k))

Get value to apply to function

-> t n

Initial value

-> (CVecPeano n a, t 'Z) 

Apply all parameters to the function.

applyFunM Source #

Arguments

:: Applicative f 
=> (forall k. t ('S k) -> (f a, t k))

Get value to apply to function

-> t n

Initial value

-> (f (CVecPeano 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  ~ ContVec n a

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

Reverse order of parameters. It's implemented directly in type class since expressing it in terms of accum will require putting ArityPeano constraint on step funcion

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

Instances details
ArityPeano 'Z Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

applyFun :: (forall (k :: PeanoNum). t ('S k) -> (a, t k)) -> t 'Z -> (CVecPeano 'Z a, t 'Z) Source #

applyFunM :: Applicative f => (forall (k :: PeanoNum). t ('S k) -> (f a, t k)) -> t 'Z -> (f (CVecPeano 'Z a), t 'Z) Source #

reverseF :: Fun 'Z a b -> Fun 'Z 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 #

ArityPeano n => ArityPeano ('S n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

applyFun :: (forall (k :: PeanoNum). t ('S k) -> (a, t k)) -> t ('S n) -> (CVecPeano ('S n) a, t 'Z) Source #

applyFunM :: Applicative f => (forall (k :: PeanoNum). t ('S k) -> (f a, t k)) -> t ('S n) -> (f (CVecPeano ('S n) a), t 'Z) Source #

reverseF :: Fun ('S n) a b -> Fun ('S n) 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 #

arity :: KnownNat n => proxy n -> Int Source #

Arity of function.

apply Source #

Arguments

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

Get value to apply to function

-> t (Peano n)

Initial value

-> ContVec n a

N-ary function

Apply all parameters to the function.

applyM Source #

Arguments

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

Get value to apply to function

-> t (Peano n)

Initial value

-> f (ContVec n a) 

Apply all parameters to the function using applicative 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 :: ArityPeano 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. ArityPeano n => Fun (Add n k) a b -> Fun n a (Fun k a b) Source #

Curry n first parameters of n-ary function

apLast :: ArityPeano 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 :: ArityPeano 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 :: * -> *) :: Nat Source #

Size of vector expressed as type-level natural.

Instances

Instances details
type Dim Complex Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim Complex = 2
type Dim Identity Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim Identity = 1
type Dim Only Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim Only = 1
type Dim ((,) a) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,) a) = 2
type Dim (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim (Proxy :: Type -> Type) = 0
type Dim (ContVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim (ContVec n) = n
type Dim (Empty :: Type -> Type) Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim (Empty :: Type -> Type) = 0
type Dim (VecList n) Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim (VecList n) = n
type Dim (Vec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Boxed

type Dim (Vec n) = n
type Dim (Vec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Primitive

type Dim (Vec n) = n
type Dim (Vec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Storable

type Dim (Vec n) = n
type Dim (Vec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

type Dim (Vec n) = n
type Dim ((,,) a b) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,,) a b) = 3
type Dim ((,,,) a b c) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,,,) a b c) = 4
type Dim ((,,,,) a b c d) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,,,,) a b c d) = 5
type Dim ((,,,,,) a b c d e) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,,,,,) a b c d e) = 6
type Dim ((,,,,,,) a b c d e f) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,,,,,,) a b c d e f) = 7

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

For example instance for 2D vectors could be written as:

data V2 a = V2 a a

type instance V2 = 2
instance Vector V2 a where
  construct                = Fun V2
  inspect (V2 a b) (Fun f) = f a b

Minimal complete definition

construct, inspect

Methods

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

N-ary function for creation of vectors.

inspect :: v a -> Fun (Peano (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

Instances details
Vector Complex a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

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

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

Vector Identity a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Vector Only a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

inspect :: Only a -> Fun (Peano (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.

Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

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

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

Vector (Proxy :: Type -> Type) a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

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

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

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

Defined in Data.Vector.Fixed.Cont

Methods

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

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

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

Vector (Empty :: Type -> Type) a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

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

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

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

Defined in Data.Vector.Fixed

Methods

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

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

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

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

Defined in Data.Vector.Fixed.Boxed

Methods

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

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

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

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

Defined in Data.Vector.Fixed.Primitive

Methods

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

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

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

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

Defined in Data.Vector.Fixed.Storable

Methods

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

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

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

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

Defined in Data.Vector.Fixed.Unboxed

Methods

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

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

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

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

Defined in Data.Vector.Fixed.Cont

Methods

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

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

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

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

Defined in Data.Vector.Fixed.Cont

Methods

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

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

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

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

Defined in Data.Vector.Fixed.Cont

Methods

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

inspect :: (b, c, d, e, a) -> Fun (Peano (Dim ((,,,,) b c d e))) a b0 -> b0 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 # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

inspect :: (b, c, d, e, f, a) -> Fun (Peano (Dim ((,,,,,) b c d e f))) a b0 -> b0 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 # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

construct :: Fun (Peano (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 (Peano (Dim ((,,,,,,) b c d e f g))) a b0 -> b0 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

Instances details
Arity n => VectorN ContVec n a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Arity n => VectorN VecList n a Source # 
Instance details

Defined in Data.Vector.Fixed

Arity n => VectorN Vec n a Source # 
Instance details

Defined in Data.Vector.Fixed.Boxed

(Arity n, Prim a) => VectorN Vec n a Source # 
Instance details

Defined in Data.Vector.Fixed.Primitive

(Arity n, Storable a) => VectorN Vec n a Source # 
Instance details

Defined in Data.Vector.Fixed.Storable

Unbox n a => VectorN Vec n a Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

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

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

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 (Peano n) a r -> r) 

Instances

Instances details
Arity n => VectorN ContVec n a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Arity n => Functor (ContVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

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

Arity n => Applicative (ContVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

pure :: a -> ContVec n a #

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

liftA2 :: (a -> b -> c) -> ContVec n a -> ContVec n b -> ContVec n c #

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

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

Arity n => Foldable (ContVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

foldMap :: Monoid m => (a -> m) -> ContVec n a -> 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 # 
Instance details

Defined in Data.Vector.Fixed.Cont

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 # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

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

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

type Dim (ContVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim (ContVec n) = n

newtype CVecPeano n a Source #

Same as ContVec but its length is expressed as Peano number.

Constructors

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

consPeano :: a -> CVecPeano n a -> CVecPeano ('S n) a Source #

Cons values to the CVecPeano.

runContVec :: Fun (Peano n) a r -> ContVec n a -> r Source #

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

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, Applicative f) => f a -> f (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 :: (Applicative f, Arity n) => (Int -> f a) -> f (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 0 a Source #

Create empty vector.

cons :: Arity n => a -> ContVec n a -> ContVec (n + 1) a Source #

O(1) Prepend element to vector

consV :: Arity n => ContVec 1 a -> ContVec n a -> ContVec (n + 1) a Source #

Prepend single element vector to another vector.

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

O(1) Append element to vector

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

Concatenate vector

mk1 :: a -> ContVec 1 a Source #

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

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

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

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

mk6 :: a -> a -> a -> a -> a -> a -> ContVec 6 a Source #

mk7 :: a -> a -> a -> a -> a -> a -> a -> ContVec 7 a Source #

mk8 :: a -> a -> a -> a -> a -> a -> a -> a -> ContVec 8 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, Applicative f) => (a -> f b) -> ContVec n a -> f (ContVec n b) Source #

Effectful map over vector.

imapM :: (Arity n, Applicative f) => (Int -> a -> f b) -> ContVec n a -> f (ContVec n b) Source #

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

mapM_ :: (Arity n, Applicative f) => (a -> f b) -> ContVec n a -> f () Source #

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

imapM_ :: (Arity n, Applicative f) => (Int -> a -> f b) -> ContVec n a -> f () 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 (n + 1) 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, Applicative f) => ContVec n (f a) -> f (ContVec n a) Source #

Evaluate every action in the vector from left to right.

sequence_ :: (Arity n, Applicative f) => ContVec n (f a) -> f () 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 #

tail :: Arity n => ContVec (n + 1) 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, Applicative f) => (a -> b -> f c) -> ContVec n a -> ContVec n b -> f (ContVec n c) Source #

Zip two vector together using monadic function.

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

izipWithM :: (Arity n, Applicative f) => (Int -> a -> b -> f c) -> ContVec n a -> ContVec n b -> f (ContVec n c) Source #

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

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

Getters

head :: (Arity n, 1 <= n) => ContVec 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

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

Minimal element of vector.

maximum :: (Ord a, Arity n, 1 <= n) => ContVec 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.