TypeCompose-0.9.13: Type composition classes & instances

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

Data.Bijection

Description

Bijections. For a more general setting, see also [1] There and Back Again: Arrows for Invertible Programming, http://citeseer.ist.psu.edu/alimarine05there.html.

Synopsis

Documentation

data Bijection j a b Source #

A type of bijective arrows

Constructors

Bi 

Fields

Instances
Arrow j => Arrow (Bijection j) Source # 
Instance details

Defined in Data.Bijection

Methods

arr :: (b -> c) -> Bijection j b c #

first :: Bijection j b c -> Bijection j (b, d) (c, d) #

second :: Bijection j b c -> Bijection j (d, b) (d, c) #

(***) :: Bijection j b c -> Bijection j b' c' -> Bijection j (b, b') (c, c') #

(&&&) :: Bijection j b c -> Bijection j b c' -> Bijection j b (c, c') #

Category j => Category (Bijection j :: * -> * -> *) Source # 
Instance details

Defined in Data.Bijection

Methods

id :: Bijection j a a #

(.) :: Bijection j b c -> Bijection j a b -> Bijection j a c #

type (:<->:) a b = Bijection (->) a b infix 8 Source #

Bijective functions

idb :: Arrow j => Bijection j a a Source #

Bijective identity arrow. Warning: uses arr on (~>). If you have no arr, but you have a DeepArrow, you can instead use Bi idA idA.

inverse :: Bijection j a b -> Bijection j b a Source #

Inverse bijection

bimap :: Functor f => (a :<->: b) -> f a :<->: f b Source #

Bijections on functors

(--->) :: Arrow j => Bijection j a b -> Bijection j c d -> (a `j` c) :<->: (b `j` d) infixr 2 Source #

Bijections on arrows.

inBi :: Arrow j => Bijection j a b -> (a `j` a) -> b `j` b Source #

Apply a function in an alternative (monomorphic) representation.