semi-iso-0.5.0.0: Weakened partial isomorphisms that work with lenses.

Copyright(c) Paweł Nowak
LicenseMIT
MaintainerPaweł Nowak <pawel834@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.SemiIsoFunctor

Description

Defines a functor from the category of semi-isomoprihsms to Hask.

It can be instantiated by both covariant (like Parser) and contravariant (like Printer) functors. Therefore it can be used as a common interface to unify parsing and pretty printing.

Synopsis

Documentation

class SemiIsoFunctor f where Source

A functor from the category of semi-isomorphisms to Hask. We can think of it as if it was both covariant and contravariant in its single argument.

The contravariant map is used by default to provide compatibility with Prisms (otherwise you would have to reverse them in most cases).

This is really a pair of functors F : SemiIso -> Hask, G : SemiIso^op -> Hask satisfying:

F(X) = G(X)
F(f) = G(f^-1)

Instances should satisfy laws:

functoriality
simap id = id
simap (f . g) = simap g . simap f
inverse
simap f = simapCo (rev f)

Minimal complete definition

simap | simapCo

Methods

simap :: ASemiIso' a b -> f b -> f a Source

The contravariant map.

simapCo :: ASemiIso' a b -> f a -> f b Source

The covariant map.

(/$/) :: SemiIsoFunctor f => ASemiIso' a b -> f b -> f a infixl 4 Source

A infix operator for simap.

(/$~) :: (SemiIsoFunctor f, HFoldable b', HFoldable b, HUnfoldable b', HUnfoldable b, Rep b' ~ Rep b) => ASemiIso' a b' -> f b -> f a infixl 4 Source

ai /$~ f = ai . morphed /$/ f

This operator handles all the hairy stuff with uncurried application: it reassociates the argument tuple and removes unnecessary (or adds necessary) units to match the function type. You don't have to use /* and */ with this operator.

(~$/) :: (SemiIsoFunctor f, HFoldable a', HFoldable a, HUnfoldable a', HUnfoldable a, Rep a' ~ Rep a) => ASemiIso' a' b -> f b -> f a infixl 4 Source

ai ~$/ f = morphed . ai /$/ f

(~$~) :: (SemiIsoFunctor f, HFoldable a, HUnfoldable a, HFoldable b, HUnfoldable b, HFoldable b', HUnfoldable b', Rep b' ~ Rep b, Rep b' ~ Rep a) => ASemiIso b' b' b' b' -> f b -> f a infixl 4 Source

ai ~$~ f = morphed . ai . morphed /$/ f

class SemiIsoFunctor f => SemiIsoApply f where Source

An applicative semi-iso functor, i. e. a lax monoidal functor from SemiIso to Hask.

Instances should satisfy laws:

homomorphism
sipure f /*/ sipure g = sipure (f `prod` g)
associativity
f /*/ (g /*/ h) = associated /$/ (f /*/ g) /*/ h
unitality
siunit /*/ x = swapped . rev unit /$/ x
x /*/ siunit = rev unit /$/ x

Additionally it should be consistent with the default implementation:

sipure ai = ai /$/ siunit
sipureCo ai = ai `simapCo` siunit
f /* g = unit /$/ f /*/ g
f */ g = unit . swapped /$/ f /*/ g

Minimal complete definition

(siunit | sipure), (/*/)

Methods

siunit :: f () Source

sipure :: ASemiIso' a () -> f a Source

sipureCo :: ASemiIso' () a -> f a Source

(/*/) :: f a -> f b -> f (a, b) infixl 5 Source

(/*) :: f a -> f () -> f a infixl 5 Source

(*/) :: f () -> f b -> f b infixl 5 Source

Instances

sifail :: SemiIsoApply f => String -> f a Source

Fails with a message.

class SemiIsoApply f => SemiIsoAlternative f where Source

Equivalent of Alternative for SemiIsoFunctor.

f a should form a monoid with identity siempty and binary operation /|/.

Minimal complete definition

siempty, (/|/)

Methods

siempty :: f a Source

(/|/) :: f a -> f a -> f a infixl 3 Source

sisome :: f a -> f [a] Source

simany :: f a -> f [a] Source

(/?/) :: SemiIsoAlternative f => f a -> String -> f a infixl 3 Source

Provides an error message in the case of failure.

class SemiIsoApply m => SemiIsoMonad m where Source

An analogue of Monad for SemiIsoFunctor.

Because of the 'no throwing away' rule bind has to "return" both a and b.

Minimal complete definition

(//=) | (=//)

Methods

(//=) :: m a -> (a -> m b) -> m (a, b) infixl 1 Source

(=//) :: (b -> m a) -> m b -> m (a, b) infixr 1 Source

Instances

class SemiIsoMonad m => SemiIsoFix m where Source

A SemiIsoMonad with fixed point operator.

Minimal complete definition

sifix | (=//=)

Methods

sifix :: (a -> m a) -> m a Source

(=//=) :: (a -> m b) -> (b -> m a) -> m (a, b) Source

Fixed point combined with bind, it's so symmetric!

sisequence :: SemiIsoApply f => [f a] -> f [a] Source

Equivalent of sequence.

sisequence_ :: SemiIsoApply f => [f ()] -> f () Source

Equivalent of sequence_, restricted to units.

sireplicate :: SemiIsoApply f => Int -> f a -> f [a] Source

Equivalent of replicateM.

sireplicate_ :: SemiIsoApply f => Int -> f () -> f () Source

Equivalent of replicateM_, restricted to units.