data-effects-0.2.0.0: A basic framework for effect systems based on effects represented by GADTs.
Safe HaskellNone
LanguageGHC2021

Data.Effect.ShiftReset

Documentation

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

Constructors

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

Instances

Instances details
() => HFunctor (Shift' r b) Source # 
Instance details

Defined in Data.Effect.ShiftReset

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> Shift' r b f :-> Shift' r b g #

type Shift r (b :: Type -> Type) = ShiftKey ##> Shift' r b Source #

shift'_ :: forall r b a m. SendHOE (Shift' r b) m => ((a -> b r) -> (forall x. m x -> b x) -> b r) -> m a Source #

shift' :: forall {k} (tag :: k) r b a m. SendHOE (TagH (Shift' r b) tag) m => ((a -> b r) -> (forall x. m x -> b x) -> b r) -> m a Source #

shift'' :: forall {k} (key :: k) r b a m. SendHOEBy key (Shift' r b) m => ((a -> b r) -> (forall x. m x -> b x) -> b r) -> m a Source #

shift :: forall r b a m. SendHOEBy ShiftKey (Shift' r b) m => ((a -> b r) -> (forall x. m x -> b x) -> b r) -> m a Source #

callCC :: (SendHOEBy ShiftKey (Shift' r b) m, Monad m, Monad b) => ((a -> b r) -> m a) -> m a Source #

exit :: forall r (b :: Type -> Type) m a. (SendHOEBy ShiftKey (Shift' r b) m, Applicative b) => r -> m a Source #

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

data Shift_' (b :: Type -> Type) (m :: Type -> Type) a where Source #

Constructors

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

Instances

Instances details
() => HFunctor (Shift_' b) Source # 
Instance details

Defined in Data.Effect.ShiftReset

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> Shift_' b f :-> Shift_' b g #

shift_''_ :: forall a b m. SendHOE (Shift_' b) m => (forall r. (a -> b r) -> (forall x. m x -> b x) -> b r) -> m a Source #

shift_'' :: forall {k} (tag :: k) a b m. SendHOE (TagH (Shift_' b) tag) m => (forall r. (a -> b r) -> (forall x. m x -> b x) -> b r) -> m a Source #

shift_''' :: forall {k} (key :: k) a b m. SendHOEBy key (Shift_' b) m => (forall r. (a -> b r) -> (forall x. m x -> b x) -> b r) -> m a Source #

shift_' :: forall a b m. SendHOEBy Shift_Key (Shift_' b) m => (forall r. (a -> b r) -> (forall x. m x -> b x) -> b r) -> m a Source #

getCC_ :: (SendHOEBy Shift_Key (Shift_' b) m, Functor b) => m (b ()) Source #

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

Constructors

Reset :: forall (m :: Type -> Type) a. 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 a m. SendHOE Reset m => m a -> m a Source #

reset' :: forall {k} (tag :: k) a m. SendHOE (TagH Reset tag) m => m a -> m a Source #

reset'' :: forall {k} (key :: k) a m. SendHOEBy key Reset m => m a -> m a Source #