Copyright | Copyright (C) 2015 Kyle Carter |
---|---|
License | BSD3 |
Maintainer | Kyle Carter <kylcarte@indiana.edu> |
Stability | experimental |
Portability | RankNTypes |
Safe Haskell | None |
Language | Haskell2010 |
Type combinators for type-level lists, where we have many functors with a single index.
- data FProd fs :: k -> * where
- pattern (:>>) :: forall k f a g. f a -> g a -> FProd k ((:) (k -> *) f ((:) (k -> *) g ([] (k -> *)))) a
- onlyF :: f a -> FProd '[f] a
- (>>:) :: FProd fs a -> f a -> FProd (fs >: f) a
- headF :: FProd (f :< fs) a -> f a
- tailF :: FProd (f :< fs) a -> FProd fs a
- initF :: FProd (f :< fs) a -> FProd (Init' f fs) a
- lastF :: FProd (f :< fs) a -> Last' f fs a
- reverseF :: FProd fs a -> FProd (Reverse fs) a
- appendF :: FProd fs a -> FProd gs a -> FProd (fs ++ gs) a
- onHeadF :: (f a -> g a) -> FProd (f :< fs) a -> FProd (g :< fs) a
- onTailF :: (FProd fs a -> FProd gs a) -> FProd (f :< fs) a -> FProd (f :< gs) a
- uncurryF :: (f a -> FProd fs a -> r) -> FProd (f :< fs) a -> r
- curryF :: l ~ (f :< fs) => (FProd l a -> r) -> f a -> FProd fs a -> r
- indexF :: Index fs f -> FProd fs a -> f a
- imapF :: (forall f. Index fs f -> f a -> f b) -> FProd fs a -> FProd fs b
- ifoldMapF :: Monoid m => (forall f. Index fs f -> f a -> m) -> FProd fs a -> m
- itraverseF :: Applicative g => (forall f. Index fs f -> f a -> g (f b)) -> FProd fs a -> g (FProd fs b)
Documentation
data FProd fs :: k -> * where Source #
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 |
ListC ((<$>) Constraint (* -> *) Foldable fs) => Foldable (FProd * fs) Source # | If all |
(ListC ((<$>) Constraint (* -> *) Functor fs), ListC ((<$>) Constraint (* -> *) Foldable fs), ListC ((<$>) Constraint (* -> *) Traversable fs)) => Traversable (FProd * fs) Source # | If all |
(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) Source # | |
type KnownC k (FProd k ((:<) (k -> *) f fs)) a Source # | |
type KnownC k (FProd k (Ø (k -> *))) a Source # | |
type WitnessC (p, s) (q, t) (FProd k ((:<) (k -> *) f fs) a) Source # | |
pattern (:>>) :: forall k f a g. 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 :<< Ø
(>>:) :: FProd fs a -> f a -> FProd (fs >: f) a infixl 6 Source #
snoc function. insert an element at the end of the FProd.
initF :: FProd (f :< fs) a -> FProd (Init' f fs) a Source #
Get all but the last element of a non-empty FProd.
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.
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.