fixed-vector-0.7.0.3: 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) 
Arity n => Arity (S n) 
(NatIso k ((-) n 1), (~) * (ToPeano ((-) n 1)) k, (~) * (ToPeano n) (S k), (~) Nat n ((+) 1 ((-) n 1))) => NatIso (S k) n 
Index k n => Index (S k) (S n) 
Typeable (* -> *) S 
type Add (S n) k = S (Add n k) 
type Fn (S n) a b = a -> Fn n a b 

data Z Source

Type level zero

Instances

Arity Z 
Typeable * Z 
NatIso Z 0 
Arity n => Index Z (S n) 
type Add Z n = n 
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 = n 
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 
(NatIso k ((-) n 1), (~) * (ToPeano ((-) n 1)) k, (~) * (ToPeano n) (S k), (~) Nat n ((+) 1 ((-) n 1))) => NatIso (S k) n 

type family ToPeano b :: * Source

Convert Nat number to Peano represenation

Equations

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

type family ToNat a :: Nat 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 = b 
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

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

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

applyFun Source

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.

applyFunM Source

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

Arity of function.

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

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 r Source

Worker function for gunfold

witSum :: WitSum n k a b Source

Proof that `Fn (n+k) a b ~ Fn n a (Fn k a b)`

Instances

Arity Z 
Arity n => Arity (S n) 

apply Source

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.

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.

data WitSum n k a b where Source

Value that carry proof that `Fn (Add n k) a b ~ Fn n a (Fn k a b)`

Constructors

WitSum :: (Fn (Add n k) a b ~ Fn n a (Fn k a b)) => WitSum n k a b 

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 :: forall n a b. 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

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

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

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 = N2 
type Dim Empty = Z 
type Dim Only = S Z 
type Dim ((,) a) = N2 
type Dim (Proxy *) = Z 
type Dim (ContVec n) = n 
type Dim (VecList n) = n 
type Dim (Vec n) = n 
type Dim (Vec n) = n 
type Dim (Vec n) = n 
type Dim (Vec n) = n 
type Dim ((,,) a b) = N3 
type Dim ((,,,) a b c) = N4 
type Dim ((,,,,) a b c d) = N5 
type Dim ((,,,,,) a b c d e) = N6 
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 
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.

Vector (Proxy *) a 
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 -> 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.

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

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

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

Unfold vector.

basis :: forall n a. (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 :: forall n a. 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 :: 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 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.

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.

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 -> r Source

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

Getters

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

Finalizer function for getting head of the vector.

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

Left fold over continuation vector.

ifoldr :: forall n a b. 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.

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.