module Data.Invertible.Bijection
( Bijection(..)
, type (<->)
) where
import Prelude hiding (id, (.))
import Control.Category
import Control.Arrow
#ifdef VERSION_semigroupoids
import Data.Semigroupoid (Semigroupoid(..))
import Data.Groupoid (Groupoid(..))
#endif
#ifdef VERSION_invariant
import Data.Functor.Invariant (Invariant(..), Invariant2(..))
#endif
infix 2 <->, :<->:
data Bijection (a :: * -> * -> *) b c = (:<->:)
{ biTo :: a b c
, biFrom :: a c b
}
type (<->) = Bijection (->)
instance Category a => Category (Bijection a) where
id = id :<->: id
(f1 :<->: g1) . (f2 :<->: g2) = f1 . f2 :<->: g2 . g1
instance Arrow a => Arrow (Bijection a) where
arr f = arr f :<->: arr (const (error "Bijection: arr has no inverse"))
first (f :<->: g) = first f :<->: first g
second (f :<->: g) = second f :<->: second g
(f :<->: g) *** (f' :<->: g') = (f *** f') :<->: (g *** g')
(f :<->: g) &&& (f' :<->: _ ) = (f &&& f') :<->: (g . arr fst)
instance ArrowChoice a => ArrowChoice (Bijection a) where
left (f :<->: g) = left f :<->: left g
right (f :<->: g) = right f :<->: right g
(f :<->: g) +++ (f' :<->: g') = (f +++ f') :<->: (g +++ g')
(f :<->: g) ||| (f' :<->: _ ) = (f ||| f') :<->: (arr Left . g)
instance ArrowZero a => ArrowZero (Bijection a) where
zeroArrow = zeroArrow :<->: zeroArrow
#ifdef VERSION_semigroupoids
instance Semigroupoid a => Semigroupoid (Bijection a) where
(f1 :<->: g1) `o` (f2 :<->: g2) = (f1 `o` f2) :<->: (g2 `o` g1)
instance Semigroupoid a => Groupoid (Bijection a) where
inv (f :<->: g) = g :<->: f
#endif
#ifdef VERSION_invariant
instance Invariant (Bijection (->) b) where
invmap = ((.) .) . (:<->:)
instance Invariant2 (Bijection (->)) where
invmap2 f g = (.) ((. (g :<->: f)) .) . invmap
#endif