Copyright | (c) 2025 Sayo contributors |
---|---|
License | MPL-2.0 (see the LICENSE file) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Data.Effect.Shift
Description
Documentation
data Shift ans (ref :: Type -> Type) (a :: Type -> Type) b where Source #
Constructors
SubShiftFork :: forall ans (ref :: Type -> Type) (a :: Type -> Type) a1. Shift ans ref a (Either (ref a1) a1) | |
Call :: forall (ref :: Type -> Type) a1 ans (a :: Type -> Type). ref a1 -> a1 -> Shift ans ref a ans | |
Abort :: forall ans (ref :: Type -> Type) (a :: Type -> Type) b. ans -> Shift ans ref a b |
Instances
FirstOrder (Shift ans ref) Source # | |
Defined in Data.Effect.Shift | |
PolyHFunctor (Shift ans ref) Source # | |
Defined in Data.Effect.Shift | |
HFunctor (Shift ans ref) Source # | |
Defined in Data.Effect.Shift | |
type FormOf (Shift ans ref) Source # | |
Defined in Data.Effect.Shift | |
type LabelOf (Shift ans ref) Source # | |
Defined in Data.Effect.Shift | |
type OrderOf (Shift ans ref) Source # | |
Defined in Data.Effect.Shift |
data ShiftLabel Source #
subShiftFork :: forall ans ref a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Shift ans ref :> es) => f (Either (ref a) a) Source #
subShiftFork' :: forall {k} (key :: k) ans ref a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Shift ans ref) es) => f (Either (ref a) a) Source #
subShiftFork'' :: forall {k} (tag :: k) ans ref a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Shift ans ref) :> es) => f (Either (ref a) a) Source #
subShiftFork'_ :: forall ans ref a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Shift ans ref) es) => f (Either (ref a) a) Source #
call :: forall ref a ans f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Shift ans ref :> es) => ref a -> a -> f ans Source #
call' :: forall {k} (key :: k) ref a ans f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Shift ans ref) es) => ref a -> a -> f ans Source #
call'' :: forall {k} (tag :: k) ref a ans f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Shift ans ref) :> es) => ref a -> a -> f ans Source #
call'_ :: forall ref a ans f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Shift ans ref) es) => ref a -> a -> f ans Source #
abort :: forall ans (ref :: Type -> Type) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Shift ans ref :> es) => ans -> f a Source #
abort' :: forall {k} (key :: k) ans (ref :: Type -> Type) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Shift ans ref) es) => ans -> f a Source #
abort'' :: forall {k} (tag :: k) ans (ref :: Type -> Type) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Shift ans ref) :> es) => ans -> f a Source #
abort'_ :: forall ans (ref :: Type -> Type) a f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Shift ans ref) es) => ans -> f a Source #
subShift :: forall a b (es :: [Effect]) ans ref (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Shift ans ref :> es, Monad (Eff ff es), Free c ff) => (ref a -> Eff ff es b) -> (a -> Eff ff es b) -> Eff ff es b Source #
shift :: forall a (es :: [Effect]) ans (ref :: Type -> Type) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Shift ans ref :> es, Monad (Eff ff es), Free c ff) => ((a -> Eff ff es ans) -> Eff ff es ans) -> Eff ff es a Source #
getShiftCC :: forall (es :: [Effect]) ans (ref :: Type -> Type) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Shift ans ref :> es, Monad (Eff ff es), Free c ff) => Eff ff es (Eff ff es ans) Source #