lens-4.0.7: Lenses, Folds and Traversals

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

Control.Lens.Iso

Description

Synopsis

Isomorphism Lenses

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

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

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

type Iso' s a = Iso s s a aSource

 type Iso'  = Simple  Iso 

type AnIso s t a b = Exchange a b a (Identity b) -> Exchange a b s (Identity t)Source

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

type AnIso' s a = AnIso s s a aSource

A Simple AnIso .

Isomorphism Construction

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

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

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 AnIso back to any Iso .

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.

withIso :: AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> rSource

Extract the two functions, one from s -> a and one from b -> t that characterize an Iso .

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 (_Unwrapping Sum) foldMap [1,2,3,4]
10

auf :: Profunctor p => AnIso s t a b -> (p r a -> e -> b) -> p 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 (_Unwrapping 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.

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

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 Iso into an arbitrary Functor .

Common Isomorphisms

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

 non non'  .  only 

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 []

non' :: APrism' a () -> Iso' (Maybe a) aSource

non' p generalizes non (p # ()) to take any unit Prism

This function generates an isomorphism between Maybe (a | isn't p a) and a.

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

anon :: a -> (a -> Bool) -> 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 => 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 
>>> (fst^.curried) 3 4
3
>>> view curried fst 3 4
3

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 
>>> ((+)^.uncurried) (1,2)
3

flipped :: Iso (a -> b -> c) (a' -> b' -> c') (b -> a -> c) (b' -> a' -> c')Source

The isomorphism for flipping a function.

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

class Bifunctor p => Swapped p whereSource

This class provides for symmetric bifunctors.

Methods

swapped :: Iso (p a b) (p c d) (p b a) (p d c)Source

 swapped  .  swapped id 
 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)

Instances

class Strict lazy strict | lazy -> strict, strict -> lazy whereSource

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

Methods

strict :: Iso' lazy strictSource

Instances

Strict (StateT s m a) (StateT s m a)
Strict (WriterT w m a) (WriterT w m a)
Strict (RWST r w s m a) (RWST r w s m a)

lazy :: Strict lazy strict => Iso' strict lazySource

An Iso between the strict variant of a structure and its lazy counterpart.

 lazy  = from  strict 

See http://hackage.haskell.org/package/strict-base-types for an example use.

class Reversing t whereSource

This class provides a generalized notion of list reversal extended to other containers.

Methods

reversing :: t -> tSource

Instances

reversed :: Reversing a => Iso' a aSource

An Iso between a list, ByteString , Text fragment, etc. and its reversal.

>>> "live" ^. reversed
"evil"
>>> "live" & reversed %~ ('d':)
"lived"

involuted :: (a -> a) -> Iso' a aSource

Given a function that is its own inverse, this gives you an Iso using it in both directions.

 involuted join  iso 
>>> "live" ^. involuted reverse
"evil"
>>> "live" & involuted reverse %~ ('d':)
"lived"

Uncommon Isomorphisms

magma :: LensLike (Mafic a b) s t a b -> Iso s u (Magma Int t b a) (Magma j u c c)Source

This isomorphism can be used to inspect a Traversal to see how it associates the structure and it can also be used to bake the Traversal into a Magma so that you can traverse over it multiple times.

imagma :: Over (Indexed i) (Molten i a b) s t a b -> Iso s t' (Magma i t b a) (Magma j t' c c)Source

This isomorphism can be used to inspect an IndexedTraversal to see how it associates the structure and it can also be used to bake the IndexedTraversal into a Magma so that you can traverse over it multiple times with access to the original indices.

data Magma i t b a Source

This provides a way to peek at the internal structure of a Traversal or IndexedTraversal

Instances

Functor (Magma i t b)
Foldable (Magma i t b)
Traversable (Magma i t b)
(Show i, Show a) => Show (Magma i t b a)

Contravariant functors

contramapping :: Contravariant f => AnIso s t a b -> Iso (f a) (f b) (f s) (f t)Source

Lift an Iso into a Contravariant functor.

 contramapping :: Contravariant  f => Iso  s t a b -> Iso  (f a) (f b) (f s) (f t)
 contramapping :: Contravariant  f => Iso'  s a -> Iso'  (f a) (f s)

Profunctors

class Profunctor p where

Formally, the class Profunctor represents a profunctor from Hask -> Hask.

Intuitively it is a bifunctor where the first argument is contravariant and the second argument is covariant.

You can define a Profunctor by either defining dimap or by defining both lmap and rmap .

If you supply dimap , you should ensure that:

dimap  id  id id 

If you supply lmap and rmap , ensure:

 lmap  id id 
 rmap  id id 

If you supply both, you should also ensure:

dimap  f g ≡ lmap  f .  rmap  g

These ensure by parametricity:

 dimap  (f .  g) (h .  i) ≡ dimap  g h .  dimap  f i
 lmap  (f .  g) ≡ lmap  g .  lmap  f
 rmap  (f .  g) ≡ rmap  f .  rmap  g

Methods

dimap :: (a -> b) -> (c -> d) -> p b c -> p a d

Map over both arguments at the same time.

dimap  f g ≡ lmap  f .  rmap  g

lmap :: (a -> b) -> p b c -> p a c

Map the first argument contravariantly.

lmap  f ≡ dimap  f id 

rmap :: (b -> c) -> p a b -> p a c

Map the second argument covariantly.

rmap dimap  id 

Instances

dimapping :: Profunctor p => AnIso s t a b -> AnIso s' t' a' b' -> Iso (p a s') (p b t') (p s a') (p t b')Source

Lift two Iso s into both arguments of a Profunctor simultaneously.

 dimapping :: Profunctor  p => Iso  s t a b -> Iso  s' t' a' b' -> Iso  (p a s') (p b t') (p s a') (p t b')
 dimapping :: Profunctor  p => Iso'  s a -> Iso'  s' a' -> Iso'  (p a s') (p s a')

lmapping :: Profunctor p => AnIso s t a b -> Iso (p a x) (p b y) (p s x) (p t y)Source

Lift an Iso contravariantly into the left argument of a Profunctor .

 lmapping :: Profunctor  p => Iso  s t a b -> Iso  (p a x) (p b y) (p s x) (p t y)
 lmapping :: Profunctor  p => Iso'  s a -> Iso'  (p a x) (p s x)

rmapping :: Profunctor p => AnIso s t a b -> Iso (p x s) (p y t) (p x a) (p y b)Source

Lift an Iso covariantly into the right argument of a Profunctor .

 rmapping :: Profunctor  p => Iso  s t a b -> Iso  (p x s) (p y t) (p x a) (p y b)
 rmapping :: Profunctor  p => Iso'  s a -> Iso'  (p x s) (p x a)

Bifunctors

bimapping :: Bifunctor f => AnIso s t a b -> AnIso s' t' a' b' -> Iso (f s s') (f t t') (f a a') (f b b')Source

Lift two Iso s into both arguments of a Bifunctor .

 bimapping :: Profunctor  p => Iso  s t a b -> Iso  s' t' a' b' -> Iso  (p s s') (p t t') (p a a') (p b b')
 bimapping :: Profunctor  p => Iso'  s a -> Iso'  s' a' -> Iso'  (p s s') (p a a')

AltStyle によって変換されたページ (->オリジナル) /