lens-core-0.1.0.3: Lenses, Folds and Traversals

Copyright(C) 2012-16 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
PortabilityRank2Types, TypeFamilies, FunctionalDependencies
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Lens.Iso

Contents

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.

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 Source #

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 a Source #

Isomorphism Construction

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

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 s Source #

Invert an isomorphism.

from (from l) ≡ l

cloneIso :: AnIso s t a b -> Iso s t a b Source #

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 :: forall s t a b rep (r :: TYPE rep). AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> r Source #

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

Working with isomorphisms

au :: Functor f => AnIso s t a b -> ((b -> t) -> f s) -> f a Source #

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

You may want to think of this combinator as having the following, simpler type:

au :: AnIso s t a b -> ((b -> t) -> e -> s) -> e -> a
au = xplat . from

auf :: (Functor f, Functor g) => AnIso s t a b -> (f t -> g s) -> f b -> g a Source #

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.

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

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

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

but the signature is general.

Note: The direction of the Iso required for this function changed in lens 4.18 to match up with the behavior of au. For the old behavior use xplatf or for a version that is compatible across both old and new versions of lens you can just use coerce!

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

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

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

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

This can be used to lift any Iso into an arbitrary Functor.

Common Isomorphisms

simple :: Equality' a a Source #

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) a Source #

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.

nonnon' . 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 []

It can also be used in reverse to exclude a given value:

>>> non 0 # rem 10 4
Just 2
>>> non 0 # rem 10 5
Nothing

non' :: APrism' a () -> Iso' (Maybe a) a Source #

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) a Source #

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 a Source #

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 where Source #

This class provides for symmetric bifunctors.

Methods

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

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)
Instances
Swapped Either Source # 
Instance details

Defined in Control.Lens.Iso

Methods

swapped :: Iso (Either a b) (Either c d) (Either b a) (Either d c) Source #

Swapped (,) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

swapped :: Iso (a, b) (c, d) (b, a) (d, c) Source #

Swapped ((,,) x) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

swapped :: Iso (x, a, b) (x, c, d) (x, b, a) (x, d, c) Source #

Swapped ((,,,) x y) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

swapped :: Iso (x, y, a, b) (x, y, c, d) (x, y, b, a) (x, y, d, c) Source #

Swapped ((,,,,) x y z) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

swapped :: Iso (x, y, z, a, b) (x, y, z, c, d) (x, y, z, b, a) (x, y, z, d, c) Source #

Swapped p => Swapped (Dual p) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

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

Swapped ((,,,,,) x y z w) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

swapped :: Iso (x, y, z, w, a, b) (x, y, z, w, c, d) (x, y, z, w, b, a) (x, y, z, w, d, c) Source #

Swapped ((,,,,,,) x y z w v) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

swapped :: Iso (x, y, z, w, v, a, b) (x, y, z, w, v, c, d) (x, y, z, w, v, b, a) (x, y, z, w, v, d, c) Source #

(Functor f, Swapped p) => Swapped (Tannen f p) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

swapped :: Iso (Tannen f p a b) (Tannen f p c d) (Tannen f p b a) (Tannen f p d c) Source #

(f ~ g, Functor f, Swapped p) => Swapped (Biff p f g) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

swapped :: Iso (Biff p f g a b) (Biff p f g c d) (Biff p f g b a) (Biff p f g d c) Source #

pattern Swapped :: forall (p :: Type -> Type -> Type) c d. Swapped p => p d c -> p c d Source #

class Strict lazy strict | lazy -> strict, strict -> lazy where Source #

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

Methods

strict :: Iso' lazy strict Source #

Instances
Strict (ST s a) (ST s a) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

strict :: Iso' (ST s a) (ST0 s a) Source #

Strict (StateT s m a) (StateT s m a) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

strict :: Iso' (StateT0 s m a) (StateT s m a) Source #

Strict (WriterT w m a) (WriterT w m a) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

strict :: Iso' (WriterT0 w m a) (WriterT w m a) Source #

Strict (RWST r w s m a) (RWST r w s m a) Source # 
Instance details

Defined in Control.Lens.Iso

Methods

strict :: Iso' (RWST0 r w s m a) (RWST r w s m a) Source #

pattern Strict :: forall s t. Strict s t => t -> s Source #

pattern Lazy :: forall t s. Strict t s => t -> s Source #

lazy :: Strict lazy strict => Iso' strict lazy Source #

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 where Source #

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

Methods

reversing :: t -> t Source #

Instances
Reversing [a] Source # 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: [a] -> [a] Source #

Reversing (NonEmpty a) Source # 
Instance details

Defined in Control.Lens.Internal.Iso

Reversing (Seq a) Source # 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Seq a -> Seq a Source #

Unbox a => Reversing (Vector a) Source # 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a Source #

Storable a => Reversing (Vector a) Source # 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a Source #

Prim a => Reversing (Vector a) Source # 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a Source #

Reversing (Vector a) Source # 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a Source #

reversed :: Reversing a => Iso' a a Source #

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

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

pattern Reversed :: forall t. Reversing t => t -> t Source #

involuted :: (a -> a) -> Iso' a a Source #

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

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

pattern List :: forall l. IsList l => [Item l] -> l Source #

Uncommon Isomorphisms

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) Source # 
Instance details

Defined in Control.Lens.Internal.Magma

Methods

fmap :: (a -> b0) -> Magma i t b a -> Magma i t b b0 #

(<$) :: a -> Magma i t b b0 -> Magma i t b a #

Foldable (Magma i t b) Source # 
Instance details

Defined in Control.Lens.Internal.Magma

Methods

fold :: Monoid m => Magma i t b m -> m #

foldMap :: Monoid m => (a -> m) -> Magma i t b a -> m #

foldr :: (a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 #

foldr' :: (a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 #

foldl :: (b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 #

foldl' :: (b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 #

foldr1 :: (a -> a -> a) -> Magma i t b a -> a #

foldl1 :: (a -> a -> a) -> Magma i t b a -> a #

toList :: Magma i t b a -> [a] #

null :: Magma i t b a -> Bool #

length :: Magma i t b a -> Int #

elem :: Eq a => a -> Magma i t b a -> Bool #

maximum :: Ord a => Magma i t b a -> a #

minimum :: Ord a => Magma i t b a -> a #

sum :: Num a => Magma i t b a -> a #

product :: Num a => Magma i t b a -> a #

Traversable (Magma i t b) Source # 
Instance details

Defined in Control.Lens.Internal.Magma

Methods

traverse :: Applicative f => (a -> f b0) -> Magma i t b a -> f (Magma i t b b0) #

sequenceA :: Applicative f => Magma i t b (f a) -> f (Magma i t b a) #

mapM :: Monad m => (a -> m b0) -> Magma i t b a -> m (Magma i t b b0) #

sequence :: Monad m => Magma i t b (m a) -> m (Magma i t b a) #

(Show i, Show a) => Show (Magma i t b a) Source # 
Instance details

Defined in Control.Lens.Internal.Magma

Methods

showsPrec :: Int -> Magma i t b a -> ShowS #

show :: Magma i t b a -> String #

showList :: [Magma i t b a] -> ShowS #

Contravar.Functor functors

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

Lift an Iso into a Functor functor.

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

Profunctors

class Profunctor (p :: Type -> Type -> Type) where #

Minimal complete definition

Nothing

Methods

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

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

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

Instances
Profunctor ReifiedFold Source # 
Instance details

Defined in Control.Lens.Reified

Methods

dimap :: (a -> b) -> (c -> d) -> ReifiedFold b c -> ReifiedFold a d #

lmap :: (a -> b) -> ReifiedFold b c -> ReifiedFold a c #

rmap :: (b -> c) -> ReifiedFold a b -> ReifiedFold a c #

Profunctor ReifiedGetter Source # 
Instance details

Defined in Control.Lens.Reified

Methods

dimap :: (a -> b) -> (c -> d) -> ReifiedGetter b c -> ReifiedGetter a d #

lmap :: (a -> b) -> ReifiedGetter b c -> ReifiedGetter a c #

rmap :: (b -> c) -> ReifiedGetter a b -> ReifiedGetter a c #

Functor f => Profunctor (Kleisli f) 
Instance details

Defined in Data.Profunctor

Methods

dimap :: (a -> b) -> (c -> d) -> Kleisli f b c -> Kleisli f a d #

lmap :: (a -> b) -> Kleisli f b c -> Kleisli f a c #

rmap :: (b -> c) -> Kleisli f a b -> Kleisli f a c #

Profunctor (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor

Methods

dimap :: (a -> b) -> (c -> d) -> Tagged b c -> Tagged a d #

lmap :: (a -> b) -> Tagged b c -> Tagged a c #

rmap :: (b -> c) -> Tagged a b -> Tagged a c #

Profunctor ((->) :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor

Methods

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

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

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

Functor f => Profunctor (Cokleisli f) 
Instance details

Defined in Data.Profunctor

Methods

dimap :: (a -> b) -> (c -> d) -> Cokleisli f b c -> Cokleisli f a d #

lmap :: (a -> b) -> Cokleisli f b c -> Cokleisli f a c #

rmap :: (b -> c) -> Cokleisli f a b -> Cokleisli f a c #

Profunctor (Exchange a b) Source # 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Exchange a b b0 c -> Exchange a b a0 d #

lmap :: (a0 -> b0) -> Exchange a b b0 c -> Exchange a b a0 c #

rmap :: (b0 -> c) -> Exchange a b a0 b0 -> Exchange a b a0 c #

Profunctor (Market a b) Source # 
Instance details

Defined in Control.Lens.Internal.Prism

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Market a b b0 c -> Market a b a0 d #

lmap :: (a0 -> b0) -> Market a b b0 c -> Market a b a0 c #

rmap :: (b0 -> c) -> Market a b a0 b0 -> Market a b a0 c #

(Functor f, Profunctor p) => Profunctor (Tannen f p) 
Instance details

Defined in Data.Profunctor

Methods

dimap :: (a -> b) -> (c -> d) -> Tannen f p b c -> Tannen f p a d #

lmap :: (a -> b) -> Tannen f p b c -> Tannen f p a c #

rmap :: (b -> c) -> Tannen f p a b -> Tannen f p a c #

(Profunctor p, Functor f, Functor g) => Profunctor (Biff p f g) 
Instance details

Defined in Data.Profunctor

Methods

dimap :: (a -> b) -> (c -> d) -> Biff p f g b c -> Biff p f g a d #

lmap :: (a -> b) -> Biff p f g b c -> Biff p f g a c #

rmap :: (b -> c) -> Biff p f g a b -> Biff p f g a c #

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

Lift two Isos 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, Profunctor q) => AnIso s t a b -> Iso (p a x) (q b y) (p s x) (q 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, Profunctor q) => AnIso s t a b -> Iso (p x s) (q y t) (p x a) (q 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, Bifunctor g) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (f s s') (g t t') (f a a') (g b b') Source #

Lift two Isos into both arguments of a Bifunctor.

bimapping :: Bifunctor 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 :: Bifunctor p => Iso' s a -> Iso' s' a' -> Iso' (p s s') (p a a')

firsting :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f s x) (g t y) (f a x) (g b y) Source #

Lift an Iso into the first argument of a Bifunctor.

firsting :: Bifunctor p => Iso s t a b -> Iso (p s x) (p t y) (p a x) (p b y)
firsting :: Bifunctor p => Iso' s a -> Iso' (p s x) (p a x)

seconding :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f x s) (g y t) (f x a) (g y b) Source #

Lift an Iso into the second argument of a Bifunctor. This is essentially the same as mapping, but it takes a 'Bifunctor p' constraint instead of a 'Functor (p a)' one.

seconding :: Bifunctor p => Iso s t a b -> Iso (p x s) (p y t) (p x a) (p y b)
seconding :: Bifunctor p => Iso' s a -> Iso' (p x s) (p x a)

Coercions

coerced :: forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b Source #

Data types that are representationally equal are isomorphic.

This is only available on GHC 7.8+

Since: 4.13