| Portability | Rank2Types | 
|---|---|
| Stability | provisional | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | Safe-Inferred | 
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.
- type Equality s t a b = forall p f. p a (f b) -> p s (f t)
- type Equality' s a = Equality s s a a
- type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t)
- type Iso' s a = Iso s s a a
- type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t)
- type Prism' s a = Prism s s a a
- type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
- type Lens' s a = Lens s s a a
- type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t
- type Traversal' s a = Traversal s s a a
- type Setter s t a b = forall f. Settable f => (a -> f b) -> s -> f t
- type Setter' s a = Setter s s a a
- type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s
- type Fold s a = forall f. (Contravariant f, Applicative f) => (a -> f a) -> s -> f s
- type Action m s a = forall f r. Effective m r f => (a -> f a) -> s -> f s
- type MonadicFold m s a = forall f r. (Effective m r f, Applicative f) => (a -> f a) -> s -> f s
- type IndexedLens i s t a b = forall f p. (Indexable i p, Functor f) => p a (f b) -> s -> f t
- type IndexedLens' i s a = IndexedLens i s s a a
- type IndexedTraversal i s t a b = forall p f. (Indexable i p, Applicative f) => p a (f b) -> s -> f t
- type IndexedTraversal' i s a = IndexedTraversal i s s a a
- type IndexedSetter i s t a b = forall f p. (Indexable i p, Settable f) => p a (f b) -> s -> f t
- type IndexedSetter' i s a = IndexedSetter i s s a a
- type IndexedGetter i s a = forall p f. (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f s
- type IndexedFold i s a = forall p f. (Indexable i p, Contravariant f, Applicative f) => p a (f a) -> s -> f s
- type IndexedAction i m s a = forall p f r. (Indexable i p, Effective m r f) => p a (f a) -> s -> f s
- type IndexedMonadicFold i m s a = forall p f r. (Indexable i p, Effective m r f, Applicative f) => p a (f a) -> s -> f s
- type IndexPreservingLens s t a b = forall p f. (Conjoined p, Functor f) => p a (f b) -> p s (f t)
- type IndexPreservingLens' s a = IndexPreservingLens s s a a
- type IndexPreservingTraversal s t a b = forall p f. (Conjoined p, Applicative f) => p a (f b) -> p s (f t)
- type IndexPreservingTraversal' s a = IndexPreservingTraversal s s a a
- type IndexPreservingSetter s t a b = forall p f. (Conjoined p, Settable f) => p a (f b) -> p s (f t)
- type IndexPreservingSetter' s a = IndexPreservingSetter s s a a
- type IndexPreservingGetter s a = forall p f. (Conjoined p, Contravariant f, Functor f) => p a (f a) -> p s (f s)
- type IndexPreservingFold s a = forall p f. (Conjoined p, Contravariant f, Applicative f) => p a (f a) -> p s (f s)
- type IndexPreservingAction m s a = forall p f r. (Conjoined p, Effective m r f) => p a (f a) -> p s (f s)
- type IndexPreservingMonadicFold m s a = forall p f r. (Conjoined p, Effective m r f, Applicative f) => p a (f a) -> p s (f s)
- type Simple f s a = f s s a a
- type LensLike f s t a b = (a -> f b) -> s -> f t
- type LensLike' f s a = LensLike f s s a a
- type Over p f s t a b = p a (f b) -> s -> f t
- type Over' p f s a = Over p f s s a a
- type IndexedLensLike i f s t a b = forall p. Indexable i p => p a (f b) -> s -> f t
- type IndexedLensLike' i f s a = IndexedLensLike i f s s a a
- type Overloading p q f s t a b = p a (f b) -> q s (f t)
- type Overloading' p q f s a = Overloading p q f s s a a
- type Overloaded p f s t a b = p a (f b) -> p s (f t)
- type Overloaded' p f s a = Overloaded p f s s a a
Other
type Equality s t a b = forall p f. 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 Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t)Source
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 0-or-1 target Traversal that can also be turned
 around with re to obtain a Getter in the
 opposite direction.
There are two 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:
previewl (reviewl b) ≡Justb
Second, if you can extract a value a using a Prism l from a value s, then the value s is completely described my l and a:
If preview l s ≡ Just areview l a ≡ s
These two laws imply that the Traversal laws hold for every Prism and that we traverse at most 1 element:
lengthOfl x<=1
It may help to think of this as a Iso that can be partial in one direction.
Every Prism is a valid Traversal.
For example, you might have a Prism' Integer NaturalNatural 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'IntegerNaturalnat=prismtoInteger$\ i -> if i<0 thenLefti elseRight(fromIntegeri)
Now we can ask if an Integer is a Natural.
>>>5^?natJust 5
>>>(-5)^?natNothing
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 -- :: Natural5
Similarly we can use a Prism to traverse the Left half of an Either:
>>>Left "hello" & _Left %~ lengthLeft 5
or to construct an Either:
>>>5^.re _LeftLeft 5
such that if you query it with the Prism, you will get your original input back.
>>>5^.re _Left ^? _LeftJust 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.
Lenses, Folds and Traversals
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f tSource
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:
viewl (setl b a) ≡ b
2) Putting back what you got doesn't change anything:
setl (viewl a) a ≡ a
3) Setting twice is the same as setting once:
setl c (setl b a) ≡setl c a
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/.
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:
lpure≡purefmap(l f).l g ≡getCompose.l (Compose.fmapf.g)
typeLenss t a b = forall f.Functorf =>LensLikef s t a b
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f tSource
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::Traversablef =>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".
tpure≡purefmap(t f).t g ≡getCompose.t (Compose.fmapf.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 Traversal' s a = Traversal s s a aSource
typeTraversal'=SimpleTraversal
type Setter s t a b = forall f. Settable f => (a -> f b) -> s -> f tSource
The only LensLike law that can apply to a Setter l is that
setl y (setl x a) ≡setl 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:
overlid≡idoverl f.overl g ≡overl (f.g)
These can be stated more directly:
lpure≡purel 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 Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f sSource
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 (a -> s).
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 sSource
A Fold describes how to retrieve multiple values in a way that can be composed
 with other LensLike constructions.
A Fold s aFoldable
 typeclass, see foldMapOf and the other Fold combinators.
By convention, if there exists a foo method that expects a Foldable (f a)fooOf method that takes a Fold s as.
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 MonadicFold m s a = forall f r. (Effective m r f, Applicative f) => (a -> f a) -> s -> f sSource
A MonadicFold is a Fold enriched with access to a Monad for side-effects.
Every Fold can be used as a MonadicFold, that simply ignores the access to the Monad.
You can compose a MonadicFold with another MonadicFold using (.) from the Prelude.
Indexed
type IndexedLens i s t a b = forall f p. (Indexable i p, Functor f) => p a (f b) -> s -> f tSource
Every IndexedLens is a valid Lens and a valid IndexedTraversal.
type IndexedLens' i s a = IndexedLens i s s a aSource
typeIndexedLens'i =Simple(IndexedLensi)
type IndexedTraversal i s t a b = forall p f. (Indexable i p, Applicative f) => p a (f b) -> s -> f tSource
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.
type IndexedTraversal' i s a = IndexedTraversal i s s a aSource
typeIndexedTraversal'i =Simple(IndexedTraversali)
type IndexedSetter i s t a b = forall f p. (Indexable i p, Settable f) => p a (f b) -> s -> f tSource
Every IndexedSetter is a valid Setter.
The Setter laws are still required to hold.
type IndexedSetter' i s a = IndexedSetter i s s a aSource
typeIndexedSetter'i =Simple(IndexedSetteri)
type IndexedGetter i s a = forall p f. (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f sSource
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 sSource
Every IndexedFold is a valid Fold and can be used for Getting.
type IndexedAction i m s a = forall p f r. (Indexable i p, Effective m r f) => p a (f a) -> s -> f sSource
An IndexedAction is an IndexedGetter enriched with access to a Monad for side-effects.
Every Getter can be used as an Action.
You can compose an Action with another Action using (.) from the Prelude.
type IndexedMonadicFold i m s a = forall p f r. (Indexable i p, Effective m r f, Applicative f) => p a (f a) -> s -> f sSource
An IndexedMonadicFold is an IndexedFold enriched with access to a Monad for side-effects.
Every IndexedFold can be used as an IndexedMonadicFold, that simply ignores the access to the Monad.
You can compose an IndexedMonadicFold with another IndexedMonadicFold using (.) from the Prelude.
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 IndexPreservingLens' s a = IndexPreservingLens s s a aSource
type IndexPreservingTraversal s t a b = forall p f. (Conjoined p, Applicative f) => p a (f b) -> p s (f t)Source
An IndexPreservingLens leaves any index it is composed with alone.
type IndexPreservingTraversal' s a = IndexPreservingTraversal s s a aSource
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 aSource
typeIndexedPreservingSetter'i =SimpleIndexedPreservingSetter
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 IndexPreservingAction m s a = forall p f r. (Conjoined p, Effective m r f) => p a (f a) -> p s (f s)Source
An IndexPreservingAction can be used as a Action, but when composed with an IndexedTraversal,
 IndexedFold, or IndexedLens yields an IndexedMonadicFold, IndexedMonadicFold or IndexedAction respectively.
type IndexPreservingMonadicFold m s a = forall p f r. (Conjoined p, Effective m r 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.
Common
type Simple f s a = f s s a aSource
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::SimpleLens(Complexa) atraversed::Simple(IndexedTraversalInt) [a] a
Note: To use this alias in your own code with LensLike fSetter, 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 tSource
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 bFunctor f,
 then they may be passed a Lens.
Further, if f is an Applicative, they may also be passed a
 Traversal.
type Over p f s t a b = p a (f b) -> s -> f tSource
This is a convenient alias for use when you need to consume either indexed or non-indexed lens-likes based on context.
type IndexedLensLike i f s t a b = forall p. Indexable i p => p a (f b) -> s -> f tSource
Convenient alias for constructing indexed lenses and their ilk.
type IndexedLensLike' i f s a = IndexedLensLike i f s s a aSource
Convenient alias for constructing simple indexed lenses and their ilk.
type Overloading p q f s t a b = p a (f b) -> q s (f t)Source
typeLensLikef s t a b =Overloading(->) (->) f s t a b
type Overloading' p q f s a = Overloading p q f s s a aSource
typeOverloading'p q f s a =Simple(Overloadingp q f) s a
type Overloaded p f s t a b = p a (f b) -> p s (f t)Source
typeLensLikef s t a b =Overloaded(->) f s t a b
type Overloaded' p f s a = Overloaded p f s s a aSource
typeOverloaded'p q f s a =Simple(Overloadedp q f) s a