optics-extra-0.1: Extra utilities and instances for optics-core

Safe HaskellNone
LanguageHaskell2010

Optics.Extra.Internal.Zoom

Contents

Synopsis

Zoom

newtype Focusing m c s Source #

Used by Zoom to zoom into StateT.

Constructors

Focusing 

Fields

Instances
Monad m => Functor (Focusing m c) Source # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

fmap :: (a -> b) -> Focusing m c a -> Focusing m c b #

(<$) :: a -> Focusing m c b -> Focusing m c a #

(Monad m, Monoid s) => Applicative (Focusing m s) Source # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

pure :: a -> Focusing m s a #

(<*>) :: Focusing m s (a -> b) -> Focusing m s a -> Focusing m s b #

liftA2 :: (a -> b -> c) -> Focusing m s a -> Focusing m s b -> Focusing m s c #

(*>) :: Focusing m s a -> Focusing m s b -> Focusing m s b #

(<*) :: Focusing m s a -> Focusing m s b -> Focusing m s a #

stateZoom :: (Is k A_Lens, Monad m) => Optic' k is t s -> (s -> m (c, s)) -> t -> m (c, t) Source #

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 #

Used by Zoom to zoom into RWST.

Constructors

FocusingWith 

Fields

Instances
Monad m => Functor (FocusingWith w m s) Source # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

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 # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

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 #

newtype May a Source #

Make a Monoid out of Maybe for error handling.

Constructors

May 

Fields

Instances
Semigroup a => Semigroup (May a) Source # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

(<>) :: May a -> May a -> May a #

sconcat :: NonEmpty (May a) -> May a #

stimes :: Integral b => b -> May a -> May a #

Monoid a => Monoid (May a) Source # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

mempty :: May a #

mappend :: May a -> May a -> May a #

mconcat :: [May a] -> May a #

newtype Err e a Source #

Make a Monoid out of Either for error handling.

Constructors

Err 

Fields

Instances
Semigroup a => Semigroup (Err e a) Source # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

(<>) :: Err e a -> Err e a -> Err e a #

sconcat :: NonEmpty (Err e a) -> Err e a #

stimes :: Integral b => b -> Err e a -> Err e a #

Monoid a => Monoid (Err e a) Source # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

mempty :: Err e a #

mappend :: Err e a -> Err e a -> Err e a #

mconcat :: [Err e a] -> Err e a #

shuffleErr :: Maybe (Err e c) -> Err e (Maybe c) Source #

Magnify

newtype Effect m r Source #

Wrap a monadic effect.

Constructors

Effect 

Fields

Instances
(Monad m, Semigroup r) => Semigroup (Effect m r) Source # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

(<>) :: Effect m r -> Effect m r -> Effect m r #

sconcat :: NonEmpty (Effect m r) -> Effect m r #

stimes :: Integral b => b -> Effect m r -> Effect m r #

(Monad m, Monoid r) => Monoid (Effect m r) Source # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

mempty :: Effect m r #

mappend :: Effect m r -> Effect m r -> Effect m r #

mconcat :: [Effect m r] -> Effect m r #

newtype EffectRWS w s m c Source #

Wrap a monadic effect. Used when magnifying RWST.

Constructors

EffectRWS 

Fields

Instances
(Semigroup c, Semigroup w, Monad m) => Semigroup (EffectRWS w s m c) Source # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

(<>) :: EffectRWS w s m c -> EffectRWS w s m c -> EffectRWS w s m c #

sconcat :: NonEmpty (EffectRWS w s m c) -> EffectRWS w s m c #

stimes :: Integral b => b -> EffectRWS w s m c -> EffectRWS w s m c #

(Monoid c, Monoid w, Monad m) => Monoid (EffectRWS w s m c) Source # 
Instance details

Defined in Optics.Extra.Internal.Zoom

Methods

mempty :: EffectRWS w s m c #

mappend :: EffectRWS w s m c -> EffectRWS w s m c -> EffectRWS w s m c #

mconcat :: [EffectRWS w s m c] -> EffectRWS w s m c #

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 #

Misc

shuffleS :: s -> Maybe (c, s) -> (Maybe c, s) Source #

shuffleW :: Monoid w => Maybe (c, w) -> (Maybe c, w) Source #