TypeCompose-0.6.8: Type composition classes & instances

PortabilityGHC
Stabilityexperimental
Maintainerconal@conal.net

Data.Pair

Contents

Description

Pair-related type constructor classes.

This module is similar to Control.Functor.Pair in the category-extras package, but it does not require a Functor superclass.

Temporarily, there is also Data.Zip, which contains the same functionality with different naming. I'm unsure which I prefer.

Synopsis

Pairpings

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. 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:

    (<*>) = pairWith ($)

Minimum definitions for instances.

Methods

pairSource

Arguments

:: PairTy f

Generalized pair

Instances

Pair [] 
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 unpair.

class Unpair f whereSource

Unpairpable. Minimal instance definition: either (a) unpair or (b) both of fsts and snds. A standard template to substitute any Functor f. But watch out for effects!

     instance Functor f => Unpair f where {fsts = fmap fst; snds = fmap snd}

Methods

unpairSource

Arguments

:: UnpairTy f

generalized unpair

fstsSource

Arguments

:: f (a, b) 
-> f a

First part of pair-like value

sndsSource

Arguments

:: f (a, b) 
-> f b

Second part of pair-like value

Instances

Unpair [] 
Unpair Endo 
Unpair Id 
Unpair ((->) a) 
Unpair ((,) a) 
Unpair (Const a) 

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
      { cofsts = cofmap fst ; cosnds = cofmap snd }

Methods

cofstsSource

Arguments

:: f a 
-> f (a, b)

Pair-like value from first part

cosndsSource

Arguments

:: f b 
-> f (a, b)

Pair-like value from second part

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.

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.