fixed-vector-hetero-0.2.0.0: Generic heterogeneous vectors

Safe HaskellNone

Data.Vector.HFixed

Contents

Description

Heterogeneous vectors.

Synopsis

HVector type classes

class Arity (Len xs) => Arity xs Source

Type class for dealing with N-ary function in generic way. Both accum and apply work with accumulator data types which are polymorphic. So it's only possible to write functions which rearrange elements in vector using plain ADT. It's possible to get around it by using GADT as accumulator (See ArityC and function which use it)

This is also somewhat a kitchen sink module. It contains witnesses which could be used to prove type equalities or to bring instance in scope.

Instances

Arity ([] *) 
Arity xs => Arity (: * x xs) 

class Arity xs => ArityC c xs Source

Declares that every type in list satisfy constraint c

Instances

ArityC c ([] *) 
(c x, ArityC c xs) => ArityC c (: * x xs) 

class Arity (Elems v) => HVector v whereSource

Type class for heterogeneous vectors. Instance should specify way to construct and deconstruct itself

Note that this type class is extremely generic. Almost any single constructor data type could be made instance. It could be monomorphic, it could be polymorphic in some or all fields it doesn't matter. Only law instance should obey is:

 inspect v construct = v

Default implementation which uses Generic is provided.

Associated Types

type Elems v :: [*]Source

Methods

construct :: Fun (Elems v) vSource

Function for constructing vector

inspect :: v -> Fun (Elems v) a -> aSource

Function for deconstruction of vector. It applies vector's elements to N-ary function.

Instances

HVector ()

Unit is empty heterogeneous vector

HVector (Complex a) 
Arity xs => HVector (ContVec xs) 
Arity xs => HVector (VecList xs) 
Arity xs => HVector (HVec xs) 
HVector (a, b) 
(Storable a, HomArity n a) => HVector (Vec n a) 
(Unbox n a, HomArity n a) => HVector (Vec n a) 
(Prim a, HomArity n a) => HVector (Vec n a) 
HomArity n a => HVector (Vec n a) 
(Arity (Wrap * * f xs), Arity xs) => HVector (HVecF xs f)

It's not possible to remove constrain Arity (Wrap f xs) because it's required by superclass and we cannot prove it for all f. witWrapped allow to generate proofs for terms

HVector (a, b, c) 
HVector (a, b, c, d) 
HVector (a, b, c, d, e) 
HVector (a, b, c, d, e, f) 
HVector (a, b, c, d, e, f, g) 

class Arity (ElemsF v) => HVectorF v whereSource

Type class for partially homogeneous vector where every element in the vector have same type constructor. Vector itself is parametrized by that constructor

Associated Types

type ElemsF v :: [*]Source

Elements of the vector without type constructors

Methods

inspectF :: v f -> TFun f (ElemsF v) a -> aSource

constructF :: TFun f (ElemsF v) (v f)Source

Instances

Arity xs => HVectorF (VecListF xs) 
Arity xs => HVectorF (HVecF xs) 
Arity xs => HVectorF (ContVecF * xs) 

type family Wrap f a :: [β]Source

Wrap every element of list into type constructor

data Proxy a Source

Constructors

Proxy 

Position based functions

convert :: (HVector v, HVector w, Elems v ~ Elems w) => v -> wSource

We can convert between any two vector which have same structure but different representations.

head :: (HVector v, Elems v ~ (a : as), Arity as) => v -> aSource

Head of the vector

tail :: (HVector v, HVector w, (a : Elems w) ~ Elems v) => v -> wSource

Tail of the vector

>>> case tail ('a',"aa",()) of x@(_,_) -> x
("aa",())

cons :: (HVector v, HVector w, Elems w ~ (a : Elems v)) => a -> v -> wSource

Prepend element to the list. Note that it changes type of vector so it either must be known from context of specified explicitly

concat :: (HVector v, HVector u, HVector w, Elems w ~ (Elems v ++ Elems u)) => v -> u -> wSource

Concatenate two vectors

Indexing

class Arity n => Index n xs Source

Indexing of vectors

Associated Types

type ValueAt n xs :: *Source

Type at position n

Instances

Arity xs => Index Z (: * x xs) 
Index n xs => Index (S n) (: * x xs) 

index :: (Index n (Elems v), HVector v) => v -> n -> ValueAt n (Elems v)Source

Index heterogeneous vector

set :: (Index n (Elems v), HVector v) => n -> ValueAt n (Elems v) -> v -> vSource

Set element in the vector

element :: (Index n (Elems v), ValueAt n (Elems v) ~ a, HVector v, Functor f) => n -> (a -> f a) -> v -> f vSource

Twan van Laarhoven's lens for i'th element.

elementCh :: (Index n (Elems v), a ~ ValueAt n (Elems v), HVector v, HVector w, Elems w ~ NewElems n (Elems v) b, Functor f) => n -> (a -> f b) -> v -> f wSource

Type changing Twan van Laarhoven's lens for i'th element.

Generic constructors

mk0 :: (HVector v, Elems v ~ `[]`) => vSource

mk1 :: (HVector v, Elems v ~ `[a]`) => a -> vSource

mk2 :: (HVector v, Elems v ~ `[a, b]`) => a -> b -> vSource

mk3 :: (HVector v, Elems v ~ `[a, b, c]`) => a -> b -> c -> vSource

mk4 :: (HVector v, Elems v ~ `[a, b, c, d]`) => a -> b -> c -> d -> vSource

mk5 :: (HVector v, Elems v ~ `[a, b, c, d, e]`) => a -> b -> c -> d -> e -> vSource

Folds and unfolds

fold :: HVector v => v -> Fn (Elems v) r -> rSource

Most generic form of fold which doesn't constrain elements id use of inspect. Or in more convenient form below:

>>> fold (12::Int,"Str") (\a s -> show a ++ s)
"12Str"

foldr :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall a. c a => a -> b -> b) -> b -> v -> bSource

Right fold over heterogeneous vector

foldl :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall a. c a => b -> a -> b) -> b -> v -> bSource

Left fold over heterogeneous vector

mapM_ :: (HVector v, ArityC c (Elems v), Monad m) => Proxy c -> (forall a. c a => a -> m ()) -> v -> m ()Source

Apply monadic action to every element in the vector

unfoldr :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall a. c a => b -> (a, b)) -> b -> vSource

Unfold vector.

Polymorphic values

replicate :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall x. c x => x) -> vSource

Replicate polymorphic value n times. Concrete instance for every element is determined by their respective types.

>>> import Data.Vector.HFixed as H
>>> H.replicate (Proxy :: Proxy Monoid) mempty :: ((),String)
((),"")

replicateM :: (HVector v, Monad m, ArityC c (Elems v)) => Proxy c -> (forall x. c x => m x) -> m vSource

Replicate monadic action n times.

>>> import Data.Vector.HFixed as H
>>> H.replicateM (Proxy :: Proxy Read) (fmap read getLine) :: IO (Int,Char)
> 12
> 'a'
(12,'a')

zipMono :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall a. c a => a -> a -> a) -> v -> v -> vSource

Zip two heterogeneous vectors

zipMonoF :: (HVectorF v, ArityC c (ElemsF v)) => Proxy c -> (forall a. c a => f a -> f a -> f a) -> v f -> v f -> v fSource

Zip two heterogeneous vectors

zipFold :: (HVector v, ArityC c (Elems v), Monoid m) => Proxy c -> (forall a. c a => a -> a -> m) -> v -> v -> mSource

monomorphize :: (HVector v, ArityC c (Elems v)) => Proxy c -> (forall a. c a => a -> x) -> v -> ContVec (Len (Elems v)) xSource

Convert heterogeneous vector to homogeneous

monomorphizeF :: (HVectorF v, ArityC c (ElemsF v)) => Proxy c -> (forall a. c a => f a -> x) -> v f -> ContVec (Len (ElemsF v)) xSource

Convert heterogeneous vector to homogeneous

Vector parametrized with type constructor

mapFunctor :: HVectorF v => (forall a. f a -> g a) -> v f -> v gSource

sequence :: (Monad m, HVectorF v, HVector w, ElemsF v ~ Elems w) => v m -> m wSource

Sequence effects for every element in the vector

sequenceA :: (Applicative f, HVectorF v, HVector w, ElemsF v ~ Elems w) => v f -> f wSource

Sequence effects for every element in the vector

sequenceF :: (Monad m, HVectorF v) => v (m `Compose` f) -> m (v f)Source

Sequence effects for every element in the vector

sequenceAF :: (Applicative f, HVectorF v) => v (f `Compose` g) -> f (v g)Source

Sequence effects for every element in the vector

wrap :: (HVector v, HVectorF w, Elems v ~ ElemsF w) => (forall a. a -> f a) -> v -> w fSource

Wrap every value in the vector into type constructor.

unwrap :: (HVectorF v, HVector w, ElemsF v ~ Elems w) => (forall a. f a -> a) -> v f -> wSource

Unwrap every value in the vector from the type constructor.

distribute :: (Functor f, HVector v, HVectorF w, Elems v ~ ElemsF w) => f v -> w fSource

Analog of distribute from Distributive type class.

distributeF :: (Functor f, HVectorF v) => f (v g) -> v (f `Compose` g)Source

Analog of distribute from Distributive type class.

Specialized operations

eq :: (HVector v, ArityC Eq (Elems v)) => v -> v -> BoolSource

Generic equality for heterogeneous vectors

compare :: (HVector v, ArityC Ord (Elems v)) => v -> v -> OrderingSource

Generic comparison for heterogeneous vectors

rnf :: (HVector v, ArityC NFData (Elems v)) => v -> ()Source

Reduce vector to normal form