Portability | Rank2Types |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
- class (Magnified m ~ Magnified n, MonadReader b m, MonadReader a n) => Magnify m n b a | m -> b, n -> a, m a -> n, n b -> m where
- class (Zoomed m ~ Zoomed n, MonadState s m, MonadState t n) => Zoom m n s t | m -> s, n -> t, m t -> n, n s -> m where
Documentation
class (Magnified m ~ Magnified n, MonadReader b m, MonadReader a n) => Magnify m n 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 :: LensLike' (Magnified m c) a b -> 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:
>>>
(1,2) & magnify _2 (+1)
3
>>>
flip Reader.runReader (1,2) $ magnify _1 Reader.ask
1
>>>
flip Reader.runReader (1,2,[10..20]) $ magnify (_3._tail) Reader.ask
[11,12,13,14,15,16,17,18,19,20]
magnify
::Getter
s a -> (a -> r) -> s -> rmagnify
::Monoid
r =>Fold
s a -> (a -> r) -> s -> r
magnify
::Monoid
w =>Getter
s t ->RWS
t w st c ->RWS
s w st cmagnify
:: (Monoid
w,Monoid
c) =>Fold
s a ->RWS
a w st c ->RWS
s w st c ...
class (Zoomed m ~ Zoomed n, MonadState s m, MonadState t n) => Zoom m n s t | m -> s, n -> t, 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 :: LensLike' (Zoomed m c) t s -> m c -> n cSource
Run a monadic action in a larger State
than it was defined in,
using a Lens'
or 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 =>Lens'
s t ->StateT
t m a ->StateT
s m azoom
:: (Monad
m,Monoid
c) =>Traversal'
s t ->StateT
t m c ->StateT
s m czoom
:: (Monad
m,Monoid
w) =>Lens'
s t ->RWST
r w t m c ->RWST
r w s m czoom
:: (Monad
m,Monoid
w,Monoid
c) =>Traversal'
s t ->RWST
r w t m c ->RWST
r w s m czoom
:: (Monad
m,Monoid
w,Error
e) =>Lens'
s t ->ErrorT
e (RWST
r w t m) c ->ErrorT
e (RWST
r w s m) czoom
:: (Monad
m,Monoid
w,Monoid
c,Error
e) =>Traversal'
s t ->ErrorT
e (RWST
r w t m) c ->ErrorT
e (RWST
r w s m) c ...
Zoom m n s t => Zoom (IdentityT m) (IdentityT n) s t | |
Zoom m n s t => Zoom (ListT m) (ListT n) s t | |
Zoom m n s t => Zoom (MaybeT m) (MaybeT n) s t | |
(Error e, Zoom m n s t) => Zoom (ErrorT e m) (ErrorT e n) s t | |
Zoom m n s t => Zoom (ReaderT e m) (ReaderT e n) s t | |
Monad z => Zoom (StateT s z) (StateT t z) s t | |
Monad z => Zoom (StateT s z) (StateT t z) s t | |
(Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t | |
(Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t | |
(Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) s t | |
(Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) s t |