Portability | Rank2Types |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
- class (MonadReader b m, MonadReader a n) => Magnify m n k b a | m -> b, n -> a, m a -> n, n b -> m where
- magnify :: ((b -> k c b) -> a -> k c a) -> m c -> n c
- class (MonadState s m, MonadState t n) => Zoom m n k s t | m -> s k, n -> t k, m t -> n, n s -> m where
- zoom :: SimpleLensLike (k c) t s -> m c -> n c
Documentation
class (MonadReader b m, MonadReader a n) => Magnify m n k b a | m -> b, n -> a, m a -> n, n b -> m whereSource
This class allows us to use magnify
part of the environment, changing the environment supplied by
many different monad transformers. Unlike zoom
this can change the environment of a deeply nested monad transformer.
Also, unlike zoom
, this can be used with any valid Getter
, but cannot be used with a Traversal
or Fold
.
magnify :: ((b -> k c b) -> a -> k c a) -> m c -> n cSource
Run a monadic action in a larger environment than it was defined in, using a Getter
.
This acts like local
, but can in many cases change the type of the environment as well.
This is commonly used to lift actions in a simpler Reader monad into a monad with a larger environment type.
This can be used to edit pretty much any monad transformer stack with an environment in it:
magnify
::Getter
s a -> (a -> r) -> s -> rmagnify
::Monoid
c =>Fold
s a -> (a -> r) -> s -> rmagnify
::Monoid
wGetter
s t ->RWST
s w st c ->RWST
t w st cmagnify
:: (Monoid
w,Monoid
c) =>Fold
s t ->RWST
s w st c ->RWST
t w st c ...
(MonadReader b ((->) b), MonadReader a ((->) a)) => Magnify ((->) b) ((->) a) Accessor b a |
|
(MonadReader b (IdentityT m), MonadReader a (IdentityT n), Magnify m n k b a) => Magnify (IdentityT m) (IdentityT n) k b a | |
(MonadReader b (ReaderT b m), MonadReader a (ReaderT a m), Monad m) => Magnify (ReaderT b m) (ReaderT a m) (Effect m) b a | |
(MonadReader b (RWST b w s m), MonadReader a (RWST a w s m), Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) (EffectRWS w s m) b a | |
(MonadReader b (RWST b w s m), MonadReader a (RWST a w s m), Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) (EffectRWS w s m) b a |
class (MonadState s m, MonadState t n) => Zoom m n k s t | m -> s k, n -> t k, m t -> n, n s -> m whereSource
This class allows us to use zoom
in, changing the State supplied by
many different monad transformers, potentially quite deep in a monad transformer stack.
zoom :: SimpleLensLike (k c) t s -> m c -> n cSource
Run a monadic action in a larger state than it was defined in,
using a Simple
Lens
or Simple
Traversal
.
This is commonly used to lift actions in a simpler state monad into a state monad with a larger state type.
When applied to a 'Simple Traversal
over
multiple values, the actions for each target are executed sequentially
and the results are aggregated.
This can be used to edit pretty much any monad transformer stack with a state in it!
>>>
flip State.evalState (a,b) $ zoom _1 $ use id
a
>>>
flip State.execState (a,b) $ zoom _1 $ id .= c
(c,b)
>>>
flip State.execState [(a,b),(c,d)] $ zoom traverse $ _2 %= f
[(a,f b),(c,f d)]
>>>
flip State.runState [(a,b),(c,d)] $ zoom traverse $ _2 <%= f
(f b <> f d <> mempty,[(a,f b),(c,f d)])
>>>
flip State.evalState (a,b) $ zoom both (use id)
a <> b
zoom
::Monad
m =>Simple
Lens
s t ->StateT
t m a ->StateT
s m azoom
:: (Monad
m,Monoid
c) =>Simple
Traversal
s t ->StateT
t m c ->StateT
s m czoom
::Monad
m =>Simple
Lens
s t ->RWST
r w t m c ->RWST
r w s m czoom
:: (Monad
m,Monoid
c) =>Simple
Traversal
s t ->RWST
r w t m c ->RWST
r w s m czoom
::Monad
m =>Simple
Lens
s t ->ErrorT
e (RWST
r w t m c) ->ErrorT
e (RWST
r w s m c)zoom
:: (Monad
m,Monoid
c) =>Simple
Traversal
s t ->ErrorT
e (RWST
r w t m c) ->ErrorT
e (RWST
r w s m c) ...