Portability | Rank2Types |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Safe-Infered |
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
type Setter a b c d = (c -> Identity d) -> a -> Identity b
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
- (.=) :: 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 -> 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
adjust l id = id adjust l f . adjust l g = adjust l (f . g)
These an be stated more directly:
l pure = pure l f . run . l g = l (f . run . 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.
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.
Mutator | |
|
Building Setters
Common Setters
mapped :: Functor f => Setter (f a) (f b) a bSource
This setter can be used to map over all of the values in a Functor
.
fmap = adjust mapped fmapDefault = adjust traverse (<$) = set mapped
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 = adjust mapped fmapDefault = adjust traverse
sets . adjust = id adjust . sets = id
adjust :: Setter a b c d -> (c -> d) -> a -> b
Another way to view adjust
is to say that it transformers a Setter
into a
"semantic editor combinator".
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 = mapOf mapped fmapDefault = mapOf traverse
sets . mapOf = id mapOf . sets = id
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
set :: 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.
(<$) = set mapped
set :: Setter a b c d -> d -> a -> b set :: Iso a b c d -> d -> a -> b set :: Lens a b c d -> d -> a -> b set :: Traversal a b c d -> 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
ghci> bitAt 0 .~ True $ 0 1
(.~) :: 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
fmap f = mapped %~ f fmapDefault f = traverse %~ f
ghci> _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
(+~) :: Num c => Setting a b c c -> c -> a -> bSource
Increment the target(s) of a numerically valued Lens
, Setter' or Traversal
ghci> _1 +~ 1 $ (1,2) (2,2)
(-~) :: Num c => Setting a b c c -> c -> a -> bSource
Decrement the target(s) of a numerically valued Lens
, Iso
, Setter
or Traversal
>>>
_1 -~ 2 $ (1,2)
(-1,2)
(*~) :: Num c => Setting a b c c -> c -> a -> bSource
Multiply the target(s) of a numerically valued Lens
, Iso
, Setter
or Traversal
>>>
_2 *~ 4 $ (1,2)
(1,8)
(//~) :: Fractional c => Setting a b c c -> c -> a -> bSource
Divide the target(s) of a numerically valued Lens
, Iso
, Setter
or Traversal
(^~) :: (Num c, Integral e) => Setting a b c c -> e -> a -> bSource
Raise the target(s) of a numerically valued Lens
, Setter
or Traversal
to a non-negative integral power
>>>
_2 ^~ 2 $ (1,3)
(1,9)
(^^~) :: (Fractional c, Integral e) => Setting a b c c -> e -> a -> bSource
Raise the target(s) of a fractionally valued Lens
, Setter
or Traversal
to an integral power
>>>
_2 ^^~ (-1) $ (1,2)
(1,0.5)
(**~) :: Floating c => Setting a b c c -> c -> a -> bSource
Raise the target(s) of a floating-point valued Lens
, Setter
or Traversal
to an arbitrary power.
>>>
_2 **~ pi $ (1,3)
(1,31.54428070019754)
(<>~) :: Monoid c => Setting a b c c -> c -> a -> bSource
Modify the target of a monoidally valued by mappend
ing another value.
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
Modify the target(s) of a Simple
Lens
, Iso
, Setter
or Traversal
by adding a value
Example:
fresh = do id += 1 access id
(-=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()Source
Modify the target(s) of a Simple
Lens
, Iso
, Setter
or Traversal
by subtracting a value
(*=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()Source
Modify the target(s) of a Simple
Lens
, Iso
, Setter
or Traversal
by multiplying by value
(//=) :: (MonadState a m, Fractional b) => SimpleSetting a b -> b -> m ()Source
Modify the target(s) of a Simple
Lens
, Iso
, Setter
or Traversal
by dividing by a value
(^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m ()Source
Raise the target(s) of a numerically valued Lens
, Setter
or Traversal
to a non-negative integral power
(^^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m ()Source
Raise the target(s) of a numerically valued Lens
, Setter
or Traversal
to an integral power
(**=) :: (MonadState a m, Floating b) => SimpleSetting a b -> b -> m ()Source
Raise the target(s) of a numerically valued Lens
, Setter
or Traversal
to an arbitrary power
(||=) :: 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 -> 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 ...
will store the result in a lenssettertraversal.
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'