| Portability | Rank2Types |
|---|---|
| Stability | provisional |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | Safe-Infered |
Control.Lens.Setter
Contents
Description
A is a generalization of Setter a b c dfmap from Functor. It allows you to map into a
structure and change out the contents, but it isn't strong enough to allow you to
enumerate those contents. Starting with fmap ::
we monomorphize the type to obtain Functor f => (c -> d) -> f c -> f d(c -> d) -> a -> b and then decorate it with Identity to obtain
typeSettera b c d = (c ->Identityd) -> a ->Identityb
Every Traversal is a valid Setter, since Identity is Applicative.
Everything you can do with a Functor, you can do with a Setter. There
are combinators that generalize fmap and (<$).
- type Setter a b c d = forall f. Settable f => (c -> f d) -> a -> f b
- class Applicative f => Settable f where
- run :: f a -> a
- type Setting a b c d = (c -> Mutator d) -> a -> Mutator b
- newtype Mutator a = Mutator {
- runMutator :: a
- sets :: ((c -> d) -> a -> b) -> Setter a b c d
- mapped :: Functor f => Setter (f a) (f b) a b
- adjust :: Setting a b c d -> (c -> d) -> a -> b
- mapOf :: Setting a b c d -> (c -> d) -> a -> b
- set :: Setting a b c d -> d -> a -> b
- (.~) :: Setting a b c d -> d -> a -> b
- (%~) :: Setting a b c d -> (c -> d) -> a -> b
- (+~) :: Num c => Setting a b c c -> c -> a -> b
- (-~) :: Num c => Setting a b c c -> c -> a -> b
- (*~) :: Num c => Setting a b c c -> c -> a -> b
- (//~) :: Fractional c => Setting a b c c -> c -> a -> b
- (^~) :: (Num c, Integral e) => Setting a b c c -> e -> a -> b
- (^^~) :: (Fractional c, Integral e) => Setting a b c c -> e -> a -> b
- (**~) :: Floating c => Setting a b c c -> c -> a -> b
- (||~) :: Setting a b Bool Bool -> Bool -> a -> b
- (&&~) :: Setting a b Bool Bool -> Bool -> a -> b
- (<>~) :: Monoid c => Setting a b c c -> c -> a -> b
- (<.~) :: Setting a b c d -> d -> a -> (d, b)
- (.=) :: MonadState a m => Setting a a c d -> d -> m ()
- (%=) :: MonadState a m => Setting a a c d -> (c -> d) -> m ()
- (+=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()
- (-=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()
- (*=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()
- (//=) :: (MonadState a m, Fractional b) => SimpleSetting a b -> b -> m ()
- (^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m ()
- (^^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m ()
- (**=) :: (MonadState a m, Floating b) => SimpleSetting a b -> b -> m ()
- (||=) :: MonadState a m => SimpleSetting a Bool -> Bool -> m ()
- (&&=) :: MonadState a m => SimpleSetting a Bool -> Bool -> m ()
- (<>=) :: (MonadState a m, Monoid b) => SimpleSetting a b -> b -> m ()
- (<.=) :: MonadState a m => Setting a a c d -> d -> m d
- (<~) :: MonadState a m => Setting a a c d -> m d -> m ()
- whisper :: (MonadWriter b m, Monoid a) => Setting a b c d -> d -> m ()
- type SimpleSetter a b = Setter a a b b
- type SimpleSetting a b = Setting a a b b
Setters
type Setter a b c d = forall f. Settable f => (c -> f d) -> a -> f bSource
The only Lens-like law that can apply to a Setter l is that
set l c (set l b a) = set l c a
You can't view a Setter in general, so the other two laws are irrelevant.
However, two functor laws apply to a Setter:
These an be stated more directly:
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.
class Applicative f => Settable f whereSource
Anything Settable must be isomorphic to the Identity Functor.
Consuming Setters
type Setting a b c d = (c -> Mutator d) -> a -> Mutator bSource
Running a Setter instantiates it to a concrete type.
When consuming a setter, use this type.
Mutator is just a renamed Identity functor to give better error
messages when someone attempts to use a getter as a setter.
Constructors
| Mutator | |
Fields
| |
Building Setters
Common Setters
Functional Combinators
adjust :: Setting a b c d -> (c -> d) -> a -> bSource
Modify the target of a Lens or all the targets of a Setter or Traversal
with a function.
fmap=adjustmapped
fmapDefault=adjusttraverse
Free Theorems:
Another way to view adjust is to say that it transformers a Setter into a
"semantic editor combinator".
adjust::Settera b c d -> (c -> d) -> a -> b
mapOf :: Setting a b c d -> (c -> d) -> a -> bSource
Modify the target of a Lens or all the targets of a Setter or Traversal
with a function. This is an alias for adjust that is provided for consistency.
mapOf=adjust
fmap=mapOfmapped
fmapDefault=mapOftraverse
Free Theorems:
mapOf :: Setter a b c d -> (c -> d) -> a -> b mapOf :: Iso a b c d -> (c -> d) -> a -> b mapOf :: Lens a b c d -> (c -> d) -> a -> b mapOf :: Traversal a b c d -> (c -> d) -> a -> b
(.~) :: Setting a b c d -> d -> a -> bSource
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
>>>import Control.Lens>>>_1 .~ "hello" $ (42,"world")("hello","world")
(.~) :: Setter a b c d -> d -> a -> b (.~) :: Iso a b c d -> d -> a -> b (.~) :: Lens a b c d -> d -> a -> b (.~) :: Traversal a b c d -> d -> a -> b
(%~) :: Setting a b c d -> (c -> d) -> a -> bSource
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 adjust
fmapf =mapped%~f
fmapDefaultf =traverse%~f
>>>import Control.Lens>>>_2 %~ length $ (1,"hello")(1,5)
(%~) :: Setter a b c d -> (c -> d) -> a -> b (%~) :: Iso a b c d -> (c -> d) -> a -> b (%~) :: Lens a b c d -> (c -> d) -> a -> b (%~) :: Traversal a b c d -> (c -> d) -> a -> b
(//~) :: Fractional c => Setting a b c c -> c -> a -> bSource
(^^~) :: (Fractional c, Integral e) => Setting a b c c -> e -> a -> bSource
(<>~) :: Monoid c => Setting a b c c -> c -> a -> bSource
Modify the target of a monoidally valued by mappending another value.
(<.~) :: Setting a b c d -> d -> a -> (d, b)Source
Set with pass-through
This is mostly present for consistency, but may be useful for for chaining assignments
If you do not need a copy of the intermediate result, then using l .~ d directly is a good idea.
State Combinators
(.=) :: MonadState a m => Setting a a c d -> d -> m ()Source
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.
(.=) :: MonadState a m => Iso a a c d -> d -> m () (.=) :: MonadState a m => Lens a a c d -> d -> m () (.=) :: MonadState a m => Traversal a a c d -> d -> m () (.=) :: MonadState a m => Setter a a c d -> d -> m ()
(%=) :: MonadState a m => Setting a a c d -> (c -> d) -> m ()Source
Map over the target of a Lens or all of the targets of a Setter or Traversal in our monadic state.
(%=) :: MonadState a m => Iso a a c d -> (c -> d) -> m () (%=) :: MonadState a m => Lens a a c d -> (c -> d) -> m () (%=) :: MonadState a m => Traversal a a c d -> (c -> d) -> m () (%=) :: MonadState a m => Setter a a c d -> (c -> d) -> m ()
(+=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()Source
(-=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()Source
(*=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()Source
(//=) :: (MonadState a m, Fractional b) => SimpleSetting a b -> b -> m ()Source
(^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m ()Source
(^^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m ()Source
(**=) :: (MonadState a m, Floating b) => SimpleSetting a b -> b -> m ()Source
(||=) :: MonadState a m => SimpleSetting a Bool -> Bool -> m ()Source
(&&=) :: MonadState a m => SimpleSetting a Bool -> Bool -> m ()Source
(<>=) :: (MonadState a m, Monoid b) => SimpleSetting a b -> b -> m ()Source
(<.=) :: MonadState a m => Setting a a c d -> d -> m dSource
Set with pass-through
This is useful for chaining assignment
do x <- _2 <.= (an expensive expression)
If you do not need a copy of the intermediate result, then using l .= d will avoid unused binding warnings
(<~) :: MonadState a m => Setting a a c d -> m d -> m ()Source
Run a monadic action, and set all of the targets of a Lens, Setter or Traversal to its result.
(<~) :: MonadState a m => Iso a a c d -> m d -> m () (<~) :: MonadState a m => Lens a a c d -> m d -> m () (<~) :: MonadState a m => Traversal a a c d -> m d -> m () (<~) :: MonadState a m => Setter a a c d -> m d -> m ()
As a reasonable mnemonic, this lets you store the result of a monadic action in a lens rather than in a local variable.
do foo <- bar
...
will store the result in a variable, while
do foo <~ bar
...
MonadWriter
whisper :: (MonadWriter b m, Monoid a) => Setting a b c d -> d -> m ()Source
Tell a part of a value to a MonadWriter, filling in the rest from mempty
whisper l d = tell (set l d mempty)
Simplicity
type SimpleSetter a b = Setter a a b bSource
'SimpleSetter' = 'Simple' 'Setter'
type SimpleSetting a b = Setting a a b bSource
'SimpleSetting' m = 'Simple' 'Setting'