TypeCompose-0.3: Type composition classes & instancesSource codeContentsIndex
Data.Pair
PortabilityGHC
Stabilityexperimental
Maintainerconal@conal.net
Contents
Pairings
Unpairings
Dual unpairings
Description
Pair-related type constructor classes. See Data.Fun for similar classes.
Synopsis
type PairTy f = forall a b. f a -> f b -> f (a, b)
class Pair f where
pair :: PairTy f
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
unpair :: UnpairTy f
pfst :: f (a, b) -> f a
psnd :: f (a, b) -> f b
class Copair f where
cofst :: f a -> f (a, b)
cosnd :: f b -> f (a, b)
copair :: (Copair f, Monoid_f f) => PairTy f
Pairings
type PairTy f = forall a b. f a -> f b -> f (a, b)Source
Type of pair method
class Pair f whereSource

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
Methods
pairSource
:: PairTy fForm a pair-like value (generalizes zip)
show/hide Instances
Pair IO
Pair Endo
Pair Id
Pair ((->) u)
Monoid u => Pair ((,) u)
Monoid o => Pair (Const o)
(Pair f, Pair g) => Pair (f :*: g)
(Arrow ~>, Monoid_f (Flip ~> o)) => Pair (Flip ~> o)
(Arrow ~>, Unpair f, Pair g) => Pair (Arrw ~> f g)
apPair :: (Applicative h, Pair f) => PairTy (h :. f)Source
Handy for Pair instances
ppPair :: (Functor g, Pair g, Pair f) => PairTy (g :. f)Source
Handy for Pair instances
arPair :: (Arrow ~>, Unpair f, Pair g) => PairTy (Arrw ~> f g)Source
Pairing of Arrw values. Warning: definition uses arr, so only use if your arrow has a working arr.
Unpairings
type UnpairTy f = forall a b. f (a, b) -> (f a, f b)Source
Type of unpair method. Generalizes unzip.
class Unpair f whereSource

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
unpairSource
:: UnpairTy fDeconstruct pair-like value
pfstSource
::
=> f (a, b)
-> f aFirst part of pair-like value
psndSource
::
=> f (a, b)
-> f bSecond part of pair-like value
show/hide Instances
Dual unpairings
class Copair f whereSource

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
cofstSource
::
=> f a
-> f (a, b)Pair-like value from first part
cosndSource
::
=> f b
-> f (a, b)Pair-like value from second part
show/hide Instances
Copair Endo
Copair (Const e)
(Copair f, Copair g) => Copair (f :*: g)
Arrow ~> => Copair (Flip ~> o)
(Functor h, Copair f) => Copair (h :. f)
copair :: (Copair f, Monoid_f f) => PairTy fSource
Pairing of Copair values. Combines contribution of each.
Produced by Haddock version 2.3.0