Safe Haskell | None |
---|---|
Language | GHC2021 |
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 #
ShiftEff | |
|
Instances
Applicative (ShiftEff ans eh ef) Source # | |
Defined in Control.Monad.Hefty.ShiftReset 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 # | |
Monad (ShiftEff ans eh ef) Source # | |
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 #
data Shift' ans (n :: Type -> Type) (m :: Type -> Type) a where #
data Shift_' (n :: Type -> Type) (m :: Type -> Type) a where #
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 #
embed :: forall (m :: Type -> Type) ans (n :: Type -> Type). (SendHOEBy ShiftKey (Shift' ans n) m, Monad n) => n ~> m #
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 #
pattern LShiftF :: forall a ans f a1. () => (a ~ a1, ()) => ((a1 -> ans) -> ans) -> LiftFOE (ShiftF ans) f a #
shiftF' :: forall {k} (tag :: k) ans a f. SendFOE (Tag (ShiftF ans) tag) f => ((a -> ans) -> ans) -> f a #