data-effects-0.1.1.0: A basic framework for effect systems based on effects represented by GADTs.
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Effect.ShiftReset

Documentation

data Shift' (r :: Type) m a where Source #

Constructors

Shift :: forall r m a. ((a -> m r) -> m r) -> Shift' r m a 

shift :: forall (r :: Type) (a :: Type) m. SendSigBy ShiftKey (Shift' r) m => ((a -> m r) -> m r) -> m a Source #

shift'' :: forall key (r :: Type) (a :: Type) m. SendSigBy key (Shift' r) m => ((a -> m r) -> m r) -> m a Source #

shift' :: forall tag (r :: Type) (a :: Type) m. SendSig (TagH (Shift' r) tag) m => ((a -> m r) -> m r) -> m a Source #

shift'_ :: forall (r :: Type) (a :: Type) m. SendSig (Shift' r) m => ((a -> m r) -> m r) -> m a Source #

callCC :: forall r m a. (SendSigBy ShiftKey (Shift' r) m, Monad m) => ((a -> m r) -> m a) -> m a Source #

exit :: (SendSigBy ShiftKey (Shift' r) f, Applicative f) => r -> f a Source #

getCC :: (SendSigBy ShiftKey (Shift' r) m, Monad m) => m (m r) Source #

data Shift_ m a where Source #

Constructors

Shift_ :: (forall (r :: Type). (a -> m r) -> m r) -> Shift_ m a 

shift_'' :: forall key (a :: Type) m. SendSigBy key Shift_ m => (forall (r :: Type). (a -> m r) -> m r) -> m a Source #

shift_' :: forall tag (a :: Type) m. SendSig (TagH Shift_ tag) m => (forall (r :: Type). (a -> m r) -> m r) -> m a Source #

shift_ :: forall (a :: Type) m. SendSig Shift_ m => (forall (r :: Type). (a -> m r) -> m r) -> m a Source #

getCC_ :: (Shift_ <<: m, Monad m) => m (m ()) Source #

data Reset m (a :: Type) where Source #

Constructors

Reset :: m a -> Reset m a 

Instances

Instances details
() => HFunctor Reset Source # 
Instance details

Defined in Data.Effect.ShiftReset

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> Reset f :-> Reset g #

reset'' :: forall key (a :: Type) m. SendSigBy key Reset m => m a -> m a Source #

reset' :: forall tag (a :: Type) m. SendSig (TagH Reset tag) m => m a -> m a Source #

reset :: forall (a :: Type) m. SendSig Reset m => m a -> m a Source #