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

Copyright(c) Paweł Nowak
LicenseMIT
MaintainerPaweł Nowak <pawel834@gmail.com>
Stabilityexperimental
Safe HaskellNone
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. (Exposed (Either String) 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 = Retail a b a (Identity b) -> Retail 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'.

Patterns.

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.

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.

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.

viewSemiIso :: ASemiIso s t a b -> (s -> Either String a, b -> Either String t) Source

Extracts the two functions that characterize the SemiIso.

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))

swapped . swappedid
first f . swapped = swapped . second f
second g . swapped = swapped . first g
bimap f g . swapped = swapped . bimap g f
>>> (1,2)^.swapped
(2,1)

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

Products are associative.

morphed :: (HFoldable a, HUnfoldable a, HFoldable b, HUnfoldable b, Rep a ~ Rep b) => Iso' a b Source

An isomorphism between two arbitrary nested tuples, as long the contained types (ignoring units!) read from left to right are the same.

This is implemented using morph from 'tuple-morph'.

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.

bifiltered :: (a -> Bool) -> SemiIso' a a Source

Like filtered but checks the predicate in both ways.

Semi-isos for numbers.

_Negative :: Real a => SemiIso' a a Source

-> Matches only negative numbers, turns it into a positive one.

<- Matches only positive numbers, turns it into a negative one.

Transforming semi-isos.

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

Reverses a SemiIso.

prod :: ASemiIso s t a b -> ASemiIso s' t' a' b' -> SemiIso (s, s') (t, t') (a, a') (b, b') Source

A product of SemiIso's.

elimFirst :: ASemiIso s' t' () () -> SemiIso (s', t) (t', t) t t Source

In the non-polymorphic case uses an SemiIso a () to construct a SemiIso (a, b) b, i.e. eliminates the first pair element.

elimSecond :: ASemiIso s' t' () () -> SemiIso (t, s') (t, t') t t Source

In the non-polymorphic case uses an SemiIso b () to construct a SemiIso (a, b) a, i.e. eliminates the second pair element.

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

Transforms the semi-iso so that applying it in both directions never fails, but instead catches any errors and returns them as an Either String a.

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

Transforms the semi-iso so that applying it in direction (->) never fails, but instead catches any errors and returns them as an Either String a.

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

Transforms the semi-iso so that applying it in direction (<-) never fails, but instead catches any errors and returns them as an Either String a.

attempt_ :: ASemiIso s t a b -> SemiIso s (Maybe t) (Maybe a) b Source

Transforms the semi-iso like attempt, but ignores the error message.

attemptAp_ :: ASemiIso s t a b -> SemiIso s t (Maybe a) b Source

Transforms the semi-iso like attemptAp, but ignores the error message.

Very useful when you want to bifold using a prism.

attemptUn_ :: ASemiIso s t a b -> SemiIso s (Maybe t) a b Source

Transforms the semi-iso like attemptUn, but ignores the error message.

Bidirectional folds.

bifoldr :: ASemiIso' a (b, a) -> SemiIso' a (a, [b]) Source

Constructs a bidirectional fold. Works with prisms.

-> Right unfolds using the (->) part of the given semi-iso, until it fails.

<- Right folds using the (<-) part of the given semi-iso.

bifoldr1 :: ASemiIso' a (a, a) -> SemiIso' a [a] Source

Constructs a bidirectional fold. Works with prisms.

-> Right unfolds using the (->) part of the given semi-iso, until it fails. It should produce a non-empty list.

<- Right folds a non-empty list using the (<-) part of the given semi-iso.

bifoldl :: ASemiIso' a (a, b) -> SemiIso' a (a, [b]) Source

Constructs a bidirectional fold. Works with prisms.

-> Left unfolds using the (->) part of the given semi-iso, until it fails.

<- Left folds using the (<-) part of the given semi-iso.

bifoldl1 :: ASemiIso' a (a, a) -> SemiIso' a [a] Source

Constructs a bidirectional fold. Works with prisms.

-> Left unfolds using the (->) part of the given semi-iso, until it fails. It should produce a non-empty list.

<- Left folds a non-empty list using the (<-) part of the given semi-iso.

bifoldr_ :: ASemiIso a a (Maybe (b, a)) (b, a) -> SemiIso' a (a, [b]) Source

Constructs a bidirectional fold.

-> Right unfolds using the (->) part of the given semi-iso.

<- Right folds using the (<-) part of the given semi-iso.

bifoldr1_ :: ASemiIso a a (Maybe (a, a)) (a, a) -> SemiIso' a [a] Source

Constructs a bidirectional fold.

-> Right unfolds using the (->) part of the given semi-iso. It should produce a non-empty list.

<- Right folds a non-empty list using the (<-) part of the given semi-iso.

bifoldl_ :: ASemiIso a a (Maybe (a, b)) (a, b) -> SemiIso' a (a, [b]) Source

Constructs a bidirectional fold.

-> Left unfolds using the (->) part of the given semi-iso.

<- Left folds using the (<-) part of the given semi-iso.

bifoldl1_ :: ASemiIso a a (Maybe (a, a)) (a, a) -> SemiIso' a [a] Source

Constructs a bidirectional fold.

-> Left unfolds using the (->) part of the given semi-iso. It should produce a non-empty list.

<- Left folds a non-empty list using the (<-) part of the given semi-iso.