lens-3.7.4: Lenses, Folds and Traversals

PortabilityRank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Control.Lens.Iso

Contents

Description

 

Synopsis

Isomorphism Lenses

type Iso s t a b = forall k f. (Isomorphic k, Functor f) => k (a -> f b) (s -> f t)Source

Isomorphism families can be composed with other lenses using (.) and id.

type AnIso s t a b = Overloaded Isoid Mutator s t a bSource

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

Isomorphism Construction

class Category k => Isomorphic k whereSource

Used to provide overloading of isomorphism application

An instance of Isomorphic is a Category with a canonical mapping to it from the category of isomorphisms over Haskell types.

Methods

iso :: Functor f => (s -> a) -> (b -> t) -> k (a -> f b) (s -> f t)Source

Build a simple isomorphism from a pair of inverse functions

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

data Isoid ab st whereSource

Reify all of the information given to you by being Isomorphic.

Constructors

Isoid :: Isoid ab ab 
Iso :: (CoA y -> CoA x) -> (CoB x -> CoB y) -> Isoid x y 

Consuming Isomorphisms

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

Invert an isomorphism.

from (from l) ≡ l

cloneIso :: AnIso s t a b -> Iso s t a bSource

Convert from an Isomorphism back to any Isomorphic value.

This is useful when you need to store an isomorphism as a data type inside a container and later reconstitute it as an overloaded function.

See cloneLens or cloneTraversal for more information on why you might want to do this.

Working with isomorphisms

au :: AnIso s t a b -> ((s -> a) -> e -> b) -> e -> tSource

Based on ala from Conor McBride's work on Epigram.

This version is generalized to accept any Iso, not just a newtype.

>>> au (wrapping Sum) foldMap [1,2,3,4]
10

auf :: AnIso s t a b -> ((r -> a) -> e -> b) -> (r -> s) -> e -> tSource

Based on ala' from Conor McBride's work on Epigram.

This version is generalized to accept any Iso, not just a newtype.

For a version you pass the name of the newtype constructor to, see alaf.

Mnemonically, the German auf plays a similar role to à la, and the combinator is au with an extra function argument.

>>> auf (wrapping Sum) (foldMapOf both) Prelude.length ("hello","world")
10

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

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

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

mapping :: Functor f => AnIso s t a b -> Iso (f s) (f t) (f a) (f b)Source

This can be used to lift any SimpleIso into an arbitrary functor.

Common Isomorphisms

simple :: Simple Iso a aSource

Composition with this isomorphism is occasionally useful when your Lens, Traversal or Iso has a constraint on an unused argument to force that argument to agree with the type of a used argument and avoid ScopedTypeVariables or other ugliness.

non :: Eq a => a -> Simple Iso (Maybe a) aSource

If v is an element of a type a, and a' is a sans the element v, then non v is an isomorphism from Maybe a' to a.

Keep in mind this is only a real isomorphism if you treat the domain as being Maybe (a sans v)

This is practically quite useful when you want to have a map where all the entries should have non-zero values.

>>> Map.fromList [("hello",1)] & at "hello" . non 0 +~ 2
fromList [("hello",3)]
>>> Map.fromList [("hello",1)] & at "hello" . non 0 -~ 1
fromList []
>>> Map.fromList [("hello",1)] ^. at "hello" . non 0
1
>>> Map.fromList [] ^. at "hello" . non 0
0

This combinator is also particularly useful when working with nested maps.

e.g. When you want to create the nested map when it is missing:

>>> Map.empty & at "hello" . non Map.empty . at "world" ?~ "!!!"
fromList [("hello",fromList [("world","!!!")])]

and when have deleting the last entry from the nested map mean that we should delete its entry from the surrounding one:

>>> fromList [("hello",fromList [("world","!!!")])] & at "hello" . non Map.empty . at "world" .~ Nothing
fromList []

anon :: a -> (a -> Bool) -> Simple Iso (Maybe a) aSource

anon a p generalizes non a to take any value and a predicate.

This function assumes that p a holds True and generates an isomorphism between Maybe (a | not (p a)) and a

>>> Map.empty & at "hello" . anon Map.empty Map.null . at "world" ?~ "!!!"
fromList [("hello",fromList [("world","!!!")])]
>>> fromList [("hello",fromList [("world","!!!")])] & at "hello" . anon Map.empty Map.null . at "world" .~ Nothing
fromList []

enum :: Enum a => Simple Iso Int aSource

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 :: Iso ((a, b) -> c) ((d, e) -> f) (a -> b -> c) (d -> e -> f)Source

The canonical isomorphism for currying and uncurrying a function.

curried = iso curry uncurry

uncurried :: Iso (a -> b -> c) (d -> e -> f) ((a, b) -> c) ((d, e) -> f)Source

The canonical isomorphism for uncurrying and currying a function.

uncurried = iso uncurry curry
uncurried = from curried

class Strict s t a b | s -> a, a -> s, b -> t, t -> b, s b -> a t, a t -> s b whereSource

Ad hoc conversion between "strict" and "lazy" versions of a structure, such as Text or ByteString.

Methods

strict :: Iso s t a bSource

Simplicity

type SimpleIso s a = Iso s s a aSource

Useful Type Families

type family CoA x :: *Source

Extract a from the type a -> f b

type family CoB x :: *Source

Extract b from the type a -> f b