lens-3.5.1: Lenses, Folds and Traversals

PortabilityRank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Control.Lens.Zoom

Description

 

Synopsis

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.

Methods

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 -> r
 magnify :: Monoid c => Fold s a   -> (a -> r) -> s -> r
 magnify :: Monoid w                Getter s t -> RWST s w st c -> RWST t w st c
 magnify :: (Monoid w, Monoid c) => Fold s t   -> RWST s w st c -> RWST t w st c
 ...

Instances

(MonadReader b ((->) b), MonadReader a ((->) a)) => Magnify ((->) b) ((->) a) Accessor b a
magnify = views
(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.

Methods

zoom :: Monad m => 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!

 zoom :: Monad m             => Simple Lens s t      -> StateT t m a -> StateT s m a
 zoom :: (Monad m, Monoid c) => Simple Traversal s t -> StateT t m c -> StateT s m c
 zoom :: Monad m             => Simple Lens s t      -> RWST r w t m c -> RWST r w s m c
 zoom :: (Monad m, Monoid c) => Simple Traversal s t -> RWST r w t m c -> RWST r w s m c
 zoom :: 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)
 ...

Instances

(MonadState s (IdentityT m), MonadState t (IdentityT n), Zoom m n k s t) => Zoom (IdentityT m) (IdentityT n) k s t 
(MonadState s (MaybeT m), MonadState t (MaybeT n), Zoom m n k s t) => Zoom (MaybeT m) (MaybeT n) (FocusingMay k) s t 
(MonadState s (ListT m), MonadState t (ListT n), Zoom m n k s t) => Zoom (ListT m) (ListT n) (FocusingOn [] k) s t 
(MonadState s (ReaderT e m), MonadState t (ReaderT e n), Zoom m n k s t) => Zoom (ReaderT e m) (ReaderT e n) k s t 
(MonadState s (StateT s z), MonadState t (StateT t z), Monad z) => Zoom (StateT s z) (StateT t z) (Focusing z) s t 
(MonadState s (StateT s z), MonadState t (StateT t z), Monad z) => Zoom (StateT s z) (StateT t z) (Focusing z) s t 
(MonadState s (ErrorT e m), MonadState t (ErrorT e n), Error e, Zoom m n k s t) => Zoom (ErrorT e m) (ErrorT e n) (FocusingErr e k) s t 
(MonadState s (WriterT w m), MonadState t (WriterT w n), Monoid w, Zoom m n k s t) => Zoom (WriterT w m) (WriterT w n) (FocusingPlus w k) s t 
(MonadState s (WriterT w m), MonadState t (WriterT w n), Monoid w, Zoom m n k s t) => Zoom (WriterT w m) (WriterT w n) (FocusingPlus w k) s t 
(MonadState s (RWST r w s z), MonadState t (RWST r w t z), Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) (FocusingWith w z) s t 
(MonadState s (RWST r w s z), MonadState t (RWST r w t z), Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) (FocusingWith w z) s t