functor-combinators-0.4.1.0: Tools for functor combinator-based program design
Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Control.Natural.IsoF

Description

Types describing isomorphisms between two functors, and functions to manipulate them.

Synopsis

Documentation

type (~>) (f :: k -> Type) (g :: k -> Type) = forall (x :: k). f x -> g x #

type (<~>) f g = forall p a. Profunctor p => p (g a) (g a) -> p (f a) (f a) infixr 0 Source #

The type of an isomorphism between two functors. f <~> g means that f and g are isomorphic to each other.

We can effectively use an f <~> g with:

viewF   :: (f <~> g) -> f a -> g a
reviewF :: (f <~> g) -> g a -> a a

Use viewF to extract the "f to g" function, and reviewF to extract the "g to f" function. Reviewing and viewing the same value (or vice versa) leaves the value unchanged.

One nice thing is that we can compose isomorphisms using . from Prelude:

(.) :: f <~> g
    -> g <~> h
    -> f <~> h

Another nice thing about this representation is that we have the "identity" isomorphism by using id from Prelude.

id :: f <~> g

As a convention, most isomorphisms have form "X-ing", where the forwards function is "ing". For example, we have:

splittingSF :: Monoidal t => SF t a <~> t f (MF t f)
splitSF     :: Monoidal t => SF t a  ~> t f (MF t f)

isoF :: (f ~> g) -> (g ~> f) -> f <~> g Source #

Create an f <~> g by providing both legs of the isomorphism (the f a -> g a and the g a -> f a.

coercedF :: forall f g. (forall x. Coercible (f x) (g x), forall x. Coercible (g x) (f x)) => f <~> g Source #

An isomorphism between two functors that are coercible/have the same internal representation. Useful for newtype wrappers.

viewF :: (f <~> g) -> f ~> g Source #

Use a <~> by retrieving the "forward" function:

viewF   :: (f ~ g) -> f a -> g a

reviewF :: (f <~> g) -> g ~> f Source #

Use a <~> by retrieving the "backwards" function:

viewF   :: (f ~ g) -> f a -> g a

overF :: (f <~> g) -> (g ~> g) -> f ~> f Source #

Lift a function g a ~> g a to be a function f a -> f a, given an isomorphism between the two.

One neat thing is that overF i id == id.

fromF :: forall (f :: Type -> Type) (g :: Type -> Type). (f <~> g) -> g <~> f Source #

Reverse an isomorphism.

viewF   (fromF i) == reviewF i
reviewF (fromF i) == viewF i