planet-mitchell-0.0.0: Planet Mitchell

Safe HaskellSafe
LanguageHaskell2010

Optic.Iso

Contents

Synopsis

Iso

type Iso s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Profunctor p, Functor f) => p a (f b) -> p s (f t) #

Isomorphism families can be composed with another Lens using (.) and id.

Since every Iso is both a valid Lens and a valid Prism, the laws for those types imply the following laws for an Iso f:

f . from f ≡ id
from f . f ≡ id

Note: Composition with an Iso is index- and measure- preserving.

type Iso' s a = Iso s s a a #

type Iso' = Simple Iso

iso :: (s -> a) -> (b -> t) -> Iso s t a b #

Build a simple isomorphism from a pair of inverse functions.

view (iso f g) ≡ f
view (from (iso f g)) ≡ g
over (iso f g) h ≡ g . h . f
over (from (iso f g)) h ≡ f . h . g

from :: AnIso s t a b -> Iso b a t s #

Invert an isomorphism.

from (from l) ≡ l

under :: AnIso s t a b -> (t -> s) -> b -> a #

The opposite of working over a Setter is working under an isomorphism.

underover . from
under :: Iso s t a b -> (t -> s) -> b -> a

enum :: Enum a => Iso' Int a #

This isomorphism can be used to convert to or from an instance of Enum.

>>> LT^.from enum
0
>>> 97^.enum :: Char
'a'

Note: this is only an isomorphism from the numeric range actually used and it is a bit of a pleasant fiction, since there are questionable Enum instances for Double, and Float that exist solely for [1.0 .. 4.0] sugar and the instances for those and Integer don't cover all values in their range.

curried :: (Profunctor p, Functor f) => p (a -> b -> c) (f (d -> e -> f)) -> p ((a, b) -> c) (f ((d, e) -> f)) #

The canonical isomorphism for currying and uncurrying a function.

curried = iso curry uncurry
>>> (fst^.curried) 3 4
3
>>> view curried fst 3 4
3

uncurried :: (Profunctor p, Functor f) => p ((a, b) -> c) (f ((d, e) -> f)) -> p (a -> b -> c) (f (d -> e -> f)) #

The canonical isomorphism for uncurrying and currying a function.

uncurried = iso uncurry curry
uncurried = from curried
>>> ((+)^.uncurried) (1,2)
3

flipped :: (Profunctor p, Functor f) => p (b -> a -> c) (f (b' -> a' -> c')) -> p (a -> b -> c) (f (a' -> b' -> c')) #

The isomorphism for flipping a function.

>>> ((,)^.flipped) 1 2
(2,1)