TypeCompose-0.9.14: 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 # 
Instance details

Defined in Data.Pair

Methods

pair :: PairTy [] Source #

Pair IO Source # 
Instance details

Defined in Data.Pair

Methods

pair :: PairTy IO Source #

Pair Endo Source # 
Instance details

Defined in Data.Pair

Methods

pair :: PairTy Endo Source #

Pair Id Source # 
Instance details

Defined in Data.Pair

Methods

pair :: PairTy Id Source #

Monoid u => Pair ((,) u) Source # 
Instance details

Defined in Data.Pair

Methods

pair :: PairTy ((,) u) Source #

Monoid o => Pair (Const o :: Type -> Type) Source # 
Instance details

Defined in Data.Pair

Methods

pair :: PairTy (Const o) Source #

Pair ((->) u :: Type -> Type) Source # 
Instance details

Defined in Data.Pair

Methods

pair :: PairTy ((->) u) Source #

(Pair f, Pair g) => Pair (f :*: g) Source # 
Instance details

Defined in Data.Pair

Methods

pair :: PairTy (f :*: g) Source #

(Arrow j, Monoid_f (Flip j o)) => Pair (Flip j o) Source # 
Instance details

Defined in Data.Pair

Methods

pair :: PairTy (Flip j o) Source #

(Arrow j, Unpair f, Pair g) => Pair (Arrw j f g) Source # 
Instance details

Defined in Data.Pair

Methods

pair :: PairTy (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

Instances
Unpair [] Source # 
Instance details

Defined in Data.Pair

Methods

unpair :: UnpairTy [] Source #

fsts :: [(a, b)] -> [a] Source #

snds :: [(a, b)] -> [b] Source #

Unpair Endo Source # 
Instance details

Defined in Data.Pair

Methods

unpair :: UnpairTy Endo Source #

fsts :: Endo (a, b) -> Endo a Source #

snds :: Endo (a, b) -> Endo b Source #

Unpair Id Source # 
Instance details

Defined in Data.Pair

Methods

unpair :: UnpairTy Id Source #

fsts :: Id (a, b) -> Id a Source #

snds :: Id (a, b) -> Id b Source #

Unpair ((,) a) Source # 
Instance details

Defined in Data.Pair

Methods

unpair :: UnpairTy ((,) a) Source #

fsts :: (a, (a0, b)) -> (a, a0) Source #

snds :: (a, (a0, b)) -> (a, b) Source #

Unpair (Const a :: Type -> Type) Source # 
Instance details

Defined in Data.Pair

Methods

unpair :: UnpairTy (Const a) Source #

fsts :: Const a (a0, b) -> Const a a0 Source #

snds :: Const a (a0, b) -> Const a b Source #

Unpair ((->) a :: Type -> Type) Source # 
Instance details

Defined in Data.Pair

Methods

unpair :: UnpairTy ((->) a) Source #

fsts :: (a -> (a0, b)) -> a -> a0 Source #

snds :: (a -> (a0, b)) -> a -> b Source #

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 Endo Source # 
Instance details

Defined in Data.Pair

Methods

cofsts :: Endo a -> Endo (a, b) Source #

cosnds :: Endo b -> Endo (a, b) Source #

Copair (Const e :: Type -> Type) Source # 
Instance details

Defined in Data.Pair

Methods

cofsts :: Const e a -> Const e (a, b) Source #

cosnds :: Const e b -> Const e (a, b) Source #

(Copair f, Copair g) => Copair (f :*: g) Source # 
Instance details

Defined in Data.Pair

Methods

cofsts :: (f :*: g) a -> (f :*: g) (a, b) Source #

cosnds :: (f :*: g) b -> (f :*: g) (a, b) Source #

Arrow j => Copair (Flip j o) Source # 
Instance details

Defined in Data.Pair

Methods

cofsts :: Flip j o a -> Flip j o (a, b) Source #

cosnds :: Flip j o b -> Flip j o (a, b) Source #

(Functor h, Copair f) => Copair (h :. f) Source # 
Instance details

Defined in Data.Pair

Methods

cofsts :: (h :. f) a -> (h :. f) (a, b) Source #

cosnds :: (h :. f) b -> (h :. f) (a, b) Source #

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.