| Copyright | (C) 2012-16 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | Rank2Types | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Control.Lens.Zoom
Description
Synopsis
- type family Magnified (m :: * -> *) :: * -> * -> *
- 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 (MonadState s m, MonadState t n) => Zoom m n s t | m -> s, n -> t, m t -> n, n s -> m where
- type family Zoomed (m :: * -> *) :: * -> * -> *
Documentation
type family Magnified (m :: * -> *) :: * -> * -> * Source #
This type family is used by Magnify to describe the common effect type.
Instances
| type Magnified (IdentityT m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Magnified ((->) b :: * -> *) Source # | |
| type Magnified (ReaderT b m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Magnified (RWST a w s m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Magnified (RWST a w s m) Source # | |
| Defined in Control.Lens.Zoom | |
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 Source #
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.
Minimal complete definition
Methods
magnify :: LensLike' (Magnified m c) a b -> m c -> n c infixr 2 Source #
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.ask1
>>>flip Reader.runReader (1,2,[10..20]) $ magnify (_3._tail) Reader.ask[11,12,13,14,15,16,17,18,19,20]
magnify::Getters a -> (a -> r) -> s -> rmagnify::Monoidr =>Folds a -> (a -> r) -> s -> r
magnify::Monoidw =>Getters t ->RWSt w st c ->RWSs w st cmagnify:: (Monoidw,Monoidc) =>Folds a ->RWSa w st c ->RWSs w st c ...
Instances
| Magnify m n b a => Magnify (IdentityT m) (IdentityT n) b a Source # | |
| Magnify ((->) b :: * -> *) ((->) a :: * -> *) b a Source # | 
 | 
| Monad m => Magnify (ReaderT b m) (ReaderT a m) b a Source # | |
| (Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) b a Source # | |
| (Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) b a Source # | |
class (MonadState s m, MonadState t n) => Zoom m n s t | m -> s, n -> t, m t -> n, n s -> m where Source #
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.
Minimal complete definition
Methods
zoom :: LensLike' (Zoomed m c) t s -> m c -> n c infixr 2 Source #
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 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 ida
>>>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::Monadm =>Lens's t ->StateTt m a ->StateTs m azoom:: (Monadm,Monoidc) =>Traversal's t ->StateTt m c ->StateTs m czoom:: (Monadm,Monoidw) =>Lens's t ->RWSTr w t m c ->RWSTr w s m czoom:: (Monadm,Monoidw,Monoidc) =>Traversal's t ->RWSTr w t m c ->RWSTr w s m czoom:: (Monadm,Monoidw,Errore) =>Lens's t ->ErrorTe (RWSTr w t m) c ->ErrorTe (RWSTr w s m) czoom:: (Monadm,Monoidw,Monoidc,Errore) =>Traversal's t ->ErrorTe (RWSTr w t m) c ->ErrorTe (RWSTr w s m) c ...
Instances
| Zoom m n s t => Zoom (MaybeT m) (MaybeT n) s t Source # | |
| Zoom m n s t => Zoom (ListT m) (ListT n) s t Source # | |
| Zoom m n s t => Zoom (IdentityT m) (IdentityT n) s t Source # | |
| Zoom m n s t => Zoom (ExceptT e m) (ExceptT e n) s t Source # | |
| (Functor f, Zoom m n s t) => Zoom (FreeT f m) (FreeT f n) s t Source # | |
| (Error e, Zoom m n s t) => Zoom (ErrorT e m) (ErrorT e n) s t Source # | |
| Monad z => Zoom (StateT s z) (StateT t z) s t Source # | |
| Monad z => Zoom (StateT s z) (StateT t z) s t Source # | |
| (Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t Source # | |
| (Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t Source # | |
| Zoom m n s t => Zoom (ReaderT e m) (ReaderT e n) s t Source # | |
| (Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) s t Source # | |
| (Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) s t Source # | |
type family Zoomed (m :: * -> *) :: * -> * -> * Source #
This type family is used by Zoom to describe the common effect type.
Instances
| type Zoomed (MaybeT m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (ListT m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (IdentityT m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (ExceptT e m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (FreeT f m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (ErrorT e m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (StateT s z) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (StateT s z) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (WriterT w m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (WriterT w m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (ReaderT e m) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (RWST r w s z) Source # | |
| Defined in Control.Lens.Zoom | |
| type Zoomed (RWST r w s z) Source # | |
| Defined in Control.Lens.Zoom | |