TypeCompose-0.9.11: Type composition classes & instances

Copyright(c) Conal Elliott 2007
LicenseBSD3
Maintainerconal@conal.net
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell98

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 where Source

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

pair Source

Arguments

:: PairTy f

Generalized pair

Instances

Pair [] Source 
Pair IO Source 
Pair Endo Source 
Pair Id Source 
Pair ((->) u) Source 
Monoid u => Pair ((,) u) Source 
Monoid o => Pair (Const o) Source 
(Pair f, Pair g) => Pair ((:*:) f g) Source 
(Arrow j, Monoid_f (Flip j o)) => Pair (Flip j o) Source 
(Arrow j, Unpair f, Pair g) => Pair (Arrw j f g) Source 

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 j, Unpair f, Pair g) => PairTy (Arrw j 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 where Source

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}

Minimal complete definition

Nothing

Methods

unpair Source

Arguments

:: UnpairTy f

generalized unpair

fsts Source

Arguments

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

First part of pair-like value

snds Source

Arguments

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

Second part of pair-like value

Dual unpairings

class Copair f where Source

Dual to Unpair. Especially handy for contravariant functors (ContraFunctor) . Use this template (filling in f) :

   instance ContraFunctor f => Copair f where
     { cofsts = cofmap fst ; cosnds = cofmap snd }

Methods

cofsts Source

Arguments

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

Pair-like value from first part

cosnds Source

Arguments

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

Pair-like value from second part

Instances

copair :: (Copair f, Monoid_f f) => PairTy f Source

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.