invertible-0.1: bidirectional arrows, bijective functions, and invariant functors

Safe HaskellTrustworthy
LanguageHaskell2010

Control.Invertible.BiArrow

Description

Bidirectional arrows. Taken directly from

Synopsis

Documentation

class (Groupoid a, Category a) => BiArrow a where Source

The bidirectional arrow class.

Instances should satisfy the following laws:

  • f1 <-> g2 >>> g1 <-> f2 = (f1 >>> g1) <-> (f2 >>> g2)
  • invert (invert f) = f
  • invert (f <-> g) = g <-> f
  • first (f <-> g) = f *** id <-> g *** id
  • first h >>> id *** f <-> id *** g = id *** f <-> id *** g >>> first h
  • first (first f) >>> assoc = assoc >>> first f

where assoc = [biCase|((x,y),z) <-> (x,(y,z))|]

Minimal complete definition

(<->)

Methods

(<->) :: (b -> c) -> (c -> b) -> a b c infix 2 Source

Take two functions and lift them into a bidirectional arrow. The intention is that these functions are each other's inverse.

invert :: a b c -> a c b Source

Inverse: reverse the direction of a bidirectional arrow.

class (BiArrow a, Arrow a) => BiArrow' a Source

Bidirectional arrows under Arrow.

Although BiArrow should not, strictly speaking, be a subclass of Arrow (as it is often impossible to define arr), this is done because (as the paper says) "conceptually bi-arrows form an extension of the arrow class. Moreover, it allows us to use bi-arrows as normal arrows." This class exists to register this confound.

biarr :: BiArrow a => (b <-> c) -> a b c Source

Lift a bidirectional function to an arbitrary arrow using <->.

involve :: BiArrow a => (b -> b) -> a b b Source

Construct an involution (a biarrow where the function and inverse are the same).

(^^>>) :: BiArrow a => (b <-> c) -> a c d -> a b d infixr 1 Source

Precomposition with a pure bijection.

(>>^^) :: BiArrow a => a b c -> (c <-> d) -> a b d infixr 1 Source

Postcomposition with a pure bijection.

(<<^^) :: BiArrow a => a c d -> (b <-> c) -> a b d infixr 1 Source

Precomposition with a pure bijection (right-to-left variant).

(^^<<) :: BiArrow a => (c <-> d) -> a b c -> a b d infixr 1 Source

Postcomposition with a pure bijection (right-to-left variant).