heftia-effects-0.5.0.0: higher-order algebraic effects done right
Safe HaskellNone
LanguageGHC2021

Control.Monad.Hefty.ShiftReset

Documentation

type Shift ans (eh :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]) = Shift ans (ShiftEff ans eh ef) Source #

newtype ShiftEff ans (eh :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]) a Source #

Constructors

ShiftEff 

Fields

Instances

Instances details
Applicative (ShiftEff ans eh ef) Source # 
Instance details

Defined in Control.Monad.Hefty.ShiftReset

Methods

pure :: a -> ShiftEff ans eh ef a #

(<*>) :: ShiftEff ans eh ef (a -> b) -> ShiftEff ans eh ef a -> ShiftEff ans eh ef b #

liftA2 :: (a -> b -> c) -> ShiftEff ans eh ef a -> ShiftEff ans eh ef b -> ShiftEff ans eh ef c #

(*>) :: ShiftEff ans eh ef a -> ShiftEff ans eh ef b -> ShiftEff ans eh ef b #

(<*) :: ShiftEff ans eh ef a -> ShiftEff ans eh ef b -> ShiftEff ans eh ef a #

Functor (ShiftEff ans eh ef) Source # 
Instance details

Defined in Control.Monad.Hefty.ShiftReset

Methods

fmap :: (a -> b) -> ShiftEff ans eh ef a -> ShiftEff ans eh ef b #

(<$) :: a -> ShiftEff ans eh ef b -> ShiftEff ans eh ef a #

Monad (ShiftEff ans eh ef) Source # 
Instance details

Defined in Control.Monad.Hefty.ShiftReset

Methods

(>>=) :: ShiftEff ans eh ef a -> (a -> ShiftEff ans eh ef b) -> ShiftEff ans eh ef b #

(>>) :: ShiftEff ans eh ef a -> ShiftEff ans eh ef b -> ShiftEff ans eh ef b #

return :: a -> ShiftEff ans eh ef a #

evalShift :: forall ans (ef :: [EffectF]). Eff '[Shift ans ('[] :: [(Type -> Type) -> Type -> Type]) ef] ef ans -> Eff ('[] :: [EffectH]) ef ans Source #

runShift :: forall a (ef :: [EffectF]) ans. (a -> Eff ('[] :: [EffectH]) ef ans) -> Eff '[Shift ans ('[] :: [(Type -> Type) -> Type -> Type]) ef] ef a -> Eff ('[] :: [EffectH]) ef ans Source #

withShift :: forall ans (eh :: [EffectH]) (ef :: [EffectF]). Eff '[Shift ans ('[] :: [(Type -> Type) -> Type -> Type]) '[Eff eh ef]] '[Eff eh ef] ans -> Eff eh ef ans Source #

runShift_ :: forall (eh :: [EffectH]) (ef :: [EffectF]) x. Eff (Shift_ (Eff eh ef) ': eh) ef x -> Eff eh ef x Source #

runReset :: forall (eh :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]) x. Eff (Reset ': eh) ef x -> Eff eh ef x Source #

runShiftF :: forall (ef :: [EffectF]) ans. Eff ('[] :: [EffectH]) (ShiftF (Eff ('[] :: [EffectH]) ef ans) ': ef) ans -> Eff ('[] :: [EffectH]) ef ans Source #

runShiftEff :: Monad n => (a -> n ans) -> Eff ('[] :: [EffectH]) '[ShiftF (n ans), n] a -> n ans Source #

runShiftAsF :: forall ans (n :: Type -> Type) (eh :: [EffectH]) (ef :: [Type -> Type]). MemberHBy ShiftKey (Shift' ans n) eh => Eff eh (ShiftF (n ans) ': ef) ~> Eff eh ef Source #

callCC :: forall a m ans n. (SendHOEBy ShiftKey (Shift' ans n) m, Monad m, Monad n) => ((a -> n ans) -> m a) -> m a #

shift :: forall ans n a m. SendHOEBy ShiftKey (Shift' ans n) m => ((a -> n ans) -> (forall x. m x -> n x) -> n ans) -> m a #

reset :: forall a m. SendHOE Reset m => m a -> m a #

data Shift' ans (n :: Type -> Type) (m :: Type -> Type) a where #

Constructors

Shift :: forall ans (n :: Type -> Type) (m :: Type -> Type) a. ((a -> n ans) -> (forall x. m x -> n x) -> n ans) -> Shift' ans n m a 

Instances

Instances details
() => HFunctor (Shift' ans n) 
Instance details

Defined in Data.Effect.ShiftReset

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> Shift' ans n f :-> Shift' ans n g #

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

Constructors

Shift_' :: forall a (n :: Type -> Type) (m :: Type -> Type). (forall ans. (a -> n ans) -> (forall x. m x -> n x) -> n ans) -> Shift_' n m a 

Instances

Instances details
() => HFunctor (Shift_' n) 
Instance details

Defined in Data.Effect.ShiftReset

Methods

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

data ShiftKey #

shift'_ :: forall ans n a m. SendHOE (Shift' ans n) m => ((a -> n ans) -> (forall x. m x -> n x) -> n ans) -> m a #

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

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

exit :: forall a m ans (n :: Type -> Type). (SendHOEBy ShiftKey (Shift' ans n) m, Applicative n) => ans -> m a #

getCC :: forall m ans n. (SendHOEBy ShiftKey (Shift' ans n) m, Monad m, Monad n) => m (n ans) #

embed :: forall (m :: Type -> Type) ans (n :: Type -> Type). (SendHOEBy ShiftKey (Shift' ans n) m, Monad n) => n ~> m #

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

Constructors

Reset :: forall (m :: Type -> Type) a. m a -> Reset m a 

Instances

Instances details
() => HFunctor Reset 
Instance details

Defined in Data.Effect.ShiftReset

Methods

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

type Shift_ (n :: Type -> Type) = Shift_Key ##> Shift_' n #

shift_''_ :: forall a n m. SendHOE (Shift_' n) m => (forall ans. (a -> n ans) -> (forall x. m x -> n x) -> n ans) -> m a #

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

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

shift_' :: forall a n m. SendHOEBy Shift_Key (Shift_' n) m => (forall ans. (a -> n ans) -> (forall x. m x -> n x) -> n ans) -> m a #

getCC_ :: forall m n. (SendHOEBy Shift_Key (Shift_' n) m, Functor n) => m (n ()) #

data ShiftF ans a where #

Constructors

ShiftF :: forall ans a. ((a -> ans) -> ans) -> ShiftF ans a 

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

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

type LShiftF ans = LiftFOE (ShiftF ans) #

pattern LShiftF :: forall a ans f a1. () => (a ~ a1, ()) => ((a1 -> ans) -> ans) -> LiftFOE (ShiftF ans) f a #

shiftF :: forall ans a f. SendFOE (ShiftF ans) f => ((a -> ans) -> ans) -> f a #

shiftF' :: forall {k} (tag :: k) ans a f. SendFOE (Tag (ShiftF ans) tag) f => ((a -> ans) -> ans) -> f a #

shiftF'' :: forall {k} (key :: k) ans a f. SendFOEBy key (ShiftF ans) f => ((a -> ans) -> ans) -> f a #

fromShiftF :: forall n ans (m :: Type -> Type) x. ShiftF (n ans) x -> Shift ans n m x #

exitF :: ShiftF ans <: m => ans -> m a #

embedF :: forall ans (n :: Type -> Type) (m :: Type -> Type). (ShiftF (n ans) <: m, Monad n) => n ~> m #