lens-5.2.3: Lenses, Folds and Traversals
Copyright(C) 2012-16 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
PortabilityRank2Types
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Lens.Type

Description

This module exports the majority of the types that need to appear in user signatures or in documentation when talking about lenses. The remaining types for consuming lenses are distributed across various modules in the hierarchy.

Synopsis

Other

type Equality (s :: k1) (t :: k2) (a :: k1) (b :: k2) = forall k3 (p :: k1 -> k3 -> Type) (f :: k2 -> k3). p a (f b) -> p s (f t) Source #

A witness that (a ~ s, b ~ t).

Note: Composition with an Equality is index-preserving.

type Equality' s a = Equality s s a a Source #

type As a = Equality' a a Source #

Composable asTypeOf. Useful for constraining excess polymorphism, foo . (id :: As Int) . bar.

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 Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t) Source #

A Prism l is a Traversal that can also be turned around with re to obtain a Getter in the opposite direction.

There are three laws that a Prism should satisfy:

First, if I re or review a value with a Prism and then preview or use (^?), I will get it back:

preview l (review l b) ≡ Just b

Second, if you can extract a value a using a Prism l from a value s, then the value s is completely described by l and a:

preview l s ≡ Just a ⟹ review l a ≡ s

Third, if you get non-match t, you can convert it result back to s:

matching l s ≡ Left t ⟹ matching l t ≡ Left s

The first two laws imply that the Traversal laws hold for every Prism and that we traverse at most 1 element:

lengthOf l x <= 1

It may help to think of this as an Iso that can be partial in one direction.

Every Prism is a valid Traversal.

Every Iso is a valid Prism.

For example, you might have a Prism' Integer Natural allows you to always go from a Natural to an Integer, and provide you with tools to check if an Integer is a Natural and/or to edit one if it is.

nat :: Prism' Integer Natural
nat = prism toInteger $ \ i ->
   if i < 0
   then Left i
   else Right (fromInteger i)

Now we can ask if an Integer is a Natural.

>>> 5^?nat
Just 5
>>> (-5)^?nat
Nothing

We can update the ones that are:

>>> (-3,4) & both.nat *~ 2
(-3,8)

And we can then convert from a Natural to an Integer.

>>> 5 ^. re nat -- :: Natural
5

Similarly we can use a Prism to traverse the Left half of an Either:

>>> Left "hello" & _Left %~ length
Left 5

or to construct an Either:

>>> 5^.re _Left
Left 5

such that if you query it with the Prism, you will get your original input back.

>>> 5^.re _Left ^? _Left
Just 5

Another interesting way to think of a Prism is as the categorical dual of a Lens -- a co-Lens, so to speak. This is what permits the construction of outside.

Note: Composition with a Prism is index-preserving.

type Prism' s a = Prism s s a a Source #

type Review t b = forall p f. (Choice p, Bifunctor p, Settable f) => Optic' p f t b Source #

This is a limited form of a Prism that can only be used for re operations.

Like with a Getter, there are no laws to state for a Review.

You can generate a Review by using unto. You can also use any Prism or Iso directly as a Review.

type AReview t b = Optic' Tagged Identity t b Source #

If you see this in a signature for a function, the function is expecting a Review (in practice, this usually means a Prism).

Lenses, Folds and Traversals

type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t Source #

A Lens is actually a lens family as described in http://comonad.com/reader/2012/mirrored-lenses/.

With great power comes great responsibility and a Lens is subject to the three common sense Lens laws:

1) You get back what you put in:

view l (set l v s)  ≡ v

2) Putting back what you got doesn't change anything:

set l (view l s) s  ≡ s

3) Setting twice is the same as setting once:

set l v' (set l v s) ≡ set l v' s

These laws are strong enough that the 4 type parameters of a Lens cannot vary fully independently. For more on how they interact, read the "Why is it a Lens Family?" section of http://comonad.com/reader/2012/mirrored-lenses/.

There are some emergent properties of these laws:

1) set l s must be injective for every s This is a consequence of law #1

2) set l must be surjective, because of law #2, which indicates that it is possible to obtain any v from some s such that set s v = s

3) Given just the first two laws you can prove a weaker form of law #3 where the values v that you are setting match:

set l v (set l v s) ≡ set l v s

Every Lens can be used directly as a Setter or Traversal.

You can also use a Lens for Getting as if it were a Fold or Getter.

Since every Lens is a valid Traversal, the Traversal laws are required of any Lens you create:

l purepure
fmap (l f) . l g ≡ getCompose . l (Compose . fmap f . g)
type Lens s t a b = forall f. Functor f => LensLike f s t a b

type Lens' s a = Lens s s a a Source #

type Lens' = Simple Lens

type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t Source #

A Traversal can be used directly as a Setter or a Fold (but not as a Lens) and provides the ability to both read and update multiple fields, subject to some relatively weak Traversal laws.

These have also been known as multilenses, but they have the signature and spirit of

traverse :: Traversable f => Traversal (f a) (f b) a b

and the more evocative name suggests their application.

Most of the time the Traversal you will want to use is just traverse, but you can also pass any Lens or Iso as a Traversal, and composition of a Traversal (or Lens or Iso) with a Traversal (or Lens or Iso) using (.) forms a valid Traversal.

The laws for a Traversal t follow from the laws for Traversable as stated in "The Essence of the Iterator Pattern".

t purepure
fmap (t f) . t g ≡ getCompose . t (Compose . fmap f . g)

One consequence of this requirement is that a Traversal needs to leave the same number of elements as a candidate for subsequent Traversal that it started with. Another testament to the strength of these laws is that the caveat expressed in section 5.5 of the "Essence of the Iterator Pattern" about exotic Traversable instances that traverse the same entry multiple times was actually already ruled out by the second law in that same paper!

type Traversal1 s t a b = forall f. Apply f => (a -> f b) -> s -> f t Source #

A Traversal which targets at least one element.

Note that since Apply is not a superclass of Applicative, a Traversal1 cannot always be used in place of a Traversal. In such circumstances cloneTraversal will convert a Traversal1 into a Traversal.

type Traversal1' s a = Traversal1 s s a a Source #

type Setter s t a b = forall f. Settable f => (a -> f b) -> s -> f t Source #

The only LensLike law that can apply to a Setter l is that

set l y (set l x a) ≡ set l y a

You can't view a Setter in general, so the other two laws are irrelevant.

However, two Functor laws apply to a Setter:

over l idid
over l f . over l g ≡ over l (f . g)

These can be stated more directly:

l purepure
l f . untainted . l g ≡ l (f . untainted . g)

You can compose a Setter with a Lens or a Traversal using (.) from the Prelude and the result is always only a Setter and nothing more.

>>> over traverse f [a,b,c,d]
[f a,f b,f c,f d]
>>> over _1 f (a,b)
(f a,b)
>>> over (traverse._1) f [(a,b),(c,d)]
[(f a,b),(f c,d)]
>>> over both f (a,b)
(f a,f b)
>>> over (traverse.both) f [(a,b),(c,d)]
[(f a,f b),(f c,f d)]

type Setter' s a = Setter s s a a Source #

A Setter' is just a Setter that doesn't change the types.

These are particularly common when talking about monomorphic containers. e.g.

sets Data.Text.map :: Setter' Text Char
type Setter' = Simple Setter

type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s Source #

A Getter describes how to retrieve a single value in a way that can be composed with other LensLike constructions.

Unlike a Lens a Getter is read-only. Since a Getter cannot be used to write back there are no Lens laws that can be applied to it. In fact, it is isomorphic to an arbitrary function from (s -> a).

Moreover, a Getter can be used directly as a Fold, since it just ignores the Applicative.

type Fold s a = forall f. (Contravariant f, Applicative f) => (a -> f a) -> s -> f s Source #

A Fold describes how to retrieve multiple values in a way that can be composed with other LensLike constructions.

A Fold s a provides a structure with operations very similar to those of the Foldable typeclass, see foldMapOf and the other Fold combinators.

By convention, if there exists a foo method that expects a Foldable (f a), then there should be a fooOf method that takes a Fold s a and a value of type s.

A Getter is a legal Fold that just ignores the supplied Monoid.

Unlike a Traversal a Fold is read-only. Since a Fold cannot be used to write back there are no Lens laws that apply.

type Fold1 s a = forall f. (Contravariant f, Apply f) => (a -> f a) -> s -> f s Source #

A relevant Fold (aka Fold1) has one or more targets.

Indexed

type IndexedLens i s t a b = forall f p. (Indexable i p, Functor f) => p a (f b) -> s -> f t Source #

Every IndexedLens is a valid Lens and a valid IndexedTraversal.

type IndexedLens' i s a = IndexedLens i s s a a Source #

type IndexedTraversal i s t a b = forall p f. (Indexable i p, Applicative f) => p a (f b) -> s -> f t Source #

Every IndexedTraversal is a valid Traversal or IndexedFold.

The Indexed constraint is used to allow an IndexedTraversal to be used directly as a Traversal.

The Traversal laws are still required to hold.

In addition, the index i should satisfy the requirement that it stays unchanged even when modifying the value a, otherwise traversals like indices break the Traversal laws.

type IndexedTraversal1 i s t a b = forall p f. (Indexable i p, Apply f) => p a (f b) -> s -> f t Source #

type IndexedSetter i s t a b = forall f p. (Indexable i p, Settable f) => p a (f b) -> s -> f t Source #

Every IndexedSetter is a valid Setter.

The Setter laws are still required to hold.

type IndexedGetter i s a = forall p f. (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f s Source #

Every IndexedGetter is a valid IndexedFold and can be used for Getting like a Getter.

type IndexedFold i s a = forall p f. (Indexable i p, Contravariant f, Applicative f) => p a (f a) -> s -> f s Source #

Every IndexedFold is a valid Fold and can be used for Getting.

type IndexedFold1 i s a = forall p f. (Indexable i p, Contravariant f, Apply f) => p a (f a) -> s -> f s Source #

Index-Preserving

type IndexPreservingLens s t a b = forall p f. (Conjoined p, Functor f) => p a (f b) -> p s (f t) Source #

An IndexPreservingLens leaves any index it is composed with alone.

type IndexPreservingTraversal s t a b = forall p f. (Conjoined p, Applicative f) => p a (f b) -> p s (f t) Source #

An IndexPreservingTraversal leaves any index it is composed with alone.

type IndexPreservingTraversal1 s t a b = forall p f. (Conjoined p, Apply f) => p a (f b) -> p s (f t) Source #

type IndexPreservingSetter s t a b = forall p f. (Conjoined p, Settable f) => p a (f b) -> p s (f t) Source #

An IndexPreservingSetter can be composed with a IndexedSetter, IndexedTraversal or IndexedLens and leaves the index intact, yielding an IndexedSetter.

type IndexPreservingSetter' s a = IndexPreservingSetter s s a a Source #

type IndexedPreservingSetter' i = Simple IndexedPreservingSetter

type IndexPreservingGetter s a = forall p f. (Conjoined p, Contravariant f, Functor f) => p a (f a) -> p s (f s) Source #

An IndexPreservingGetter can be used as a Getter, but when composed with an IndexedTraversal, IndexedFold, or IndexedLens yields an IndexedFold, IndexedFold or IndexedGetter respectively.

type IndexPreservingFold s a = forall p f. (Conjoined p, Contravariant f, Applicative f) => p a (f a) -> p s (f s) Source #

An IndexPreservingFold can be used as a Fold, but when composed with an IndexedTraversal, IndexedFold, or IndexedLens yields an IndexedFold respectively.

type IndexPreservingFold1 s a = forall p f. (Conjoined p, Contravariant f, Apply f) => p a (f a) -> p s (f s) Source #

Common

type Simple f s a = f s s a a Source #

A Simple Lens, Simple Traversal, ... can be used instead of a Lens,Traversal, ... whenever the type variables don't change upon setting a value.

_imagPart :: Simple Lens (Complex a) a
traversed :: Simple (IndexedTraversal Int) [a] a

Note: To use this alias in your own code with LensLike f or Setter, you may have to turn on LiberalTypeSynonyms.

This is commonly abbreviated as a "prime" marker, e.g. Lens' = Simple Lens.

type LensLike f s t a b = (a -> f b) -> s -> f t Source #

Many combinators that accept a Lens can also accept a Traversal in limited situations.

They do so by specializing the type of Functor that they require of the caller.

If a function accepts a LensLike f s t a b for some Functor f, then they may be passed a Lens.

Further, if f is an Applicative, they may also be passed a Traversal.

type LensLike' f s a = LensLike f s s a a Source #

type LensLike' f = Simple (LensLike f)

type Over p f s t a b = p a (f b) -> s -> f t Source #

This is a convenient alias for use when you need to consume either indexed or non-indexed lens-likes based on context.

type Over' p f s a = Over p f s s a a Source #

This is a convenient alias for use when you need to consume either indexed or non-indexed lens-likes based on context.

type Over' p f = Simple (Over p f)

type IndexedLensLike i f s t a b = forall p. Indexable i p => p a (f b) -> s -> f t Source #

Convenient alias for constructing indexed lenses and their ilk.

type IndexedLensLike' i f s a = IndexedLensLike i f s s a a Source #

Convenient alias for constructing simple indexed lenses and their ilk.

type Optical p q f s t a b = p a (f b) -> q s (f t) Source #

type LensLike f s t a b = Optical (->) (->) f s t a b
type Over p f s t a b = Optical p (->) f s t a b
type Optic p f s t a b = Optical p p f s t a b

type Optical' p q f s a = Optical p q f s s a a Source #

type Optical' p q f s a = Simple (Optical p q f) s a

type Optic p f s t a b = p a (f b) -> p s (f t) Source #

A valid Optic l should satisfy the laws:

l purepure
l (Procompose f g) = Procompose (l f) (l g)

This gives rise to the laws for Equality, Iso, Prism, Lens, Traversal, Traversal1, Setter, Fold, Fold1, and Getter as well along with their index-preserving variants.

type LensLike f s t a b = Optic (->) f s t a b

type Optic' p f s a = Optic p f s s a a Source #

type Optic' p f s a = Simple (Optic p f) s a