type-combinators-0.1.2.1: A collection of data types for type-level programming

CopyrightCopyright (C) 2015 Kyle Carter
LicenseBSD3
MaintainerKyle Carter <kylcarte@indiana.edu>
Stabilityexperimental
PortabilityRankNTypes
Safe HaskellNone
LanguageHaskell2010

Data.Type.Product.Dual

Description

Type combinators for type-level lists, where we have many functors with a single index.

Synopsis

Documentation

data FProd fs :: k -> * where Source

Constructors

ØF :: FProd Ø a 
(:<<) :: !(f a) -> !(FProd fs a) -> FProd (f :< fs) a infixr 5 

Instances

Witness ØC ØC (FProd k (Ø (k -> *)) a) Source

An empty FProd is a no-op Witness.

(Known k f a, Known k (FProd k fs) a) => Known k (FProd k ((:<) (k -> *) f fs)) a Source 
Known k (FProd k (Ø (k -> *))) a Source 
ListC ((<$>) Constraint (* -> *) Functor fs) => Functor (FProd * fs) Source

If all f in fs are Functors, then FProd fs is a Functor.

ListC ((<$>) Constraint (* -> *) Foldable fs) => Foldable (FProd * fs) Source

If all f in fs are Foldables, then FProd fs is a Foldable.

(ListC ((<$>) Constraint (* -> *) Functor fs), ListC ((<$>) Constraint (* -> *) Foldable fs), ListC ((<$>) Constraint (* -> *) Traversable fs)) => Traversable (FProd * fs) Source

If all f in fs are Traversables, then FProd fs is a Traversable.

(Witness p q (f a), Witness s t (FProd k fs a)) => Witness (p, s) (q, t) (FProd k ((:<) (k -> *) f fs) a) Source

A non-empty FProd is a Witness if both its head and tail are Witnesses.

type WitnessC ØC ØC (FProd k (Ø (k -> *)) a) = ØC 
type KnownC k (FProd k ((:<) (k -> *) f fs)) a = (Known k f a, Known k (FProd k fs) a) Source 
type KnownC k (FProd k (Ø (k -> *))) a = ØC 
type WitnessC (p, s) (q, t) (FProd k ((:<) (k -> *) f fs) a) = (Witness p q (f a), Witness s t (FProd k fs a)) Source 

pattern (:>>) :: f a -> g a -> FProd k ((:) (k -> *) f ((:) (k -> *) g ([] (k -> *)))) a infix 6 Source

Construct a two element FProd. Since the precedence of (:>>) is higher than (:<<), we can conveniently write lists like:

>>> a :<< b :>> c

Which is identical to:

>>> a :<< b :<< c :<< Ø

onlyF :: f a -> FProd `[f]` a Source

Build a singleton FProd.

(>>:) :: FProd fs a -> f a -> FProd (fs >: f) a infixl 6 Source

snoc function. insert an element at the end of the FProd.

headF :: FProd (f :< fs) a -> f a Source

tailF :: FProd (f :< fs) a -> FProd fs a Source

initF :: FProd (f :< fs) a -> FProd (Init' f fs) a Source

Get all but the last element of a non-empty FProd.

lastF :: FProd (f :< fs) a -> Last' f fs a Source

Get the last element of a non-empty FProd.

reverseF :: FProd fs a -> FProd (Reverse fs) a Source

Reverse the elements of an FProd.

appendF :: FProd fs a -> FProd gs a -> FProd (fs ++ gs) a Source

Append two FProds.

onHeadF :: (f a -> g a) -> FProd (f :< fs) a -> FProd (g :< fs) a Source

Map over the head of a non-empty FProd.

onTailF :: (FProd fs a -> FProd gs a) -> FProd (f :< fs) a -> FProd (f :< gs) a Source

Map over the tail of a non-empty FProd.

uncurryF :: (f a -> FProd fs a -> r) -> FProd (f :< fs) a -> r Source

curryF :: (l ~ (f :< fs)) => (FProd l a -> r) -> f a -> FProd fs a -> r Source

indexF :: Index fs f -> FProd fs a -> f a Source

imapF :: (forall f. Index fs f -> f a -> f b) -> FProd fs a -> FProd fs b Source

Map over all elements of an FProd with access to the element's index.

ifoldMapF :: Monoid m => (forall f. Index fs f -> f a -> m) -> FProd fs a -> m Source

Fold over all elements of an FProd with access to the element's index.

itraverseF :: Applicative g => (forall f. Index fs f -> f a -> g (f b)) -> FProd fs a -> g (FProd fs b) Source

Traverse over all elements of an FProd with access to the element's index.