Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Focusing m c s = Focusing {
- unfocusing :: m (c, s)
- stateZoom :: (Is k A_Lens, Monad m) => Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t)
- stateZoomMaybe :: (Is k An_AffineTraversal, Monad m) => Optic' k is t s -> (s -> m (c, s)) -> t -> m (Maybe c, t)
- stateZoomMany :: (Is k A_Traversal, Monad m, Monoid c) => Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t)
- newtype FocusingWith w m c s = FocusingWith {
- unfocusingWith :: m (c, s, w)
- rwsZoom :: (Is k A_Lens, Monad m) => Optic' k is t s -> (r -> s -> m (c, s, w)) -> r -> t -> m (c, t, w)
- rwsZoomMaybe :: (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)
- rwsZoomMany :: (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)
- newtype May a = May {}
- shuffleMay :: Maybe (May c) -> May (Maybe c)
- newtype Err e a = Err {}
- shuffleErr :: Maybe (Err e c) -> Err e (Maybe c)
- newtype Effect m r = Effect {
- getEffect :: m r
- newtype EffectRWS w s m c = EffectRWS {
- getEffectRWS :: s -> m (c, s, w)
- rwsMagnify :: Is k A_Getter => Optic' k is a b -> (b -> s -> f (c, s, w)) -> a -> s -> f (c, s, w)
- rwsMagnifyMaybe :: (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)
- rwsMagnifyMany :: (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)
- shuffleS :: s -> Maybe (c, s) -> (Maybe c, s)
- shuffleW :: Monoid w => Maybe (c, w) -> (Maybe c, w)
Zoom
newtype Focusing m c s Source #
Focusing | |
|
stateZoomMaybe :: (Is k An_AffineTraversal, Monad m) => Optic' k is t s -> (s -> m (c, s)) -> t -> m (Maybe c, t) Source #
stateZoomMany :: (Is k A_Traversal, Monad m, Monoid c) => Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t) Source #
newtype FocusingWith w m c s Source #
FocusingWith | |
|
Instances
Monad m => Functor (FocusingWith w m s) Source # | |
Defined in Optics.Extra.Internal.Zoom fmap :: (a -> b) -> FocusingWith w m s a -> FocusingWith w m s b # (<$) :: a -> FocusingWith w m s b -> FocusingWith w m s a # | |
(Monad m, Monoid s, Monoid w) => Applicative (FocusingWith w m s) Source # | |
Defined in Optics.Extra.Internal.Zoom pure :: a -> FocusingWith w m s a # (<*>) :: FocusingWith w m s (a -> b) -> FocusingWith w m s a -> FocusingWith w m s b # liftA2 :: (a -> b -> c) -> FocusingWith w m s a -> FocusingWith w m s b -> FocusingWith w m s c # (*>) :: FocusingWith w m s a -> FocusingWith w m s b -> FocusingWith w m s b # (<*) :: FocusingWith w m s a -> FocusingWith w m s b -> FocusingWith w m s a # |
rwsZoom :: (Is k A_Lens, Monad m) => Optic' k is t s -> (r -> s -> m (c, s, w)) -> r -> t -> m (c, t, w) Source #
rwsZoomMaybe :: (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) Source #
rwsZoomMany :: (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) Source #
Magnify
Wrap a monadic effect.
newtype EffectRWS w s m c Source #
Wrap a monadic effect. Used when magnifying RWST
.
EffectRWS | |
|
rwsMagnify :: Is k A_Getter => Optic' k is a b -> (b -> s -> f (c, s, w)) -> a -> s -> f (c, s, w) Source #
rwsMagnifyMaybe :: (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) Source #
rwsMagnifyMany :: (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) Source #