| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Lens
Description
Module Lens include the most common objects for working with lenses.
Synopsis
- type Getter s a = forall (f :: Type -> Type). (Contravariant f, Functor f) => (a -> f a) -> s -> f s
- type Getting r s a = (a -> Const r a) -> s -> Const r s
- type Setter s t a b = forall (f :: Type -> Type). Settable f => (a -> f b) -> s -> f t
- type ASetter s t a b = (a -> Identity b) -> s -> Identity t
- type Traversal' s a = Traversal s s a a
- (^.) :: s -> Getting a s a -> a
- to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a
- view :: MonadReader s m => Getting a s a -> m a
- views :: MonadReader s m => LensLike' (Const r :: Type -> Type) s a -> (a -> r) -> m r
- use :: MonadState s m => Getting a s a -> m a
- uses :: MonadState s m => LensLike' (Const r :: Type -> Type) s a -> (a -> r) -> m r
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- (%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
- (.~) :: ASetter s t a b -> b -> s -> t
- (.=) :: MonadState s m => ASetter s s a b -> b -> m ()
- _1 :: Field1 s t a b => Lens s t a b
- _2 :: Field2 s t a b => Lens s t a b
- both :: forall (r :: Type -> Type -> Type) a b. Bitraversable r => Traversal (r a a) (r b b) a b
- (&) :: a -> (a -> b) -> b
- makeLenses :: Name -> DecsQ
- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
Documentation
type Getter s a = forall (f :: Type -> Type). (Contravariant f, Functor f) => (a -> f a) -> s -> f s #
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 Getting r s a = (a -> Const r a) -> s -> Const r s #
When you see this in a type signature it indicates that you can
pass the function a Lens, Getter,
Traversal, Fold,
Prism, Iso, or one of
the indexed variants, and it will just "do the right thing".
Most Getter combinators are able to be used with both a Getter or a
Fold in limited situations, to do so, they need to be
monomorphic in what we are going to extract with Const. To be compatible
with Lens, Traversal and
Iso we also restricted choices of the irrelevant t and
b parameters.
If a function accepts a , then when Getting r s ar is a Monoid, then
you can pass a Fold (or
Traversal), otherwise you can only pass this a
Getter or Lens.
type Setter s t a b = forall (f :: Type -> Type). Settable f => (a -> f b) -> s -> f t #
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 ASetter s t a b = (a -> Identity b) -> s -> Identity t #
Running a Setter instantiates it to a concrete type.
When consuming a setter directly to perform a mapping, you can use this type, but most user code will not need to use this type.
type Traversal' s a = Traversal s s a a #
typeTraversal'=SimpleTraversal
(^.) :: s -> Getting a s a -> a infixl 8 #
View the value pointed to by a Getter or Lens or the
result of folding over all the results of a Fold or
Traversal that points at a monoidal values.
This is the same operation as view with the arguments flipped.
The fixity and semantics are such that subsequent field accesses can be
performed with (.).
>>>(a,b)^._2b
>>>("hello","world")^._2"world"
>>>import Data.Complex>>>((0, 1 :+ 2), 3)^._1._2.to magnitude2.23606797749979
(^.) :: s ->Getters a -> a (^.) ::Monoidm => s ->Folds m -> m (^.) :: s ->Iso's a -> a (^.) :: s ->Lens's a -> a (^.) ::Monoidm => s ->Traversal's m -> m
to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a #
view :: MonadReader s m => Getting a s a -> m a #
View the value pointed to by a Getter, Iso or
Lens or the result of folding over all the results of a
Fold or Traversal that points
at a monoidal value.
view.to≡id
>>>view (to f) af a
>>>view _2 (1,"hello")"hello"
>>>view (to succ) 56
>>>view (_2._1) ("hello",("world","!!!"))"world"
As view is commonly used to access the target of a Getter or obtain a monoidal summary of the targets of a Fold,
It may be useful to think of it as having one of these more restricted signatures:
view::Getters a -> s -> aview::Monoidm =>Folds m -> s -> mview::Iso's a -> s -> aview::Lens's a -> s -> aview::Monoidm =>Traversal's m -> s -> m
In a more general setting, such as when working with a Monad transformer stack you can use:
view::MonadReaders m =>Getters a -> m aview:: (MonadReaders m,Monoida) =>Folds a -> m aview::MonadReaders m =>Iso's a -> m aview::MonadReaders m =>Lens's a -> m aview:: (MonadReaders m,Monoida) =>Traversal's a -> m a
views :: MonadReader s m => LensLike' (Const r :: Type -> Type) s a -> (a -> r) -> m r #
View a function of the value pointed to by a Getter or Lens or the result of
folding over the result of mapping the targets of a Fold or
Traversal.
viewsl f ≡view(l.tof)
>>>views (to f) g ag (f a)
>>>views _2 length (1,"hello")5
As views is commonly used to access the target of a Getter or obtain a monoidal summary of the targets of a Fold,
It may be useful to think of it as having one of these more restricted signatures:
views::Getters a -> (a -> r) -> s -> rviews::Monoidm =>Folds a -> (a -> m) -> s -> mviews::Iso's a -> (a -> r) -> s -> rviews::Lens's a -> (a -> r) -> s -> rviews::Monoidm =>Traversal's a -> (a -> m) -> s -> m
In a more general setting, such as when working with a Monad transformer stack you can use:
views::MonadReaders m =>Getters a -> (a -> r) -> m rviews:: (MonadReaders m,Monoidr) =>Folds a -> (a -> r) -> m rviews::MonadReaders m =>Iso's a -> (a -> r) -> m rviews::MonadReaders m =>Lens's a -> (a -> r) -> m rviews:: (MonadReaders m,Monoidr) =>Traversal's a -> (a -> r) -> m r
views::MonadReaders m =>Gettingr s a -> (a -> r) -> m r
use :: MonadState s m => Getting a s a -> m a #
Use the target of a Lens, Iso, or
Getter in the current state, or use a summary of a
Fold or Traversal that points
to a monoidal value.
>>>evalState (use _1) (a,b)a
>>>evalState (use _1) ("hello","world")"hello"
use::MonadStates m =>Getters a -> m ause:: (MonadStates m,Monoidr) =>Folds r -> m ruse::MonadStates m =>Iso's a -> m ause::MonadStates m =>Lens's a -> m ause:: (MonadStates m,Monoidr) =>Traversal's r -> m r
uses :: MonadState s m => LensLike' (Const r :: Type -> Type) s a -> (a -> r) -> m r #
Use the target of a Lens, Iso or
Getter in the current state, or use a summary of a
Fold or Traversal that
points to a monoidal value.
>>>evalState (uses _1 length) ("hello","world")5
uses::MonadStates m =>Getters a -> (a -> r) -> m ruses:: (MonadStates m,Monoidr) =>Folds a -> (a -> r) -> m ruses::MonadStates m =>Lens's a -> (a -> r) -> m ruses::MonadStates m =>Iso's a -> (a -> r) -> m ruses:: (MonadStates m,Monoidr) =>Traversal's a -> (a -> r) -> m r
uses::MonadStates m =>Gettingr s t a b -> (a -> r) -> m r
(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 #
Modifies the target of a Lens or all of the targets of a Setter or
Traversal with a user supplied function.
This is an infix version of over.
fmapf ≡mapped%~ffmapDefaultf ≡traverse%~f
>>>(a,b,c) & _3 %~ f(a,b,f c)
>>>(a,b) & both %~ f(f a,f b)
>>>_2 %~ length $ (1,"hello")(1,5)
>>>traverse %~ f $ [a,b,c][f a,f b,f c]
>>>traverse %~ even $ [1,2,3][False,True,False]
>>>traverse.traverse %~ length $ [["hello","world"],["!!!"]][[5,5],[3]]
(%~) ::Setters t a b -> (a -> b) -> s -> t (%~) ::Isos t a b -> (a -> b) -> s -> t (%~) ::Lenss t a b -> (a -> b) -> s -> t (%~) ::Traversals t a b -> (a -> b) -> s -> t
(%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m () infix 4 #
Map over the target of a Lens or all of the targets of a Setter or Traversal in our monadic state.
>>>execState (do _1 %= f;_2 %= g) (a,b)(f a,g b)
>>>execState (do both %= f) (a,b)(f a,f b)
(%=) ::MonadStates m =>Iso's a -> (a -> a) -> m () (%=) ::MonadStates m =>Lens's a -> (a -> a) -> m () (%=) ::MonadStates m =>Traversal's a -> (a -> a) -> m () (%=) ::MonadStates m =>Setter's a -> (a -> a) -> m ()
(%=) ::MonadStates m =>ASetters s a b -> (a -> b) -> m ()
(.~) :: ASetter s t a b -> b -> s -> t infixr 4 #
Replace the target of a Lens or all of the targets of a Setter
or Traversal with a constant value.
This is an infix version of set, provided for consistency with (.=).
f<$a ≡mapped.~f$a
>>>(a,b,c,d) & _4 .~ e(a,b,c,e)
>>>(42,"world") & _1 .~ "hello"("hello","world")
>>>(a,b) & both .~ c(c,c)
(.~) ::Setters t a b -> b -> s -> t (.~) ::Isos t a b -> b -> s -> t (.~) ::Lenss t a b -> b -> s -> t (.~) ::Traversals t a b -> b -> s -> t
(.=) :: MonadState s m => ASetter s s a b -> b -> m () infix 4 #
Replace the target of a Lens or all of the targets of a Setter
or Traversal in our monadic state with a new value, irrespective of the
old.
This is an infix version of assign.
>>>execState (do _1 .= c; _2 .= d) (a,b)(c,d)
>>>execState (both .= c) (a,b)(c,c)
(.=) ::MonadStates m =>Iso's a -> a -> m () (.=) ::MonadStates m =>Lens's a -> a -> m () (.=) ::MonadStates m =>Traversal's a -> a -> m () (.=) ::MonadStates m =>Setter's a -> a -> m ()
It puts the state in the monad or it gets the hose again.
_1 :: Field1 s t a b => Lens s t a b #
Access the 1st field of a tuple (and possibly change its type).
>>>(1,2)^._11
>>>_1 .~ "hello" $ (1,2)("hello",2)
>>>(1,2) & _1 .~ "hello"("hello",2)
>>>_1 putStrLn ("hello","world")hello ((),"world")
This can also be used on larger tuples as well:
>>>(1,2,3,4,5) & _1 +~ 41(42,2,3,4,5)
_1::Lens(a,b) (a',b) a a'_1::Lens(a,b,c) (a',b,c) a a'_1::Lens(a,b,c,d) (a',b,c,d) a a' ..._1::Lens(a,b,c,d,e,f,g,h,i) (a',b,c,d,e,f,g,h,i) a a'
_2 :: Field2 s t a b => Lens s t a b #
Access the 2nd field of a tuple.
>>>_2 .~ "hello" $ (1,(),3,4)(1,"hello",3,4)
>>>(1,2,3,4) & _2 *~ 3(1,6,3,4)
>>>_2 print (1,2)2 (1,())
anyOf_2:: (s ->Bool) -> (a, s) ->Booltraverse._2:: (Applicativef,Traversablet) => (a -> f b) -> t (s, a) -> f (t (s, b))foldMapOf(traverse._2) :: (Traversablet,Monoidm) => (s -> m) -> t (b, s) -> m
both :: forall (r :: Type -> Type -> Type) a b. Bitraversable r => Traversal (r a a) (r b b) a b #
Traverse both parts of a Bitraversable container with matching types.
Usually that type will be a pair. Use each to traverse
the elements of arbitrary homogeneous tuples.
>>>(1,2) & both *~ 10(10,20)
>>>over both length ("hello","world")(5,5)
>>>("hello","world")^.both"helloworld"
both::Traversal(a, a) (b, b) a bboth::Traversal(Eithera a) (Eitherb b) a b
makeLenses :: Name -> DecsQ #
Build lenses (and traversals) with a sensible default configuration.
e.g.
data FooBar
= Foo { _x, _y :: Int }
| Bar { _x :: Int }
makeLenses ''FooBar
will create
x ::Lens'FooBarIntx f (Foo a b) = (\a' -> Foo a' b) <$> f a x f (Bar a) = Bar <$> f a y ::Traversal'FooBarInty f (Foo a b) = (\b' -> Foo a b') <$> f b y _ c@(Bar _) = pure c
makeLenses=makeLensesWithlensRules