Copyright | (c) 2025 Sayo contributors |
---|---|
License | MPL-2.0 (see the LICENSE file) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Data.Effect.Shift
Description
Documentation
data Shift ans ref :: Effect where Source #
Constructors
SubShiftFork :: Shift ans ref f (Either (ref a) a) | |
Call :: ref a -> a -> Shift ans ref f ans | |
Abort :: ans -> Shift ans ref f a |
Instances
FirstOrder (Shift ans ref) Source # | |
Defined in Data.Effect.Shift | |
HFunctor (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 #
abort'_ :: forall (ans :: Type) (ref :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In (Shift ans ref) es) => ans -> f a Source #
abort'' :: forall tag (ans :: Type) (ref :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Tagged tag (Shift ans ref)) es) => ans -> f a Source #
abort' :: forall key (ans :: Type) (ref :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, Has key (Shift ans ref) es) => ans -> f a Source #
abort :: forall (ans :: Type) (ref :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Shift ans ref) es) => ans -> f a Source #
call'_ :: forall (ref :: Type -> Type) (a :: Type) (ans :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In (Shift ans ref) es) => ref a -> a -> f ans Source #
call'' :: forall tag (ref :: Type -> Type) (a :: Type) (ans :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Tagged tag (Shift ans ref)) es) => ref a -> a -> f ans Source #
call' :: forall key (ref :: Type -> Type) (a :: Type) (ans :: Type) f es ff c. (Free c ff, f ~ Eff ff es, Has key (Shift ans ref) es) => ref a -> a -> f ans Source #
call :: forall (ref :: Type -> Type) (a :: Type) (ans :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Shift ans ref) es) => ref a -> a -> f ans Source #
subShiftFork'_ :: forall (ans :: Type) (ref :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In (Shift ans ref) es) => f (Either (ref a) a) Source #
subShiftFork'' :: forall tag (ans :: Type) (ref :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Tagged tag (Shift ans ref)) es) => f (Either (ref a) a) Source #
subShiftFork' :: forall key (ans :: Type) (ref :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, Has key (Shift ans ref) es) => f (Either (ref a) a) Source #
subShiftFork :: forall (ans :: Type) (ref :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Shift ans ref) es) => f (Either (ref a) a) Source #
subShift :: forall a b es ans ref ff c. (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 ans ref ff c. (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 ans ref ff c. (Shift ans ref :> es, Monad (Eff ff es), Free c ff) => Eff ff es (Eff ff es ans) Source #