{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
module Optics.Zoom
(
Zoom(..)
, Magnify(..)
, MagnifyMany(..)
) where
import Control.Monad.Reader (ReaderT (..), MonadReader)
import Control.Monad.State (MonadState (..))
import Control.Monad.Trans.Error (Error, ErrorT (..))
import Control.Monad.Trans.Except (ExceptT (..), runExceptT)
import Control.Monad.Trans.Identity (IdentityT (..))
import Control.Monad.Trans.List (ListT (..))
import Control.Monad.Trans.Maybe (MaybeT (..))
import qualified Control.Monad.Trans.RWS.Lazy as L
import qualified Control.Monad.Trans.RWS.Strict as S
import qualified Control.Monad.Trans.State.Lazy as L
import qualified Control.Monad.Trans.State.Strict as S
import qualified Control.Monad.Trans.Writer.Lazy as L
import qualified Control.Monad.Trans.Writer.Strict as S
import Optics.Core
import Optics.Internal.Utils
import Optics.Extra.Internal.Zoom
infixr 2 `zoom`, `zoomMaybe`, `zoomMany`
infixr 2 `magnify`, `magnifyMaybe`, `magnifyMany`
class
(MonadState s m, MonadState t n
) => Zoom m n s t | m -> s, n -> t, m t -> n, n s -> m where
zoom
:: Is k A_Lens
=> Optic' k is t s
-> m c
-> n c
zoomMaybe
:: Is k An_AffineTraversal
=> Optic' k is t s
-> m c
-> n (Maybe c)
zoomMany
:: (Is k A_Traversal, Monoid c)
=> Optic' k is t s
-> m c
-> n c
instance Monad m => Zoom (S.StateT s m) (S.StateT t m) s t where
zoom :: Optic' k is t s -> StateT s m c -> StateT t m c
zoom Optic' k is t s
o = \(S.StateT s -> m (c, s)
m) -> (t -> m (c, t)) -> StateT t m c
forall (s :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(s -> m (a, s)) -> StateT s m a
S.StateT ((t -> m (c, t)) -> StateT t m c)
-> (t -> m (c, t)) -> StateT t m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(is :: IxList) (t :: OpticKind) (s :: OpticKind) (c :: OpticKind).
(Is k A_Lens, Monad m) =>
Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t)
stateZoom Optic' k is t s
o s -> m (c, s)
m
zoomMaybe :: Optic' k is t s -> StateT s m c -> StateT t m (Maybe c)
zoomMaybe Optic' k is t s
o = \(S.StateT s -> m (c, s)
m) -> (t -> m (Maybe c, t)) -> StateT t m (Maybe c)
forall (s :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(s -> m (a, s)) -> StateT s m a
S.StateT ((t -> m (Maybe c, t)) -> StateT t m (Maybe c))
-> (t -> m (Maybe c, t)) -> StateT t m (Maybe c)
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s -> (s -> m (c, s)) -> t -> m (Maybe c, t)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(is :: IxList) (t :: OpticKind) (s :: OpticKind) (c :: OpticKind).
(Is k An_AffineTraversal, Monad m) =>
Optic' k is t s -> (s -> m (c, s)) -> t -> m (Maybe c, t)
stateZoomMaybe Optic' k is t s
o s -> m (c, s)
m
zoomMany :: Optic' k is t s -> StateT s m c -> StateT t m c
zoomMany Optic' k is t s
o = \(S.StateT s -> m (c, s)
m) -> (t -> m (c, t)) -> StateT t m c
forall (s :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(s -> m (a, s)) -> StateT s m a
S.StateT ((t -> m (c, t)) -> StateT t m c)
-> (t -> m (c, t)) -> StateT t m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(c :: OpticKind) (is :: IxList) (t :: OpticKind) (s :: OpticKind).
(Is k A_Traversal, Monad m, Monoid c) =>
Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t)
stateZoomMany Optic' k is t s
o s -> m (c, s)
m
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
instance Monad m => Zoom (L.StateT s m) (L.StateT t m) s t where
zoom :: Optic' k is t s -> StateT s m c -> StateT t m c
zoom Optic' k is t s
o = \(L.StateT s -> m (c, s)
m) -> (t -> m (c, t)) -> StateT t m c
forall (s :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(s -> m (a, s)) -> StateT s m a
L.StateT ((t -> m (c, t)) -> StateT t m c)
-> (t -> m (c, t)) -> StateT t m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(is :: IxList) (t :: OpticKind) (s :: OpticKind) (c :: OpticKind).
(Is k A_Lens, Monad m) =>
Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t)
stateZoom Optic' k is t s
o s -> m (c, s)
m
zoomMaybe :: Optic' k is t s -> StateT s m c -> StateT t m (Maybe c)
zoomMaybe Optic' k is t s
o = \(L.StateT s -> m (c, s)
m) -> (t -> m (Maybe c, t)) -> StateT t m (Maybe c)
forall (s :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(s -> m (a, s)) -> StateT s m a
L.StateT ((t -> m (Maybe c, t)) -> StateT t m (Maybe c))
-> (t -> m (Maybe c, t)) -> StateT t m (Maybe c)
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s -> (s -> m (c, s)) -> t -> m (Maybe c, t)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(is :: IxList) (t :: OpticKind) (s :: OpticKind) (c :: OpticKind).
(Is k An_AffineTraversal, Monad m) =>
Optic' k is t s -> (s -> m (c, s)) -> t -> m (Maybe c, t)
stateZoomMaybe Optic' k is t s
o s -> m (c, s)
m
zoomMany :: Optic' k is t s -> StateT s m c -> StateT t m c
zoomMany Optic' k is t s
o = \(L.StateT s -> m (c, s)
m) -> (t -> m (c, t)) -> StateT t m c
forall (s :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(s -> m (a, s)) -> StateT s m a
L.StateT ((t -> m (c, t)) -> StateT t m c)
-> (t -> m (c, t)) -> StateT t m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(c :: OpticKind) (is :: IxList) (t :: OpticKind) (s :: OpticKind).
(Is k A_Traversal, Monad m, Monoid c) =>
Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t)
stateZoomMany Optic' k is t s
o s -> m (c, s)
m
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
instance Zoom m n s t => Zoom (ReaderT e m) (ReaderT e n) s t where
zoom :: Optic' k is t s -> ReaderT e m c -> ReaderT e n c
zoom Optic' k is t s
o = \(ReaderT e -> m c
m) -> (e -> n c) -> ReaderT e n c
forall (r :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(r -> m a) -> ReaderT r m a
ReaderT (Optic' k is t s -> m c -> n c
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k A_Lens) =>
Optic' k is t s -> m c -> n c
zoom Optic' k is t s
o (m c -> n c) -> (e -> m c) -> e -> n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. e -> m c
m)
zoomMaybe :: Optic' k is t s -> ReaderT e m c -> ReaderT e n (Maybe c)
zoomMaybe Optic' k is t s
o = \(ReaderT e -> m c
m) -> (e -> n (Maybe c)) -> ReaderT e n (Maybe c)
forall (r :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(r -> m a) -> ReaderT r m a
ReaderT (Optic' k is t s -> m c -> n (Maybe c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k An_AffineTraversal) =>
Optic' k is t s -> m c -> n (Maybe c)
zoomMaybe Optic' k is t s
o (m c -> n (Maybe c)) -> (e -> m c) -> e -> n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. e -> m c
m)
zoomMany :: Optic' k is t s -> ReaderT e m c -> ReaderT e n c
zoomMany Optic' k is t s
o = \(ReaderT e -> m c
m) -> (e -> n c) -> ReaderT e n c
forall (r :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(r -> m a) -> ReaderT r m a
ReaderT (Optic' k is t s -> m c -> n c
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(Zoom m n s t, Is k A_Traversal, Monoid c) =>
Optic' k is t s -> m c -> n c
zoomMany Optic' k is t s
o (m c -> n c) -> (e -> m c) -> e -> n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. e -> m c
m)
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
instance Zoom m n s t => Zoom (IdentityT m) (IdentityT n) s t where
zoom :: Optic' k is t s -> IdentityT m c -> IdentityT n c
zoom Optic' k is t s
o = \(IdentityT m c
m) -> n c -> IdentityT n c
forall (k :: OpticKind) (f :: k -> OpticKind) (a :: k).
f a -> IdentityT f a
IdentityT (Optic' k is t s -> m c -> n c
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k A_Lens) =>
Optic' k is t s -> m c -> n c
zoom Optic' k is t s
o m c
m)
zoomMaybe :: Optic' k is t s -> IdentityT m c -> IdentityT n (Maybe c)
zoomMaybe Optic' k is t s
o = \(IdentityT m c
m) -> n (Maybe c) -> IdentityT n (Maybe c)
forall (k :: OpticKind) (f :: k -> OpticKind) (a :: k).
f a -> IdentityT f a
IdentityT (Optic' k is t s -> m c -> n (Maybe c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k An_AffineTraversal) =>
Optic' k is t s -> m c -> n (Maybe c)
zoomMaybe Optic' k is t s
o m c
m)
zoomMany :: Optic' k is t s -> IdentityT m c -> IdentityT n c
zoomMany Optic' k is t s
o = \(IdentityT m c
m) -> n c -> IdentityT n c
forall (k :: OpticKind) (f :: k -> OpticKind) (a :: k).
f a -> IdentityT f a
IdentityT (Optic' k is t s -> m c -> n c
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(Zoom m n s t, Is k A_Traversal, Monoid c) =>
Optic' k is t s -> m c -> n c
zoomMany Optic' k is t s
o m c
m)
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
instance (Monoid w, Monad m) => Zoom (S.RWST r w s m) (S.RWST r w t m) s t where
zoom :: Optic' k is t s -> RWST r w s m c -> RWST r w t m c
zoom Optic' k is t s
o = \(S.RWST r -> s -> m (c, s, w)
m) -> (r -> t -> m (c, t, w)) -> RWST r w t m c
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
S.RWST ((r -> t -> m (c, t, w)) -> RWST r w t m c)
-> (r -> t -> m (c, t, w)) -> RWST r w t m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s -> (r -> s -> m (c, s, w)) -> r -> t -> m (c, t, w)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(is :: IxList) (t :: OpticKind) (s :: OpticKind) (r :: OpticKind)
(c :: OpticKind) (w :: OpticKind).
(Is k A_Lens, Monad m) =>
Optic' k is t s -> (r -> s -> m (c, s, w)) -> r -> t -> m (c, t, w)
rwsZoom Optic' k is t s
o r -> s -> m (c, s, w)
m
zoomMaybe :: Optic' k is t s -> RWST r w s m c -> RWST r w t m (Maybe c)
zoomMaybe Optic' k is t s
o = \(S.RWST r -> s -> m (c, s, w)
m) -> (r -> t -> m (Maybe c, t, w)) -> RWST r w t m (Maybe c)
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
S.RWST ((r -> t -> m (Maybe c, t, w)) -> RWST r w t m (Maybe c))
-> (r -> t -> m (Maybe c, t, w)) -> RWST r w t m (Maybe c)
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s
-> (r -> s -> m (c, s, w)) -> r -> t -> m (Maybe c, t, w)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(w :: OpticKind) (is :: IxList) (t :: OpticKind) (s :: OpticKind)
(r :: OpticKind) (c :: OpticKind).
(Is k An_AffineTraversal, Monad m, Monoid w) =>
Optic' k is t s
-> (r -> s -> m (c, s, w)) -> r -> t -> m (Maybe c, t, w)
rwsZoomMaybe Optic' k is t s
o r -> s -> m (c, s, w)
m
zoomMany :: Optic' k is t s -> RWST r w s m c -> RWST r w t m c
zoomMany Optic' k is t s
o = \(S.RWST r -> s -> m (c, s, w)
m) -> (r -> t -> m (c, t, w)) -> RWST r w t m c
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
S.RWST ((r -> t -> m (c, t, w)) -> RWST r w t m c)
-> (r -> t -> m (c, t, w)) -> RWST r w t m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s -> (r -> s -> m (c, s, w)) -> r -> t -> m (c, t, w)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(w :: OpticKind) (c :: OpticKind) (is :: IxList) (t :: OpticKind)
(s :: OpticKind) (r :: OpticKind).
(Is k A_Traversal, Monad m, Monoid w, Monoid c) =>
Optic' k is t s -> (r -> s -> m (c, s, w)) -> r -> t -> m (c, t, w)
rwsZoomMany Optic' k is t s
o r -> s -> m (c, s, w)
m
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
instance (Monoid w, Monad m) => Zoom (L.RWST r w s m) (L.RWST r w t m) s t where
zoom :: Optic' k is t s -> RWST r w s m c -> RWST r w t m c
zoom Optic' k is t s
o = \(L.RWST r -> s -> m (c, s, w)
m) -> (r -> t -> m (c, t, w)) -> RWST r w t m c
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
L.RWST ((r -> t -> m (c, t, w)) -> RWST r w t m c)
-> (r -> t -> m (c, t, w)) -> RWST r w t m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s -> (r -> s -> m (c, s, w)) -> r -> t -> m (c, t, w)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(is :: IxList) (t :: OpticKind) (s :: OpticKind) (r :: OpticKind)
(c :: OpticKind) (w :: OpticKind).
(Is k A_Lens, Monad m) =>
Optic' k is t s -> (r -> s -> m (c, s, w)) -> r -> t -> m (c, t, w)
rwsZoom Optic' k is t s
o r -> s -> m (c, s, w)
m
zoomMaybe :: Optic' k is t s -> RWST r w s m c -> RWST r w t m (Maybe c)
zoomMaybe Optic' k is t s
o = \(L.RWST r -> s -> m (c, s, w)
m) -> (r -> t -> m (Maybe c, t, w)) -> RWST r w t m (Maybe c)
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
L.RWST ((r -> t -> m (Maybe c, t, w)) -> RWST r w t m (Maybe c))
-> (r -> t -> m (Maybe c, t, w)) -> RWST r w t m (Maybe c)
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s
-> (r -> s -> m (c, s, w)) -> r -> t -> m (Maybe c, t, w)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(w :: OpticKind) (is :: IxList) (t :: OpticKind) (s :: OpticKind)
(r :: OpticKind) (c :: OpticKind).
(Is k An_AffineTraversal, Monad m, Monoid w) =>
Optic' k is t s
-> (r -> s -> m (c, s, w)) -> r -> t -> m (Maybe c, t, w)
rwsZoomMaybe Optic' k is t s
o r -> s -> m (c, s, w)
m
zoomMany :: Optic' k is t s -> RWST r w s m c -> RWST r w t m c
zoomMany Optic' k is t s
o = \(L.RWST r -> s -> m (c, s, w)
m) -> (r -> t -> m (c, t, w)) -> RWST r w t m c
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
L.RWST ((r -> t -> m (c, t, w)) -> RWST r w t m c)
-> (r -> t -> m (c, t, w)) -> RWST r w t m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is t s -> (r -> s -> m (c, s, w)) -> r -> t -> m (c, t, w)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(w :: OpticKind) (c :: OpticKind) (is :: IxList) (t :: OpticKind)
(s :: OpticKind) (r :: OpticKind).
(Is k A_Traversal, Monad m, Monoid w, Monoid c) =>
Optic' k is t s -> (r -> s -> m (c, s, w)) -> r -> t -> m (c, t, w)
rwsZoomMany Optic' k is t s
o r -> s -> m (c, s, w)
m
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
instance (Monoid w, Zoom m n s t) => Zoom (S.WriterT w m) (S.WriterT w n) s t where
zoom :: Optic' k is t s -> WriterT w m c -> WriterT w n c
zoom Optic' k is t s
o = n (c, w) -> WriterT w n c
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
S.WriterT (n (c, w) -> WriterT w n c)
-> (m (c, w) -> n (c, w)) -> m (c, w) -> WriterT w n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is t s -> m (c, w) -> n (c, w)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k A_Lens) =>
Optic' k is t s -> m c -> n c
zoom Optic' k is t s
o (m (c, w) -> WriterT w n c)
-> (WriterT w m c -> m (c, w)) -> WriterT w m c -> WriterT w n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
S.runWriterT
zoomMaybe :: Optic' k is t s -> WriterT w m c -> WriterT w n (Maybe c)
zoomMaybe Optic' k is t s
o = n (Maybe c, w) -> WriterT w n (Maybe c)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
S.WriterT (n (Maybe c, w) -> WriterT w n (Maybe c))
-> (m (c, w) -> n (Maybe c, w))
-> m (c, w)
-> WriterT w n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe (c, w) -> (Maybe c, w))
-> n (Maybe (c, w)) -> n (Maybe c, w)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Maybe (c, w) -> (Maybe c, w)
forall (w :: OpticKind) (c :: OpticKind).
Monoid w =>
Maybe (c, w) -> (Maybe c, w)
shuffleW (n (Maybe (c, w)) -> n (Maybe c, w))
-> (m (c, w) -> n (Maybe (c, w))) -> m (c, w) -> n (Maybe c, w)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is t s -> m (c, w) -> n (Maybe (c, w))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k An_AffineTraversal) =>
Optic' k is t s -> m c -> n (Maybe c)
zoomMaybe Optic' k is t s
o (m (c, w) -> WriterT w n (Maybe c))
-> (WriterT w m c -> m (c, w))
-> WriterT w m c
-> WriterT w n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
S.runWriterT
zoomMany :: Optic' k is t s -> WriterT w m c -> WriterT w n c
zoomMany Optic' k is t s
o = n (c, w) -> WriterT w n c
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
S.WriterT (n (c, w) -> WriterT w n c)
-> (m (c, w) -> n (c, w)) -> m (c, w) -> WriterT w n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is t s -> m (c, w) -> n (c, w)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(Zoom m n s t, Is k A_Traversal, Monoid c) =>
Optic' k is t s -> m c -> n c
zoomMany Optic' k is t s
o (m (c, w) -> WriterT w n c)
-> (WriterT w m c -> m (c, w)) -> WriterT w m c -> WriterT w n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
S.runWriterT
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
instance (Monoid w, Zoom m n s t) => Zoom (L.WriterT w m) (L.WriterT w n) s t where
zoom :: Optic' k is t s -> WriterT w m c -> WriterT w n c
zoom Optic' k is t s
o = n (c, w) -> WriterT w n c
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
L.WriterT (n (c, w) -> WriterT w n c)
-> (m (c, w) -> n (c, w)) -> m (c, w) -> WriterT w n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is t s -> m (c, w) -> n (c, w)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k A_Lens) =>
Optic' k is t s -> m c -> n c
zoom Optic' k is t s
o (m (c, w) -> WriterT w n c)
-> (WriterT w m c -> m (c, w)) -> WriterT w m c -> WriterT w n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
L.runWriterT
zoomMaybe :: Optic' k is t s -> WriterT w m c -> WriterT w n (Maybe c)
zoomMaybe Optic' k is t s
o = n (Maybe c, w) -> WriterT w n (Maybe c)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
L.WriterT (n (Maybe c, w) -> WriterT w n (Maybe c))
-> (m (c, w) -> n (Maybe c, w))
-> m (c, w)
-> WriterT w n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe (c, w) -> (Maybe c, w))
-> n (Maybe (c, w)) -> n (Maybe c, w)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Maybe (c, w) -> (Maybe c, w)
forall (w :: OpticKind) (c :: OpticKind).
Monoid w =>
Maybe (c, w) -> (Maybe c, w)
shuffleW (n (Maybe (c, w)) -> n (Maybe c, w))
-> (m (c, w) -> n (Maybe (c, w))) -> m (c, w) -> n (Maybe c, w)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is t s -> m (c, w) -> n (Maybe (c, w))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k An_AffineTraversal) =>
Optic' k is t s -> m c -> n (Maybe c)
zoomMaybe Optic' k is t s
o (m (c, w) -> WriterT w n (Maybe c))
-> (WriterT w m c -> m (c, w))
-> WriterT w m c
-> WriterT w n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
L.runWriterT
zoomMany :: Optic' k is t s -> WriterT w m c -> WriterT w n c
zoomMany Optic' k is t s
o = n (c, w) -> WriterT w n c
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
L.WriterT (n (c, w) -> WriterT w n c)
-> (m (c, w) -> n (c, w)) -> m (c, w) -> WriterT w n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is t s -> m (c, w) -> n (c, w)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(Zoom m n s t, Is k A_Traversal, Monoid c) =>
Optic' k is t s -> m c -> n c
zoomMany Optic' k is t s
o (m (c, w) -> WriterT w n c)
-> (WriterT w m c -> m (c, w)) -> WriterT w m c -> WriterT w n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
L.runWriterT
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
instance Zoom m n s t => Zoom (ListT m) (ListT n) s t where
zoom :: Optic' k is t s -> ListT m c -> ListT n c
zoom Optic' k is t s
o = n [c] -> ListT n c
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m [a] -> ListT m a
ListT (n [c] -> ListT n c) -> (m [c] -> n [c]) -> m [c] -> ListT n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is t s -> m [c] -> n [c]
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k A_Lens) =>
Optic' k is t s -> m c -> n c
zoom Optic' k is t s
o (m [c] -> ListT n c)
-> (ListT m c -> m [c]) -> ListT m c -> ListT n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ListT m c -> m [c]
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
ListT m a -> m [a]
runListT
zoomMaybe :: Optic' k is t s -> ListT m c -> ListT n (Maybe c)
zoomMaybe Optic' k is t s
o = n [Maybe c] -> ListT n (Maybe c)
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m [a] -> ListT m a
ListT (n [Maybe c] -> ListT n (Maybe c))
-> (m [c] -> n [Maybe c]) -> m [c] -> ListT n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe [c] -> [Maybe c]) -> n (Maybe [c]) -> n [Maybe c]
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Maybe [c] -> [Maybe c]
forall (t :: OpticKind -> OpticKind) (f :: OpticKind -> OpticKind)
(a :: OpticKind).
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (n (Maybe [c]) -> n [Maybe c])
-> (m [c] -> n (Maybe [c])) -> m [c] -> n [Maybe c]
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is t s -> m [c] -> n (Maybe [c])
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k An_AffineTraversal) =>
Optic' k is t s -> m c -> n (Maybe c)
zoomMaybe Optic' k is t s
o (m [c] -> ListT n (Maybe c))
-> (ListT m c -> m [c]) -> ListT m c -> ListT n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ListT m c -> m [c]
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
ListT m a -> m [a]
runListT
zoomMany :: Optic' k is t s -> ListT m c -> ListT n c
zoomMany Optic' k is t s
o = n [c] -> ListT n c
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m [a] -> ListT m a
ListT (n [c] -> ListT n c) -> (m [c] -> n [c]) -> m [c] -> ListT n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is t s -> m [c] -> n [c]
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(Zoom m n s t, Is k A_Traversal, Monoid c) =>
Optic' k is t s -> m c -> n c
zoomMany Optic' k is t s
o (m [c] -> ListT n c)
-> (ListT m c -> m [c]) -> ListT m c -> ListT n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ListT m c -> m [c]
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
ListT m a -> m [a]
runListT
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
instance Zoom m n s t => Zoom (MaybeT m) (MaybeT n) s t where
zoom :: Optic' k is t s -> MaybeT m c -> MaybeT n c
zoom Optic' k is t s
o =
n (Maybe c) -> MaybeT n c
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m (Maybe a) -> MaybeT m a
MaybeT (n (Maybe c) -> MaybeT n c)
-> (m (Maybe c) -> n (Maybe c)) -> m (Maybe c) -> MaybeT n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is t s -> m (Maybe c) -> n (Maybe c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k A_Lens) =>
Optic' k is t s -> m c -> n c
zoom Optic' k is t s
o (m (Maybe c) -> MaybeT n c)
-> (MaybeT m c -> m (Maybe c)) -> MaybeT m c -> MaybeT n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# MaybeT m c -> m (Maybe c)
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
MaybeT m a -> m (Maybe a)
runMaybeT
zoomMaybe :: Optic' k is t s -> MaybeT m c -> MaybeT n (Maybe c)
zoomMaybe Optic' k is t s
o =
n (Maybe (Maybe c)) -> MaybeT n (Maybe c)
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m (Maybe a) -> MaybeT m a
MaybeT (n (Maybe (Maybe c)) -> MaybeT n (Maybe c))
-> (m (Maybe c) -> n (Maybe (Maybe c)))
-> m (Maybe c)
-> MaybeT n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe (May c) -> Maybe (Maybe c))
-> n (Maybe (May c)) -> n (Maybe (Maybe c))
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap (May (Maybe c) -> Maybe (Maybe c)
forall (a :: OpticKind). May a -> Maybe a
getMay (May (Maybe c) -> Maybe (Maybe c))
-> (Maybe (May c) -> May (Maybe c))
-> Maybe (May c)
-> Maybe (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Maybe (May c) -> May (Maybe c)
forall (c :: OpticKind). Maybe (May c) -> May (Maybe c)
shuffleMay) (n (Maybe (May c)) -> n (Maybe (Maybe c)))
-> (m (Maybe c) -> n (Maybe (May c)))
-> m (Maybe c)
-> n (Maybe (Maybe c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is t s -> m (May c) -> n (Maybe (May c))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k An_AffineTraversal) =>
Optic' k is t s -> m c -> n (Maybe c)
zoomMaybe Optic' k is t s
o (m (May c) -> n (Maybe (May c)))
-> (m (Maybe c) -> m (May c)) -> m (Maybe c) -> n (Maybe (May c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Maybe c -> May c) -> m (Maybe c) -> m (May c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Maybe c -> May c
forall (a :: OpticKind). Maybe a -> May a
May (m (Maybe c) -> MaybeT n (Maybe c))
-> (MaybeT m c -> m (Maybe c)) -> MaybeT m c -> MaybeT n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# MaybeT m c -> m (Maybe c)
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
MaybeT m a -> m (Maybe a)
runMaybeT
zoomMany :: Optic' k is t s -> MaybeT m c -> MaybeT n c
zoomMany Optic' k is t s
o =
n (Maybe c) -> MaybeT n c
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m (Maybe a) -> MaybeT m a
MaybeT (n (Maybe c) -> MaybeT n c)
-> (m (Maybe c) -> n (Maybe c)) -> m (Maybe c) -> MaybeT n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (May c -> Maybe c) -> n (May c) -> n (Maybe c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap May c -> Maybe c
forall (a :: OpticKind). May a -> Maybe a
getMay (n (May c) -> n (Maybe c))
-> (m (Maybe c) -> n (May c)) -> m (Maybe c) -> n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is t s -> m (May c) -> n (May c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(Zoom m n s t, Is k A_Traversal, Monoid c) =>
Optic' k is t s -> m c -> n c
zoomMany Optic' k is t s
o (m (May c) -> n (May c))
-> (m (Maybe c) -> m (May c)) -> m (Maybe c) -> n (May c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Maybe c -> May c) -> m (Maybe c) -> m (May c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Maybe c -> May c
forall (a :: OpticKind). Maybe a -> May a
May (m (Maybe c) -> MaybeT n c)
-> (MaybeT m c -> m (Maybe c)) -> MaybeT m c -> MaybeT n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# MaybeT m c -> m (Maybe c)
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
MaybeT m a -> m (Maybe a)
runMaybeT
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
instance (Error e, Zoom m n s t) => Zoom (ErrorT e m) (ErrorT e n) s t where
zoom :: Optic' k is t s -> ErrorT e m c -> ErrorT e n c
zoom Optic' k is t s
o =
n (Either e c) -> ErrorT e n c
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ErrorT e m a
ErrorT (n (Either e c) -> ErrorT e n c)
-> (m (Either e c) -> n (Either e c))
-> m (Either e c)
-> ErrorT e n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is t s -> m (Either e c) -> n (Either e c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k A_Lens) =>
Optic' k is t s -> m c -> n c
zoom Optic' k is t s
o (m (Either e c) -> ErrorT e n c)
-> (ErrorT e m c -> m (Either e c)) -> ErrorT e m c -> ErrorT e n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ErrorT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ErrorT e m a -> m (Either e a)
runErrorT
zoomMaybe :: Optic' k is t s -> ErrorT e m c -> ErrorT e n (Maybe c)
zoomMaybe Optic' k is t s
o =
n (Either e (Maybe c)) -> ErrorT e n (Maybe c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ErrorT e m a
ErrorT (n (Either e (Maybe c)) -> ErrorT e n (Maybe c))
-> (m (Either e c) -> n (Either e (Maybe c)))
-> m (Either e c)
-> ErrorT e n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe (Err e c) -> Either e (Maybe c))
-> n (Maybe (Err e c)) -> n (Either e (Maybe c))
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap (Err e (Maybe c) -> Either e (Maybe c)
forall (e :: OpticKind) (a :: OpticKind). Err e a -> Either e a
getErr (Err e (Maybe c) -> Either e (Maybe c))
-> (Maybe (Err e c) -> Err e (Maybe c))
-> Maybe (Err e c)
-> Either e (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Maybe (Err e c) -> Err e (Maybe c)
forall (e :: OpticKind) (c :: OpticKind).
Maybe (Err e c) -> Err e (Maybe c)
shuffleErr) (n (Maybe (Err e c)) -> n (Either e (Maybe c)))
-> (m (Either e c) -> n (Maybe (Err e c)))
-> m (Either e c)
-> n (Either e (Maybe c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is t s -> m (Err e c) -> n (Maybe (Err e c))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k An_AffineTraversal) =>
Optic' k is t s -> m c -> n (Maybe c)
zoomMaybe Optic' k is t s
o (m (Err e c) -> n (Maybe (Err e c)))
-> (m (Either e c) -> m (Err e c))
-> m (Either e c)
-> n (Maybe (Err e c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Either e c -> Err e c) -> m (Either e c) -> m (Err e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Either e c -> Err e c
forall (e :: OpticKind) (a :: OpticKind). Either e a -> Err e a
Err (m (Either e c) -> ErrorT e n (Maybe c))
-> (ErrorT e m c -> m (Either e c))
-> ErrorT e m c
-> ErrorT e n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ErrorT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ErrorT e m a -> m (Either e a)
runErrorT
zoomMany :: Optic' k is t s -> ErrorT e m c -> ErrorT e n c
zoomMany Optic' k is t s
o =
n (Either e c) -> ErrorT e n c
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ErrorT e m a
ErrorT (n (Either e c) -> ErrorT e n c)
-> (m (Either e c) -> n (Either e c))
-> m (Either e c)
-> ErrorT e n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Err e c -> Either e c) -> n (Err e c) -> n (Either e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Err e c -> Either e c
forall (e :: OpticKind) (a :: OpticKind). Err e a -> Either e a
getErr (n (Err e c) -> n (Either e c))
-> (m (Either e c) -> n (Err e c))
-> m (Either e c)
-> n (Either e c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is t s -> m (Err e c) -> n (Err e c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(Zoom m n s t, Is k A_Traversal, Monoid c) =>
Optic' k is t s -> m c -> n c
zoomMany Optic' k is t s
o (m (Err e c) -> n (Err e c))
-> (m (Either e c) -> m (Err e c)) -> m (Either e c) -> n (Err e c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Either e c -> Err e c) -> m (Either e c) -> m (Err e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Either e c -> Err e c
forall (e :: OpticKind) (a :: OpticKind). Either e a -> Err e a
Err (m (Either e c) -> ErrorT e n c)
-> (ErrorT e m c -> m (Either e c)) -> ErrorT e m c -> ErrorT e n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ErrorT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ErrorT e m a -> m (Either e a)
runErrorT
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
instance Zoom m n s t => Zoom (ExceptT e m) (ExceptT e n) s t where
zoom :: Optic' k is t s -> ExceptT e m c -> ExceptT e n c
zoom Optic' k is t s
o =
n (Either e c) -> ExceptT e n c
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ExceptT e m a
ExceptT (n (Either e c) -> ExceptT e n c)
-> (m (Either e c) -> n (Either e c))
-> m (Either e c)
-> ExceptT e n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is t s -> m (Either e c) -> n (Either e c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k A_Lens) =>
Optic' k is t s -> m c -> n c
zoom Optic' k is t s
o (m (Either e c) -> ExceptT e n c)
-> (ExceptT e m c -> m (Either e c))
-> ExceptT e m c
-> ExceptT e n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ExceptT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ExceptT e m a -> m (Either e a)
runExceptT
zoomMaybe :: Optic' k is t s -> ExceptT e m c -> ExceptT e n (Maybe c)
zoomMaybe Optic' k is t s
o =
n (Either e (Maybe c)) -> ExceptT e n (Maybe c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ExceptT e m a
ExceptT (n (Either e (Maybe c)) -> ExceptT e n (Maybe c))
-> (m (Either e c) -> n (Either e (Maybe c)))
-> m (Either e c)
-> ExceptT e n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe (Err e c) -> Either e (Maybe c))
-> n (Maybe (Err e c)) -> n (Either e (Maybe c))
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap (Err e (Maybe c) -> Either e (Maybe c)
forall (e :: OpticKind) (a :: OpticKind). Err e a -> Either e a
getErr (Err e (Maybe c) -> Either e (Maybe c))
-> (Maybe (Err e c) -> Err e (Maybe c))
-> Maybe (Err e c)
-> Either e (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Maybe (Err e c) -> Err e (Maybe c)
forall (e :: OpticKind) (c :: OpticKind).
Maybe (Err e c) -> Err e (Maybe c)
shuffleErr) (n (Maybe (Err e c)) -> n (Either e (Maybe c)))
-> (m (Either e c) -> n (Maybe (Err e c)))
-> m (Either e c)
-> n (Either e (Maybe c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is t s -> m (Err e c) -> n (Maybe (Err e c))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Zoom m n s t, Is k An_AffineTraversal) =>
Optic' k is t s -> m c -> n (Maybe c)
zoomMaybe Optic' k is t s
o (m (Err e c) -> n (Maybe (Err e c)))
-> (m (Either e c) -> m (Err e c))
-> m (Either e c)
-> n (Maybe (Err e c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Either e c -> Err e c) -> m (Either e c) -> m (Err e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Either e c -> Err e c
forall (e :: OpticKind) (a :: OpticKind). Either e a -> Err e a
Err (m (Either e c) -> ExceptT e n (Maybe c))
-> (ExceptT e m c -> m (Either e c))
-> ExceptT e m c
-> ExceptT e n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ExceptT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ExceptT e m a -> m (Either e a)
runExceptT
zoomMany :: Optic' k is t s -> ExceptT e m c -> ExceptT e n c
zoomMany Optic' k is t s
o =
n (Either e c) -> ExceptT e n c
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ExceptT e m a
ExceptT (n (Either e c) -> ExceptT e n c)
-> (m (Either e c) -> n (Either e c))
-> m (Either e c)
-> ExceptT e n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Err e c -> Either e c) -> n (Err e c) -> n (Either e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Err e c -> Either e c
forall (e :: OpticKind) (a :: OpticKind). Err e a -> Either e a
getErr (n (Err e c) -> n (Either e c))
-> (m (Either e c) -> n (Err e c))
-> m (Either e c)
-> n (Either e c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is t s -> m (Err e c) -> n (Err e c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(s :: OpticKind) (t :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(Zoom m n s t, Is k A_Traversal, Monoid c) =>
Optic' k is t s -> m c -> n c
zoomMany Optic' k is t s
o (m (Err e c) -> n (Err e c))
-> (m (Either e c) -> m (Err e c)) -> m (Either e c) -> n (Err e c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Either e c -> Err e c) -> m (Either e c) -> m (Err e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Either e c -> Err e c
forall (e :: OpticKind) (a :: OpticKind). Either e a -> Err e a
Err (m (Either e c) -> ExceptT e n c)
-> (ExceptT e m c -> m (Either e c))
-> ExceptT e m c
-> ExceptT e n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ExceptT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ExceptT e m a -> m (Either e a)
runExceptT
{-# INLINE zoom #-}
{-# INLINE zoomMaybe #-}
{-# INLINE zoomMany #-}
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
instance Magnify ((->) b) ((->) a) b a where
magnify :: Optic' k is a b -> (b -> c) -> a -> c
magnify = Optic' k is a b -> (b -> c) -> a -> c
forall (k :: OpticKind) (is :: IxList) (s :: OpticKind)
(a :: OpticKind) (r :: OpticKind).
Is k A_Getter =>
Optic' k is s a -> (a -> r) -> s -> r
views
magnifyMaybe :: Optic' k is a b -> (b -> c) -> a -> Maybe c
magnifyMaybe = Optic' k is a b -> (b -> c) -> a -> Maybe c
forall (k :: OpticKind) (is :: IxList) (s :: OpticKind)
(a :: OpticKind) (r :: OpticKind).
Is k An_AffineFold =>
Optic' k is s a -> (a -> r) -> s -> Maybe r
previews
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance MagnifyMany ((->) b) ((->) a) b a where
magnifyMany :: Optic' k is a b -> (b -> c) -> a -> c
magnifyMany = Optic' k is a b -> (b -> c) -> a -> c
forall (k :: OpticKind) (m :: OpticKind) (is :: IxList)
(s :: OpticKind) (a :: OpticKind).
(Is k A_Fold, Monoid m) =>
Optic' k is s a -> (a -> m) -> s -> m
foldMapOf
{-# INLINE magnifyMany #-}
instance Monad m => Magnify (ReaderT b m) (ReaderT a m) b a where
magnify :: Optic' k is a b -> ReaderT b m c -> ReaderT a m c
magnify Optic' k is a b
o = \(ReaderT b -> m c
m) ->
(a -> m c) -> ReaderT a m c
forall (r :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(r -> m a) -> ReaderT r m a
ReaderT ((a -> m c) -> ReaderT a m c) -> (a -> m c) -> ReaderT a m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ \a
r -> Effect m c -> m c
forall (m :: OpticKind -> OpticKind) (r :: OpticKind).
Effect m r -> m r
getEffect (Optic' k is a b -> (b -> Effect m c) -> a -> Effect m c
forall (k :: OpticKind) (is :: IxList) (s :: OpticKind)
(a :: OpticKind) (r :: OpticKind).
Is k A_Getter =>
Optic' k is s a -> (a -> r) -> s -> r
views Optic' k is a b
o (m c -> Effect m c
forall (m :: OpticKind -> OpticKind) (r :: OpticKind).
m r -> Effect m r
Effect (m c -> Effect m c) -> (b -> m c) -> b -> Effect m c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. b -> m c
m) a
r)
magnifyMaybe :: Optic' k is a b -> ReaderT b m c -> ReaderT a m (Maybe c)
magnifyMaybe Optic' k is a b
o = \(ReaderT b -> m c
m) ->
(a -> m (Maybe c)) -> ReaderT a m (Maybe c)
forall (r :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(r -> m a) -> ReaderT r m a
ReaderT ((a -> m (Maybe c)) -> ReaderT a m (Maybe c))
-> (a -> m (Maybe c)) -> ReaderT a m (Maybe c)
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ \a
r -> (Effect m c -> m c) -> Maybe (Effect m c) -> m (Maybe c)
forall (t :: OpticKind -> OpticKind) (f :: OpticKind -> OpticKind)
(a :: OpticKind) (b :: OpticKind).
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Effect m c -> m c
forall (m :: OpticKind -> OpticKind) (r :: OpticKind).
Effect m r -> m r
getEffect (Optic' k is a b -> (b -> Effect m c) -> a -> Maybe (Effect m c)
forall (k :: OpticKind) (is :: IxList) (s :: OpticKind)
(a :: OpticKind) (r :: OpticKind).
Is k An_AffineFold =>
Optic' k is s a -> (a -> r) -> s -> Maybe r
previews Optic' k is a b
o (m c -> Effect m c
forall (m :: OpticKind -> OpticKind) (r :: OpticKind).
m r -> Effect m r
Effect (m c -> Effect m c) -> (b -> m c) -> b -> Effect m c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. b -> m c
m) a
r)
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance Monad m => MagnifyMany (ReaderT b m) (ReaderT a m) b a where
magnifyMany :: Optic' k is a b -> ReaderT b m c -> ReaderT a m c
magnifyMany Optic' k is a b
o = \(ReaderT b -> m c
m) ->
(a -> m c) -> ReaderT a m c
forall (r :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(r -> m a) -> ReaderT r m a
ReaderT ((a -> m c) -> ReaderT a m c) -> (a -> m c) -> ReaderT a m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ \a
r -> Effect m c -> m c
forall (m :: OpticKind -> OpticKind) (r :: OpticKind).
Effect m r -> m r
getEffect (Optic' k is a b -> (b -> Effect m c) -> a -> Effect m c
forall (k :: OpticKind) (m :: OpticKind) (is :: IxList)
(s :: OpticKind) (a :: OpticKind).
(Is k A_Fold, Monoid m) =>
Optic' k is s a -> (a -> m) -> s -> m
foldMapOf Optic' k is a b
o (m c -> Effect m c
forall (m :: OpticKind -> OpticKind) (r :: OpticKind).
m r -> Effect m r
Effect (m c -> Effect m c) -> (b -> m c) -> b -> Effect m c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. b -> m c
m) a
r)
{-# INLINE magnifyMany #-}
instance (Monad m, Monoid w) => Magnify (S.RWST b w s m) (S.RWST a w s m) b a where
magnify :: Optic' k is a b -> RWST b w s m c -> RWST a w s m c
magnify Optic' k is a b
o = \(S.RWST b -> s -> m (c, s, w)
m) -> (a -> s -> m (c, s, w)) -> RWST a w s m c
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
S.RWST ((a -> s -> m (c, s, w)) -> RWST a w s m c)
-> (a -> s -> m (c, s, w)) -> RWST a w s m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is a b -> (b -> s -> m (c, s, w)) -> a -> s -> m (c, s, w)
forall (k :: OpticKind) (is :: IxList) (a :: OpticKind)
(b :: OpticKind) (s :: OpticKind) (f :: OpticKind -> OpticKind)
(c :: OpticKind) (w :: OpticKind).
Is k A_Getter =>
Optic' k is a b -> (b -> s -> f (c, s, w)) -> a -> s -> f (c, s, w)
rwsMagnify Optic' k is a b
o b -> s -> m (c, s, w)
m
magnifyMaybe :: Optic' k is a b -> RWST b w s m c -> RWST a w s m (Maybe c)
magnifyMaybe Optic' k is a b
o = \(S.RWST b -> s -> m (c, s, w)
m) -> (a -> s -> m (Maybe c, s, w)) -> RWST a w s m (Maybe c)
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
S.RWST ((a -> s -> m (Maybe c, s, w)) -> RWST a w s m (Maybe c))
-> (a -> s -> m (Maybe c, s, w)) -> RWST a w s m (Maybe c)
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is a b
-> (b -> s -> m (c, s, w)) -> a -> s -> m (Maybe c, s, w)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(w :: OpticKind) (is :: IxList) (a :: OpticKind) (b :: OpticKind)
(s :: OpticKind) (c :: OpticKind).
(Is k An_AffineFold, Applicative m, Monoid w) =>
Optic' k is a b
-> (b -> s -> m (c, s, w)) -> a -> s -> m (Maybe c, s, w)
rwsMagnifyMaybe Optic' k is a b
o b -> s -> m (c, s, w)
m
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance
(Monad m, Monoid w
) => MagnifyMany (S.RWST b w s m) (S.RWST a w s m) b a where
magnifyMany :: Optic' k is a b -> RWST b w s m c -> RWST a w s m c
magnifyMany Optic' k is a b
o = \(S.RWST b -> s -> m (c, s, w)
m) -> (a -> s -> m (c, s, w)) -> RWST a w s m c
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
S.RWST ((a -> s -> m (c, s, w)) -> RWST a w s m c)
-> (a -> s -> m (c, s, w)) -> RWST a w s m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is a b -> (b -> s -> m (c, s, w)) -> a -> s -> m (c, s, w)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(w :: OpticKind) (c :: OpticKind) (is :: IxList) (a :: OpticKind)
(b :: OpticKind) (s :: OpticKind).
(Is k A_Fold, Monad m, Monoid w, Monoid c) =>
Optic' k is a b -> (b -> s -> m (c, s, w)) -> a -> s -> m (c, s, w)
rwsMagnifyMany Optic' k is a b
o b -> s -> m (c, s, w)
m
{-# INLINE magnifyMany #-}
instance (Monad m, Monoid w) => Magnify (L.RWST b w s m) (L.RWST a w s m) b a where
magnify :: Optic' k is a b -> RWST b w s m c -> RWST a w s m c
magnify Optic' k is a b
o = \(L.RWST b -> s -> m (c, s, w)
m) -> (a -> s -> m (c, s, w)) -> RWST a w s m c
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
L.RWST ((a -> s -> m (c, s, w)) -> RWST a w s m c)
-> (a -> s -> m (c, s, w)) -> RWST a w s m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is a b -> (b -> s -> m (c, s, w)) -> a -> s -> m (c, s, w)
forall (k :: OpticKind) (is :: IxList) (a :: OpticKind)
(b :: OpticKind) (s :: OpticKind) (f :: OpticKind -> OpticKind)
(c :: OpticKind) (w :: OpticKind).
Is k A_Getter =>
Optic' k is a b -> (b -> s -> f (c, s, w)) -> a -> s -> f (c, s, w)
rwsMagnify Optic' k is a b
o b -> s -> m (c, s, w)
m
magnifyMaybe :: Optic' k is a b -> RWST b w s m c -> RWST a w s m (Maybe c)
magnifyMaybe Optic' k is a b
o = \(L.RWST b -> s -> m (c, s, w)
m) -> (a -> s -> m (Maybe c, s, w)) -> RWST a w s m (Maybe c)
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
L.RWST ((a -> s -> m (Maybe c, s, w)) -> RWST a w s m (Maybe c))
-> (a -> s -> m (Maybe c, s, w)) -> RWST a w s m (Maybe c)
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is a b
-> (b -> s -> m (c, s, w)) -> a -> s -> m (Maybe c, s, w)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(w :: OpticKind) (is :: IxList) (a :: OpticKind) (b :: OpticKind)
(s :: OpticKind) (c :: OpticKind).
(Is k An_AffineFold, Applicative m, Monoid w) =>
Optic' k is a b
-> (b -> s -> m (c, s, w)) -> a -> s -> m (Maybe c, s, w)
rwsMagnifyMaybe Optic' k is a b
o b -> s -> m (c, s, w)
m
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance
(Monad m, Monoid w
) => MagnifyMany (L.RWST b w s m) (L.RWST a w s m) b a where
magnifyMany :: Optic' k is a b -> RWST b w s m c -> RWST a w s m c
magnifyMany Optic' k is a b
o = \(L.RWST b -> s -> m (c, s, w)
m) -> (a -> s -> m (c, s, w)) -> RWST a w s m c
forall (r :: OpticKind) (w :: OpticKind) (s :: OpticKind)
(m :: OpticKind -> OpticKind) (a :: OpticKind).
(r -> s -> m (a, s, w)) -> RWST r w s m a
L.RWST ((a -> s -> m (c, s, w)) -> RWST a w s m c)
-> (a -> s -> m (c, s, w)) -> RWST a w s m c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is a b -> (b -> s -> m (c, s, w)) -> a -> s -> m (c, s, w)
forall (k :: OpticKind) (m :: OpticKind -> OpticKind)
(w :: OpticKind) (c :: OpticKind) (is :: IxList) (a :: OpticKind)
(b :: OpticKind) (s :: OpticKind).
(Is k A_Fold, Monad m, Monoid w, Monoid c) =>
Optic' k is a b -> (b -> s -> m (c, s, w)) -> a -> s -> m (c, s, w)
rwsMagnifyMany Optic' k is a b
o b -> s -> m (c, s, w)
m
{-# INLINE magnifyMany #-}
instance Magnify m n b a => Magnify (IdentityT m) (IdentityT n) b a where
magnify :: Optic' k is a b -> IdentityT m c -> IdentityT n c
magnify Optic' k is a b
o = \(IdentityT m c
m) -> n c -> IdentityT n c
forall (k :: OpticKind) (f :: k -> OpticKind) (a :: k).
f a -> IdentityT f a
IdentityT (Optic' k is a b -> m c -> n c
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k A_Getter) =>
Optic' k is a b -> m c -> n c
magnify Optic' k is a b
o m c
m)
magnifyMaybe :: Optic' k is a b -> IdentityT m c -> IdentityT n (Maybe c)
magnifyMaybe Optic' k is a b
o = \(IdentityT m c
m) -> n (Maybe c) -> IdentityT n (Maybe c)
forall (k :: OpticKind) (f :: k -> OpticKind) (a :: k).
f a -> IdentityT f a
IdentityT (Optic' k is a b -> m c -> n (Maybe c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k An_AffineFold) =>
Optic' k is a b -> m c -> n (Maybe c)
magnifyMaybe Optic' k is a b
o m c
m)
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance MagnifyMany m n b a => MagnifyMany (IdentityT m) (IdentityT n) b a where
magnifyMany :: Optic' k is a b -> IdentityT m c -> IdentityT n c
magnifyMany Optic' k is a b
o = \(IdentityT m c
m) -> n c -> IdentityT n c
forall (k :: OpticKind) (f :: k -> OpticKind) (a :: k).
f a -> IdentityT f a
IdentityT (Optic' k is a b -> m c -> n c
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(MagnifyMany m n b a, Is k A_Fold, Monoid c) =>
Optic' k is a b -> m c -> n c
magnifyMany Optic' k is a b
o m c
m)
{-# INLINE magnifyMany #-}
instance Magnify m n b a => Magnify (S.StateT s m) (S.StateT s n) b a where
magnify :: Optic' k is a b -> StateT s m c -> StateT s n c
magnify Optic' k is a b
o = \(S.StateT s -> m (c, s)
m) -> (s -> n (c, s)) -> StateT s n c
forall (s :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(s -> m (a, s)) -> StateT s m a
S.StateT ((s -> n (c, s)) -> StateT s n c)
-> (s -> n (c, s)) -> StateT s n c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is a b -> m (c, s) -> n (c, s)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k A_Getter) =>
Optic' k is a b -> m c -> n c
magnify Optic' k is a b
o (m (c, s) -> n (c, s)) -> (s -> m (c, s)) -> s -> n (c, s)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. s -> m (c, s)
m
magnifyMaybe :: Optic' k is a b -> StateT s m c -> StateT s n (Maybe c)
magnifyMaybe Optic' k is a b
o = \(S.StateT s -> m (c, s)
m) -> (s -> n (Maybe c, s)) -> StateT s n (Maybe c)
forall (s :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(s -> m (a, s)) -> StateT s m a
S.StateT ((s -> n (Maybe c, s)) -> StateT s n (Maybe c))
-> (s -> n (Maybe c, s)) -> StateT s n (Maybe c)
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ \s
s ->
(Maybe (c, s) -> (Maybe c, s))
-> n (Maybe (c, s)) -> n (Maybe c, s)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap (s -> Maybe (c, s) -> (Maybe c, s)
forall (s :: OpticKind) (c :: OpticKind).
s -> Maybe (c, s) -> (Maybe c, s)
shuffleS s
s) (n (Maybe (c, s)) -> n (Maybe c, s))
-> n (Maybe (c, s)) -> n (Maybe c, s)
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is a b -> m (c, s) -> n (Maybe (c, s))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k An_AffineFold) =>
Optic' k is a b -> m c -> n (Maybe c)
magnifyMaybe Optic' k is a b
o (s -> m (c, s)
m s
s)
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance Magnify m n b a => Magnify (L.StateT s m) (L.StateT s n) b a where
magnify :: Optic' k is a b -> StateT s m c -> StateT s n c
magnify Optic' k is a b
o = \(L.StateT s -> m (c, s)
m) -> (s -> n (c, s)) -> StateT s n c
forall (s :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(s -> m (a, s)) -> StateT s m a
L.StateT ((s -> n (c, s)) -> StateT s n c)
-> (s -> n (c, s)) -> StateT s n c
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is a b -> m (c, s) -> n (c, s)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k A_Getter) =>
Optic' k is a b -> m c -> n c
magnify Optic' k is a b
o (m (c, s) -> n (c, s)) -> (s -> m (c, s)) -> s -> n (c, s)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. s -> m (c, s)
m
magnifyMaybe :: Optic' k is a b -> StateT s m c -> StateT s n (Maybe c)
magnifyMaybe Optic' k is a b
o = \(L.StateT s -> m (c, s)
m) -> (s -> n (Maybe c, s)) -> StateT s n (Maybe c)
forall (s :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
(s -> m (a, s)) -> StateT s m a
L.StateT ((s -> n (Maybe c, s)) -> StateT s n (Maybe c))
-> (s -> n (Maybe c, s)) -> StateT s n (Maybe c)
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ \s
s ->
(Maybe (c, s) -> (Maybe c, s))
-> n (Maybe (c, s)) -> n (Maybe c, s)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap (s -> Maybe (c, s) -> (Maybe c, s)
forall (s :: OpticKind) (c :: OpticKind).
s -> Maybe (c, s) -> (Maybe c, s)
shuffleS s
s) (n (Maybe (c, s)) -> n (Maybe c, s))
-> n (Maybe (c, s)) -> n (Maybe c, s)
forall (a :: OpticKind) b. (a -> b) -> a -> b
$ Optic' k is a b -> m (c, s) -> n (Maybe (c, s))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k An_AffineFold) =>
Optic' k is a b -> m c -> n (Maybe c)
magnifyMaybe Optic' k is a b
o (s -> m (c, s)
m s
s)
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance
(Monoid w, Magnify m n b a
) => Magnify (S.WriterT w m) (S.WriterT w n) b a where
magnify :: Optic' k is a b -> WriterT w m c -> WriterT w n c
magnify Optic' k is a b
o = n (c, w) -> WriterT w n c
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
S.WriterT (n (c, w) -> WriterT w n c)
-> (m (c, w) -> n (c, w)) -> m (c, w) -> WriterT w n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is a b -> m (c, w) -> n (c, w)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k A_Getter) =>
Optic' k is a b -> m c -> n c
magnify Optic' k is a b
o (m (c, w) -> WriterT w n c)
-> (WriterT w m c -> m (c, w)) -> WriterT w m c -> WriterT w n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
S.runWriterT
magnifyMaybe :: Optic' k is a b -> WriterT w m c -> WriterT w n (Maybe c)
magnifyMaybe Optic' k is a b
o = n (Maybe c, w) -> WriterT w n (Maybe c)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
S.WriterT (n (Maybe c, w) -> WriterT w n (Maybe c))
-> (m (c, w) -> n (Maybe c, w))
-> m (c, w)
-> WriterT w n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe (c, w) -> (Maybe c, w))
-> n (Maybe (c, w)) -> n (Maybe c, w)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Maybe (c, w) -> (Maybe c, w)
forall (w :: OpticKind) (c :: OpticKind).
Monoid w =>
Maybe (c, w) -> (Maybe c, w)
shuffleW (n (Maybe (c, w)) -> n (Maybe c, w))
-> (m (c, w) -> n (Maybe (c, w))) -> m (c, w) -> n (Maybe c, w)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is a b -> m (c, w) -> n (Maybe (c, w))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k An_AffineFold) =>
Optic' k is a b -> m c -> n (Maybe c)
magnifyMaybe Optic' k is a b
o (m (c, w) -> WriterT w n (Maybe c))
-> (WriterT w m c -> m (c, w))
-> WriterT w m c
-> WriterT w n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
S.runWriterT
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance
(Monoid w, MagnifyMany m n b a
) => MagnifyMany (S.WriterT w m) (S.WriterT w n) b a where
magnifyMany :: Optic' k is a b -> WriterT w m c -> WriterT w n c
magnifyMany Optic' k is a b
o = n (c, w) -> WriterT w n c
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
S.WriterT (n (c, w) -> WriterT w n c)
-> (m (c, w) -> n (c, w)) -> m (c, w) -> WriterT w n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is a b -> m (c, w) -> n (c, w)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(MagnifyMany m n b a, Is k A_Fold, Monoid c) =>
Optic' k is a b -> m c -> n c
magnifyMany Optic' k is a b
o (m (c, w) -> WriterT w n c)
-> (WriterT w m c -> m (c, w)) -> WriterT w m c -> WriterT w n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
S.runWriterT
{-# INLINE magnifyMany #-}
instance
(Monoid w, Magnify m n b a
) => Magnify (L.WriterT w m) (L.WriterT w n) b a where
magnify :: Optic' k is a b -> WriterT w m c -> WriterT w n c
magnify Optic' k is a b
o = n (c, w) -> WriterT w n c
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
L.WriterT (n (c, w) -> WriterT w n c)
-> (m (c, w) -> n (c, w)) -> m (c, w) -> WriterT w n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is a b -> m (c, w) -> n (c, w)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k A_Getter) =>
Optic' k is a b -> m c -> n c
magnify Optic' k is a b
o (m (c, w) -> WriterT w n c)
-> (WriterT w m c -> m (c, w)) -> WriterT w m c -> WriterT w n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
L.runWriterT
magnifyMaybe :: Optic' k is a b -> WriterT w m c -> WriterT w n (Maybe c)
magnifyMaybe Optic' k is a b
o = n (Maybe c, w) -> WriterT w n (Maybe c)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
L.WriterT (n (Maybe c, w) -> WriterT w n (Maybe c))
-> (m (c, w) -> n (Maybe c, w))
-> m (c, w)
-> WriterT w n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe (c, w) -> (Maybe c, w))
-> n (Maybe (c, w)) -> n (Maybe c, w)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Maybe (c, w) -> (Maybe c, w)
forall (w :: OpticKind) (c :: OpticKind).
Monoid w =>
Maybe (c, w) -> (Maybe c, w)
shuffleW (n (Maybe (c, w)) -> n (Maybe c, w))
-> (m (c, w) -> n (Maybe (c, w))) -> m (c, w) -> n (Maybe c, w)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is a b -> m (c, w) -> n (Maybe (c, w))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k An_AffineFold) =>
Optic' k is a b -> m c -> n (Maybe c)
magnifyMaybe Optic' k is a b
o (m (c, w) -> WriterT w n (Maybe c))
-> (WriterT w m c -> m (c, w))
-> WriterT w m c
-> WriterT w n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
L.runWriterT
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance
(Monoid w, MagnifyMany m n b a
) => MagnifyMany (L.WriterT w m) (L.WriterT w n) b a where
magnifyMany :: Optic' k is a b -> WriterT w m c -> WriterT w n c
magnifyMany Optic' k is a b
o = n (c, w) -> WriterT w n c
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (a, w) -> WriterT w m a
L.WriterT (n (c, w) -> WriterT w n c)
-> (m (c, w) -> n (c, w)) -> m (c, w) -> WriterT w n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is a b -> m (c, w) -> n (c, w)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(MagnifyMany m n b a, Is k A_Fold, Monoid c) =>
Optic' k is a b -> m c -> n c
magnifyMany Optic' k is a b
o (m (c, w) -> WriterT w n c)
-> (WriterT w m c -> m (c, w)) -> WriterT w m c -> WriterT w n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# WriterT w m c -> m (c, w)
forall (w :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
WriterT w m a -> m (a, w)
L.runWriterT
{-# INLINE magnifyMany #-}
instance Magnify m n b a => Magnify (ListT m) (ListT n) b a where
magnify :: Optic' k is a b -> ListT m c -> ListT n c
magnify Optic' k is a b
o = n [c] -> ListT n c
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m [a] -> ListT m a
ListT (n [c] -> ListT n c) -> (m [c] -> n [c]) -> m [c] -> ListT n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is a b -> m [c] -> n [c]
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k A_Getter) =>
Optic' k is a b -> m c -> n c
magnify Optic' k is a b
o (m [c] -> ListT n c)
-> (ListT m c -> m [c]) -> ListT m c -> ListT n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ListT m c -> m [c]
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
ListT m a -> m [a]
runListT
magnifyMaybe :: Optic' k is a b -> ListT m c -> ListT n (Maybe c)
magnifyMaybe Optic' k is a b
o = n [Maybe c] -> ListT n (Maybe c)
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m [a] -> ListT m a
ListT (n [Maybe c] -> ListT n (Maybe c))
-> (m [c] -> n [Maybe c]) -> m [c] -> ListT n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe [c] -> [Maybe c]) -> n (Maybe [c]) -> n [Maybe c]
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Maybe [c] -> [Maybe c]
forall (t :: OpticKind -> OpticKind) (f :: OpticKind -> OpticKind)
(a :: OpticKind).
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (n (Maybe [c]) -> n [Maybe c])
-> (m [c] -> n (Maybe [c])) -> m [c] -> n [Maybe c]
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is a b -> m [c] -> n (Maybe [c])
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k An_AffineFold) =>
Optic' k is a b -> m c -> n (Maybe c)
magnifyMaybe Optic' k is a b
o (m [c] -> ListT n (Maybe c))
-> (ListT m c -> m [c]) -> ListT m c -> ListT n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ListT m c -> m [c]
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
ListT m a -> m [a]
runListT
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance MagnifyMany m n b a => MagnifyMany (ListT m) (ListT n) b a where
magnifyMany :: Optic' k is a b -> ListT m c -> ListT n c
magnifyMany Optic' k is a b
o = n [c] -> ListT n c
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m [a] -> ListT m a
ListT (n [c] -> ListT n c) -> (m [c] -> n [c]) -> m [c] -> ListT n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is a b -> m [c] -> n [c]
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(MagnifyMany m n b a, Is k A_Fold, Monoid c) =>
Optic' k is a b -> m c -> n c
magnifyMany Optic' k is a b
o (m [c] -> ListT n c)
-> (ListT m c -> m [c]) -> ListT m c -> ListT n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ListT m c -> m [c]
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
ListT m a -> m [a]
runListT
{-# INLINE magnifyMany #-}
instance Magnify m n b a => Magnify (MaybeT m) (MaybeT n) b a where
magnify :: Optic' k is a b -> MaybeT m c -> MaybeT n c
magnify Optic' k is a b
o = n (Maybe c) -> MaybeT n c
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m (Maybe a) -> MaybeT m a
MaybeT (n (Maybe c) -> MaybeT n c)
-> (m (Maybe c) -> n (Maybe c)) -> m (Maybe c) -> MaybeT n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is a b -> m (Maybe c) -> n (Maybe c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k A_Getter) =>
Optic' k is a b -> m c -> n c
magnify Optic' k is a b
o (m (Maybe c) -> MaybeT n c)
-> (MaybeT m c -> m (Maybe c)) -> MaybeT m c -> MaybeT n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# MaybeT m c -> m (Maybe c)
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
MaybeT m a -> m (Maybe a)
runMaybeT
magnifyMaybe :: Optic' k is a b -> MaybeT m c -> MaybeT n (Maybe c)
magnifyMaybe Optic' k is a b
o =
n (Maybe (Maybe c)) -> MaybeT n (Maybe c)
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m (Maybe a) -> MaybeT m a
MaybeT (n (Maybe (Maybe c)) -> MaybeT n (Maybe c))
-> (m (Maybe c) -> n (Maybe (Maybe c)))
-> m (Maybe c)
-> MaybeT n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe (May c) -> Maybe (Maybe c))
-> n (Maybe (May c)) -> n (Maybe (Maybe c))
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap (May (Maybe c) -> Maybe (Maybe c)
forall (a :: OpticKind). May a -> Maybe a
getMay (May (Maybe c) -> Maybe (Maybe c))
-> (Maybe (May c) -> May (Maybe c))
-> Maybe (May c)
-> Maybe (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Maybe (May c) -> May (Maybe c)
forall (c :: OpticKind). Maybe (May c) -> May (Maybe c)
shuffleMay) (n (Maybe (May c)) -> n (Maybe (Maybe c)))
-> (m (Maybe c) -> n (Maybe (May c)))
-> m (Maybe c)
-> n (Maybe (Maybe c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is a b -> m (May c) -> n (Maybe (May c))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k An_AffineFold) =>
Optic' k is a b -> m c -> n (Maybe c)
magnifyMaybe Optic' k is a b
o (m (May c) -> n (Maybe (May c)))
-> (m (Maybe c) -> m (May c)) -> m (Maybe c) -> n (Maybe (May c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Maybe c -> May c) -> m (Maybe c) -> m (May c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Maybe c -> May c
forall (a :: OpticKind). Maybe a -> May a
May (m (Maybe c) -> MaybeT n (Maybe c))
-> (MaybeT m c -> m (Maybe c)) -> MaybeT m c -> MaybeT n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# MaybeT m c -> m (Maybe c)
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
MaybeT m a -> m (Maybe a)
runMaybeT
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance MagnifyMany m n b a => MagnifyMany (MaybeT m) (MaybeT n) b a where
magnifyMany :: Optic' k is a b -> MaybeT m c -> MaybeT n c
magnifyMany Optic' k is a b
o = n (Maybe c) -> MaybeT n c
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
m (Maybe a) -> MaybeT m a
MaybeT (n (Maybe c) -> MaybeT n c)
-> (m (Maybe c) -> n (Maybe c)) -> m (Maybe c) -> MaybeT n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (May c -> Maybe c) -> n (May c) -> n (Maybe c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap May c -> Maybe c
forall (a :: OpticKind). May a -> Maybe a
getMay (n (May c) -> n (Maybe c))
-> (m (Maybe c) -> n (May c)) -> m (Maybe c) -> n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is a b -> m (May c) -> n (May c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(MagnifyMany m n b a, Is k A_Fold, Monoid c) =>
Optic' k is a b -> m c -> n c
magnifyMany Optic' k is a b
o (m (May c) -> n (May c))
-> (m (Maybe c) -> m (May c)) -> m (Maybe c) -> n (May c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Maybe c -> May c) -> m (Maybe c) -> m (May c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Maybe c -> May c
forall (a :: OpticKind). Maybe a -> May a
May (m (Maybe c) -> MaybeT n c)
-> (MaybeT m c -> m (Maybe c)) -> MaybeT m c -> MaybeT n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# MaybeT m c -> m (Maybe c)
forall (m :: OpticKind -> OpticKind) (a :: OpticKind).
MaybeT m a -> m (Maybe a)
runMaybeT
{-# INLINE magnifyMany #-}
instance (Error e, Magnify m n b a) => Magnify (ErrorT e m) (ErrorT e n) b a where
magnify :: Optic' k is a b -> ErrorT e m c -> ErrorT e n c
magnify Optic' k is a b
o = n (Either e c) -> ErrorT e n c
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ErrorT e m a
ErrorT (n (Either e c) -> ErrorT e n c)
-> (m (Either e c) -> n (Either e c))
-> m (Either e c)
-> ErrorT e n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is a b -> m (Either e c) -> n (Either e c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k A_Getter) =>
Optic' k is a b -> m c -> n c
magnify Optic' k is a b
o (m (Either e c) -> ErrorT e n c)
-> (ErrorT e m c -> m (Either e c)) -> ErrorT e m c -> ErrorT e n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ErrorT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ErrorT e m a -> m (Either e a)
runErrorT
magnifyMaybe :: Optic' k is a b -> ErrorT e m c -> ErrorT e n (Maybe c)
magnifyMaybe Optic' k is a b
o =
n (Either e (Maybe c)) -> ErrorT e n (Maybe c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ErrorT e m a
ErrorT (n (Either e (Maybe c)) -> ErrorT e n (Maybe c))
-> (m (Either e c) -> n (Either e (Maybe c)))
-> m (Either e c)
-> ErrorT e n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe (Err e c) -> Either e (Maybe c))
-> n (Maybe (Err e c)) -> n (Either e (Maybe c))
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap (Err e (Maybe c) -> Either e (Maybe c)
forall (e :: OpticKind) (a :: OpticKind). Err e a -> Either e a
getErr (Err e (Maybe c) -> Either e (Maybe c))
-> (Maybe (Err e c) -> Err e (Maybe c))
-> Maybe (Err e c)
-> Either e (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Maybe (Err e c) -> Err e (Maybe c)
forall (e :: OpticKind) (c :: OpticKind).
Maybe (Err e c) -> Err e (Maybe c)
shuffleErr) (n (Maybe (Err e c)) -> n (Either e (Maybe c)))
-> (m (Either e c) -> n (Maybe (Err e c)))
-> m (Either e c)
-> n (Either e (Maybe c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is a b -> m (Err e c) -> n (Maybe (Err e c))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k An_AffineFold) =>
Optic' k is a b -> m c -> n (Maybe c)
magnifyMaybe Optic' k is a b
o (m (Err e c) -> n (Maybe (Err e c)))
-> (m (Either e c) -> m (Err e c))
-> m (Either e c)
-> n (Maybe (Err e c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Either e c -> Err e c) -> m (Either e c) -> m (Err e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Either e c -> Err e c
forall (e :: OpticKind) (a :: OpticKind). Either e a -> Err e a
Err (m (Either e c) -> ErrorT e n (Maybe c))
-> (ErrorT e m c -> m (Either e c))
-> ErrorT e m c
-> ErrorT e n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ErrorT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ErrorT e m a -> m (Either e a)
runErrorT
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance
(Error e, MagnifyMany m n b a
) => MagnifyMany (ErrorT e m) (ErrorT e n) b a where
magnifyMany :: Optic' k is a b -> ErrorT e m c -> ErrorT e n c
magnifyMany Optic' k is a b
o = n (Either e c) -> ErrorT e n c
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ErrorT e m a
ErrorT (n (Either e c) -> ErrorT e n c)
-> (m (Either e c) -> n (Either e c))
-> m (Either e c)
-> ErrorT e n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Err e c -> Either e c) -> n (Err e c) -> n (Either e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Err e c -> Either e c
forall (e :: OpticKind) (a :: OpticKind). Err e a -> Either e a
getErr (n (Err e c) -> n (Either e c))
-> (m (Either e c) -> n (Err e c))
-> m (Either e c)
-> n (Either e c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is a b -> m (Err e c) -> n (Err e c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(MagnifyMany m n b a, Is k A_Fold, Monoid c) =>
Optic' k is a b -> m c -> n c
magnifyMany Optic' k is a b
o (m (Err e c) -> n (Err e c))
-> (m (Either e c) -> m (Err e c)) -> m (Either e c) -> n (Err e c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Either e c -> Err e c) -> m (Either e c) -> m (Err e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Either e c -> Err e c
forall (e :: OpticKind) (a :: OpticKind). Either e a -> Err e a
Err (m (Either e c) -> ErrorT e n c)
-> (ErrorT e m c -> m (Either e c)) -> ErrorT e m c -> ErrorT e n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ErrorT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ErrorT e m a -> m (Either e a)
runErrorT
{-# INLINE magnifyMany #-}
instance Magnify m n b a => Magnify (ExceptT e m) (ExceptT e n) b a where
magnify :: Optic' k is a b -> ExceptT e m c -> ExceptT e n c
magnify Optic' k is a b
o = n (Either e c) -> ExceptT e n c
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ExceptT e m a
ExceptT (n (Either e c) -> ExceptT e n c)
-> (m (Either e c) -> n (Either e c))
-> m (Either e c)
-> ExceptT e n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. Optic' k is a b -> m (Either e c) -> n (Either e c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k A_Getter) =>
Optic' k is a b -> m c -> n c
magnify Optic' k is a b
o (m (Either e c) -> ExceptT e n c)
-> (ExceptT e m c -> m (Either e c))
-> ExceptT e m c
-> ExceptT e n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ExceptT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ExceptT e m a -> m (Either e a)
runExceptT
magnifyMaybe :: Optic' k is a b -> ExceptT e m c -> ExceptT e n (Maybe c)
magnifyMaybe Optic' k is a b
o =
n (Either e (Maybe c)) -> ExceptT e n (Maybe c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ExceptT e m a
ExceptT (n (Either e (Maybe c)) -> ExceptT e n (Maybe c))
-> (m (Either e c) -> n (Either e (Maybe c)))
-> m (Either e c)
-> ExceptT e n (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Maybe (Err e c) -> Either e (Maybe c))
-> n (Maybe (Err e c)) -> n (Either e (Maybe c))
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap (Err e (Maybe c) -> Either e (Maybe c)
forall (e :: OpticKind) (a :: OpticKind). Err e a -> Either e a
getErr (Err e (Maybe c) -> Either e (Maybe c))
-> (Maybe (Err e c) -> Err e (Maybe c))
-> Maybe (Err e c)
-> Either e (Maybe c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Maybe (Err e c) -> Err e (Maybe c)
forall (e :: OpticKind) (c :: OpticKind).
Maybe (Err e c) -> Err e (Maybe c)
shuffleErr) (n (Maybe (Err e c)) -> n (Either e (Maybe c)))
-> (m (Either e c) -> n (Maybe (Err e c)))
-> m (Either e c)
-> n (Either e (Maybe c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is a b -> m (Err e c) -> n (Maybe (Err e c))
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (is :: IxList)
(c :: OpticKind).
(Magnify m n b a, Is k An_AffineFold) =>
Optic' k is a b -> m c -> n (Maybe c)
magnifyMaybe Optic' k is a b
o (m (Err e c) -> n (Maybe (Err e c)))
-> (m (Either e c) -> m (Err e c))
-> m (Either e c)
-> n (Maybe (Err e c))
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Either e c -> Err e c) -> m (Either e c) -> m (Err e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Either e c -> Err e c
forall (e :: OpticKind) (a :: OpticKind). Either e a -> Err e a
Err (m (Either e c) -> ExceptT e n (Maybe c))
-> (ExceptT e m c -> m (Either e c))
-> ExceptT e m c
-> ExceptT e n (Maybe c)
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ExceptT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ExceptT e m a -> m (Either e a)
runExceptT
{-# INLINE magnify #-}
{-# INLINE magnifyMaybe #-}
instance MagnifyMany m n b a => MagnifyMany (ExceptT e m) (ExceptT e n) b a where
magnifyMany :: Optic' k is a b -> ExceptT e m c -> ExceptT e n c
magnifyMany Optic' k is a b
o = n (Either e c) -> ExceptT e n c
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
m (Either e a) -> ExceptT e m a
ExceptT (n (Either e c) -> ExceptT e n c)
-> (m (Either e c) -> n (Either e c))
-> m (Either e c)
-> ExceptT e n c
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
Coercible b c =>
(b -> c) -> (a -> b) -> a -> c
#. (Err e c -> Either e c) -> n (Err e c) -> n (Either e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Err e c -> Either e c
forall (e :: OpticKind) (a :: OpticKind). Err e a -> Either e a
getErr (n (Err e c) -> n (Either e c))
-> (m (Either e c) -> n (Err e c))
-> m (Either e c)
-> n (Either e c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. Optic' k is a b -> m (Err e c) -> n (Err e c)
forall (m :: OpticKind -> OpticKind) (n :: OpticKind -> OpticKind)
(b :: OpticKind) (a :: OpticKind) (k :: OpticKind) (c :: OpticKind)
(is :: IxList).
(MagnifyMany m n b a, Is k A_Fold, Monoid c) =>
Optic' k is a b -> m c -> n c
magnifyMany Optic' k is a b
o (m (Err e c) -> n (Err e c))
-> (m (Either e c) -> m (Err e c)) -> m (Either e c) -> n (Err e c)
forall (b :: OpticKind) (c :: OpticKind) (a :: OpticKind).
(b -> c) -> (a -> b) -> a -> c
. (Either e c -> Err e c) -> m (Either e c) -> m (Err e c)
forall (f :: OpticKind -> OpticKind) (a :: OpticKind)
(b :: OpticKind).
Functor f =>
(a -> b) -> f a -> f b
fmap Either e c -> Err e c
forall (e :: OpticKind) (a :: OpticKind). Either e a -> Err e a
Err (m (Either e c) -> ExceptT e n c)
-> (ExceptT e m c -> m (Either e c))
-> ExceptT e m c
-> ExceptT e n c
forall (a :: OpticKind) (b :: OpticKind) (c :: OpticKind).
Coercible a b =>
(b -> c) -> (a -> b) -> a -> c
.# ExceptT e m c -> m (Either e c)
forall (e :: OpticKind) (m :: OpticKind -> OpticKind)
(a :: OpticKind).
ExceptT e m a -> m (Either e a)
runExceptT
{-# INLINE magnifyMany #-}