tup-functor-0.2.0.3: Homogeneous tuples

Safe HaskellNone

Data.Tup.Vec

Contents

Description

Homogeneous lists with the length encoded in the type.

This can be considered as a different implementation of Data.Tup.Tup (one which also scales for vectors/tuples longer than 9 elements)

Synopsis

The Vec type class

class (Functor v, Applicative v, Foldable v, Traversable v) => Vec v whereSource

Methods

vecSize :: v a -> IntSource

vecToList :: v a -> [a]Source

vecFromList :: [a] -> v aSource

vecUndef :: v a -> aSource

undefinedVec :: v aSource

Instances

Type abbreviations for short vectors

The constructor types

data Empty a Source

Constructors

Empty 

Instances

data Cons v a Source

Constructors

Cons a (v a) 

Instances

Functor v => Functor (Cons v) 
(Functor (Cons v), Applicative v) => Applicative (Cons v) 
Foldable v => Foldable (Cons v) 
(Functor (Cons v), Foldable (Cons v), Traversable v) => Traversable (Cons v) 
(Functor (Cons v), Applicative (Cons v), Foldable (Cons v), Traversable (Cons v), Vec v) => Vec (Cons v) 
(Vec (Cons u), Vec (Cons w), Vec u, Vec v, VecConcat u v w) => VecConcat (Cons u) v (Cons w) 
(Eq a, Eq (v a)) => Eq (Cons v a) 
(Num (Cons v a), Fractional a, Fractional (v a), Vec v) => Fractional (Cons v a) 
(Num a, Num (v a), Vec v) => Num (Cons v a) 
(Eq (Cons v a), Ord a, Ord (v a)) => Ord (Cons v a) 
(Show a, Vec v) => Show (Cons v a) 
(Monoid a, Monoid (v a), Vec v) => Monoid (Cons v a) 
(Storable a, Storable (v a), Vec v) => Storable (Cons v a) 

consUndefTail :: Vec v => Cons v a -> v aSource

Misc

maybeVecFromList :: Vec f => [a] -> Maybe (f a)Source

Safe version of vecFromList.

transposeVec :: (Vec f, Vec g) => f (g a) -> g (f a)Source

Transpose a Vec of Vecs.

Concatenation

maybeVecConcat :: (Vec f, Vec g, Vec h) => f a -> g a -> Maybe (h a)Source

safe concatenation

unsafeVecConcat :: (Vec f, Vec g, Vec h) => f a -> g a -> h aSource

unsafe concatenation

class (Vec u, Vec v, Vec w) => VecConcat u v w | u v -> w whereSource

concatenation with type class

Methods

vecConcat :: u a -> v a -> w aSource

Instances

(Vec Empty, Vec v) => VecConcat Empty v v 
(Vec (Cons u), Vec (Cons w), Vec u, Vec v, VecConcat u v w) => VecConcat (Cons u) v (Cons w) 

Zipping

zipVecWith :: Applicative f => (a -> b -> c) -> f a -> f b -> f cSource

zipVecWith3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f dSource

zipVecWith4 :: Applicative f => (a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f eSource

zipVec :: Applicative f => f a -> f b -> f (a, b)Source

zipVec3 :: Applicative f => f a -> f b -> f c -> f (a, b, c)Source

zipVec4 :: Applicative f => f a -> f b -> f c -> f d -> f (a, b, c, d)Source

Short constructor functions

vec1 :: a -> Vec1 aSource

vec2 :: a -> a -> Vec2 aSource

vec3 :: a -> a -> a -> Vec3 aSource

vec4 :: a -> a -> a -> a -> Vec4 aSource

vec5 :: a -> a -> a -> a -> a -> Vec5 aSource

vec6 :: a -> a -> a -> a -> a -> a -> Vec6 aSource

vec7 :: a -> a -> a -> a -> a -> a -> a -> Vec7 aSource

vec8 :: a -> a -> a -> a -> a -> a -> a -> a -> Vec8 aSource

vec9 :: a -> a -> a -> a -> a -> a -> a -> a -> a -> Vec9 aSource

"veccing"

vecVec :: Applicative f => f a -> f a -> f (Vec2 a)Source

vecVec3 :: Applicative f => f a -> f a -> f a -> f (Vec3 a)Source

vecVec4 :: Applicative f => f a -> f a -> f a -> f a -> f (Vec4 a)Source

vecVec5 :: Applicative f => f a -> f a -> f a -> f a -> f a -> f (Vec5 a)Source