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

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

Control.Lens.SemiIso

Contents

Description

Semi-isomorphisms were motivated by reversible parsing/pretty printing. For example we can map a number 12 to a string "12" (and the other way around). But the isomorphism is partial - we cannot map the string "forty-two" to a number.

Another example: when parsing a list of numbers like "12_53___42" we want to skip underscores between numbers (and forget about them). During pretty printing we have to decide how many underscores should we insert between numbers. Let's say we insert a single underscore. But now prettyPrint (parse "12_53___42") = "12_53_42" and not "12_53___42". We have to weaken isomorphism laws to allow such semi-iso. Notice that

parse (prettyPrint (parse "12_53___42"))       = parse "12_53___42"
prettyPrint (parse (prettyPrint [12, 53, 42])) = prettyPrint [12, 53, 42]

Our semi-isomorphisms will obey weakened laws:

apply i   >=> unapply i >=> apply i   = apply i
unapply i >=> apply i   >=> unapply i = unapply i

When you see an "Either String a", the String is usually an error message.

Disclaimer: the name "semi-isomorphism" is fictitious and made up for this library. Any resemblance to known mathematical objects of the same name is purely coincidental.

Synopsis

Semi-isomorphism types.

type SemiIso s t a b = forall p f. (Failure p, Traversable f) => p a (f b) -> p s (f t) Source

A semi-isomorphism is a partial isomorphism with weakened laws.

Should satisfy laws:

apply i   >=> unapply i >=> apply i   = apply i
unapply i >=> apply i   >=> unapply i = unapply i

Every Prism is a SemiIso. Every Iso is a Prism.

type SemiIso' s a = SemiIso s s a a Source

Non-polymorphic variant of SemiIso.

type ASemiIso s t a b = Barter a b a (Identity b) -> Barter a b s (Identity t) Source

When you see this as an argument to a function, it expects a SemiIso.

type ASemiIso' s a = ASemiIso s s a a Source

When you see this as an argument to a function, it expects a SemiIso'.

Constructing semi-isos.

semiIso :: (s -> Either String a) -> (b -> Either String t) -> SemiIso s t a b Source

Constructs a semi isomorphism from a pair of functions that can fail with an error message.

Consuming semi-isos.

withSemiIso :: ASemiIso s t a b -> ((s -> Either String a) -> (b -> Either String t) -> r) -> r Source

Extracts the two functions that characterize the SemiIso.

fromSemi :: ASemiIso s t a b -> SemiIso b a t s Source

Reverses a SemiIso.

apply :: ASemiIso s t a b -> s -> Either String a Source

Applies the SemiIso.

unapply :: ASemiIso s t a b -> b -> Either String t Source

Applies the SemiIso in the opposite direction.

Common semi-isomorphisms and isomorphisms.

unit :: Iso' a (a, ()) Source

A trivial isomorphism between a and (a, ()).

swapped :: Swapped p => forall a b c d p f. (Profunctor p, Functor f) => p (p b a) (f (p d c)) -> p (p a b) (f (p c d))

associated :: Iso' (a, (b, c)) ((a, b), c) Source

Products are associative.

constant :: a -> SemiIso' () a Source

-> Always returns the argument.

<- Maps everything to a ().

Note that this isn't an Iso' because

unapply (constant x) >=> apply (constant x) /= id

But SemiIso laws do hold.

exact :: Eq a => a -> SemiIso' () a Source

-> Always returns the argument.

<- Filters out all values not equal to the argument.