| Portability | GHC |
|---|---|
| Stability | experimental |
| Maintainer | conal@conal.net |
Data.Pair
Contents
Description
Pair-related type constructor classes. See Data.Fun for similar classes.
- type PairTy f = forall a b. f a -> f b -> f (a, b)
- class Pair f where
- apPair :: (Applicative h, Pair f) => PairTy (h :. f)
- ppPair :: (Functor g, Pair g, Pair f) => PairTy (g :. f)
- arPair :: (Arrow ~>, Unpair f, Pair g) => PairTy (Arrw ~> f g)
- type UnpairTy f = forall a b. f (a, b) -> (f a, f b)
- class Unpair f where
- class Copair f where
- copair :: (Copair f, Monoid_f f) => PairTy f
- pairEdit :: (Functor m, Monoid (m ((c, d) -> (c, d)))) => (m c, m d) -> m ((c, d) -> (c, d))
- pairEditM :: MonadPlus m => (m c, m d) -> m ((c, d) -> (c, d))
Pairings
Type constructor class for pair-like things. Generalizes zip.
Here are some standard instance templates you can fill in. They're not
defined in the general forms below, because they would lead to a lot of
overlap.
instance Applicative f => Pair f where
pair = liftA2 (,)
instance (Applicative h, Pair f) => Pair (h :. f) where
pair = apPair
instance (Functor g, Pair g, Pair f) => Pair (g :. f)
where pair = ppPair
instance (Arrow (~>), Unpair f, Pair g) => Pair (Arrw (~>) f g) where
pair = arPair
instance (Monoid_f h, Copair h) => Pair h where
pair = copair
Also, if you have a type constructor that's a Functor and a Pair,
here is a way to define '(*)' for Applicative:
rf * rx = uncurry ($) $ (rf pair rx)
Unpairings
Dissectable as pairs. Minimal instance definition: either (a)
unpair or (b) both of pfst and psnd.
A standard template to substitute any Functor f. But watch out for
effects!
instance Functor f => Unpair f where {pfst = fmap fst; psnd = fmap snd}
Methods
Arguments
| :: UnpairTy f | Deconstruct pair-like value |
Arguments
| :: f (a, b) | |
| -> f a | First part of pair-like value |
Arguments
| :: f (a, b) | |
| -> f b | Second part of pair-like value |
Dual unpairings
Dual to Unpair.
Especially handy for contravariant functors (Cofunctor) . Use this
template (filling in f) :
instance Cofunctor f => Copair f where
{ cofst = cofmap fst ; cosnd = cofmap snd }
Methods
Arguments
| :: f a | |
| -> f (a, b) | Pair-like value from first part |
Arguments
| :: f b | |
| -> f (a, b) | Pair-like value from second part |
copair :: (Copair f, Monoid_f f) => PairTy fSource
Pairing of Copair values. Combines contribution of each.
Misc
pairEdit :: (Functor m, Monoid (m ((c, d) -> (c, d)))) => (m c, m d) -> m ((c, d) -> (c, d))Source
Turn a pair of sources into a source of pair-editors. See
http://conal.net/blog/posts/pairs-sums-and-reactivity/.
'Functor'\/'Monoid' version. See also pairEditM.
pairEditM :: MonadPlus m => (m c, m d) -> m ((c, d) -> (c, d))Source
Turn a pair of sources into a source of pair-editors. See
http://conal.net/blog/posts/pairs-sums-and-reactivity/.
Monad version. See also pairEdit.