Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class (MonadState s m, MonadState t n) => Zoom m n s t | m -> s, n -> t, m t -> n, n s -> m where
- class (MonadReader b m, MonadReader a n) => Magnify m n b a | m -> b, n -> a, m a -> n, n b -> m where
- magnify :: Is k A_Getter => Optic' k is a b -> m c -> n c
- magnifyMaybe :: Is k An_AffineFold => Optic' k is a b -> m c -> n (Maybe c)
- class (MonadReader b m, MonadReader a n, Magnify m n b a) => MagnifyMany m n b a | m -> b, n -> a, m a -> n, n b -> m where
- magnifyMany :: (Is k A_Fold, Monoid c) => Optic' k is a b -> m c -> n c
Zoom
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 zoom
in, changing the State
supplied by many
different monad transformers, potentially quite deep in a monad transformer
stack.
Its functions can be used to run a monadic action in a larger State
than it
was defined in, using a Lens'
, an AffineTraversal'
or a Traversal'
.
This is commonly used to lift actions in a simpler State
Monad
into a
State
Monad
with a larger State
type.
When used with 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 L.evalState ('a','b') $ zoom _1 $ use equality
'a'
>>>
flip S.execState ('a','b') $ zoom _1 $ equality .= 'c'
('c','b')
>>>
flip L.execState [(1,2),(3,4)] $ zoomMany traversed $ _2 %= (*10)
[(1,20),(3,40)]
>>>
flip S.runState [('a',"b"),('c',"d")] $ zoomMany traversed $ _2 <%= (\x -> x <> x)
("bbdd",[('a',"bb"),('c',"dd")])
>>>
flip S.evalState ("a","b") $ zoomMany each (use equality)
"ab"
zoom :: Is k A_Lens => Optic' k is t s -> m c -> n c infixr 2 Source #
zoomMaybe :: Is k An_AffineTraversal => Optic' k is t s -> m c -> n (Maybe c) infixr 2 Source #
zoomMany :: (Is k A_Traversal, Monoid c) => Optic' k is t s -> m c -> n c infixr 2 Source #
Instances
Zoom m n s t => Zoom (ListT m) (ListT n) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> ListT m c -> ListT n c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> ListT m c -> ListT n (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> ListT m c -> ListT n c Source # | |
Zoom m n s t => Zoom (MaybeT m) (MaybeT n) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> MaybeT m c -> MaybeT n c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> MaybeT m c -> MaybeT n (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> MaybeT m c -> MaybeT n c Source # | |
Zoom m n s t => Zoom (IdentityT m) (IdentityT n) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> IdentityT m c -> IdentityT n c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> IdentityT m c -> IdentityT n (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> IdentityT m c -> IdentityT n c Source # | |
(Error e, Zoom m n s t) => Zoom (ErrorT e m) (ErrorT e n) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> ErrorT e m c -> ErrorT e n c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> ErrorT e m c -> ErrorT e n (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> ErrorT e m c -> ErrorT e n c Source # | |
Zoom m n s t => Zoom (ExceptT e m) (ExceptT e n) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> ExceptT e m c -> ExceptT e n c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> ExceptT e m c -> ExceptT e n (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> ExceptT e m c -> ExceptT e n c Source # | |
Zoom m n s t => Zoom (ReaderT e m) (ReaderT e n) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> ReaderT e m c -> ReaderT e n c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> ReaderT e m c -> ReaderT e n (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> ReaderT e m c -> ReaderT e n c Source # | |
Monad m => Zoom (StateT s m) (StateT t m) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> StateT s m c -> StateT t m c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> StateT s m c -> StateT t m (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> StateT s m c -> StateT t m c Source # | |
Monad m => Zoom (StateT s m) (StateT t m) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> StateT s m c -> StateT t m c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> StateT s m c -> StateT t m (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> StateT s m c -> StateT t m c Source # | |
(Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> WriterT w m c -> WriterT w n c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> WriterT w m c -> WriterT w n (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> WriterT w m c -> WriterT w n c Source # | |
(Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> WriterT w m c -> WriterT w n c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> WriterT w m c -> WriterT w n (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> WriterT w m c -> WriterT w n c Source # | |
(Monoid w, Monad m) => Zoom (RWST r w s m) (RWST r w t m) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> RWST r w s m c -> RWST r w t m c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> RWST r w s m c -> RWST r w t m (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> RWST r w s m c -> RWST r w t m c Source # | |
(Monoid w, Monad m) => Zoom (RWST r w s m) (RWST r w t m) s t Source # | |
Defined in Optics.Zoom zoom :: forall k (is :: IxList) c. Is k A_Lens => Optic' k is t s -> RWST r w s m c -> RWST r w t m c Source # zoomMaybe :: forall k (is :: IxList) c. Is k An_AffineTraversal => Optic' k is t s -> RWST r w s m c -> RWST r w t m (Maybe c) Source # zoomMany :: forall k c (is :: IxList). (Is k A_Traversal, Monoid c) => Optic' k is t s -> RWST r w s m c -> RWST r w t m c Source # |
Magnify
class (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 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.
Its functions can be used to run a monadic action in a larger environment
than it was defined in, using a Getter
or an AffineFold
.
They act like local
, but can in many cases
change the type of the environment as well.
They're commonly used to lift actions in a simpler Reader
Monad
into a
Monad
with a larger environment type.
They can be used to edit pretty much any Monad
transformer stack with an
environment in it:
>>>
(1,2) & magnify _2 (+1)
3
>>>
flip runReader (1,2) $ magnify _1 ask
1
>>>
flip runReader (1,2,[10..20]) $ magnifyMaybe (_3 % _tail) ask
Just [11,12,13,14,15,16,17,18,19,20]
magnify :: Is k A_Getter => Optic' k is a b -> m c -> n c infixr 2 Source #
magnifyMaybe :: Is k An_AffineFold => Optic' k is a b -> m c -> n (Maybe c) infixr 2 Source #
Instances
Magnify m n b a => Magnify (ListT m) (ListT n) b a Source # | |
Magnify m n b a => Magnify (MaybeT m) (MaybeT n) b a Source # | |
Magnify m n b a => Magnify (IdentityT m) (IdentityT n) b a Source # | |
(Error e, Magnify m n b a) => Magnify (ErrorT e m) (ErrorT e n) b a Source # | |
Magnify m n b a => Magnify (ExceptT e m) (ExceptT e n) b a Source # | |
Monad m => Magnify (ReaderT b m) (ReaderT a m) b a Source # | |
Magnify m n b a => Magnify (StateT s m) (StateT s n) b a Source # | |
Magnify m n b a => Magnify (StateT s m) (StateT s n) b a Source # | |
(Monoid w, Magnify m n b a) => Magnify (WriterT w m) (WriterT w n) b a Source # | |
(Monoid w, Magnify m n b a) => Magnify (WriterT w m) (WriterT w n) b a Source # | |
Magnify ((->) b :: Type -> Type) ((->) a :: Type -> Type) 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 (MonadReader b m, MonadReader a n, Magnify m n b a) => MagnifyMany m n b a | m -> b, n -> a, m a -> n, n b -> m where Source #
Extends Magnify
with an ability to magnify using a Fold
over multiple
targets so that actions for each one are executed sequentially and the
results are aggregated.
There is however no sensible instance of MagnifyMany
for StateT
.
Instances
MagnifyMany m n b a => MagnifyMany (ListT m) (ListT n) b a Source # | |
MagnifyMany m n b a => MagnifyMany (MaybeT m) (MaybeT n) b a Source # | |
MagnifyMany m n b a => MagnifyMany (IdentityT m) (IdentityT n) b a Source # | |
(Error e, MagnifyMany m n b a) => MagnifyMany (ErrorT e m) (ErrorT e n) b a Source # | |
MagnifyMany m n b a => MagnifyMany (ExceptT e m) (ExceptT e n) b a Source # | |
Monad m => MagnifyMany (ReaderT b m) (ReaderT a m) b a Source # | |
(Monoid w, MagnifyMany m n b a) => MagnifyMany (WriterT w m) (WriterT w n) b a Source # | |
(Monoid w, MagnifyMany m n b a) => MagnifyMany (WriterT w m) (WriterT w n) b a Source # | |
MagnifyMany ((->) b :: Type -> Type) ((->) a :: Type -> Type) b a Source # |
|
Defined in Optics.Zoom | |
(Monad m, Monoid w) => MagnifyMany (RWST b w s m) (RWST a w s m) b a Source # | |
(Monad m, Monoid w) => MagnifyMany (RWST b w s m) (RWST a w s m) b a Source # | |