Copyright | (c) 2023-2025 Sayo contributors |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Control.Effect
Description
Synopsis
- newtype Eff (ff :: (Type -> Type) -> Type -> Type) (es :: [Effect]) a = Eff {}
- perform :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (e :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- perform' :: forall {k} (key :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Has key e es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- perform'' :: forall {k} (tag :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). ((e # tag) :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- send :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- sendAt :: forall (i :: Nat) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownIndex i es, Free c ff) => At i es (Eff ff es) a -> Eff ff es a
- sendFor :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownOrder e, Free c ff) => Membership e es -> e (Eff ff es) a -> Eff ff es a
- emb :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb f :> es, Free c ff) => f a -> Eff ff es a
- type (~>) (f :: Type -> Type) (g :: Type -> Type) = forall x. f x -> g x
- type (~~>) (e :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) = e f ~> f
- type ($) (f :: Type -> Type) a = f a
- type ($$) (h :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) = h f
- pass :: forall w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Tell w :> es, WriterH w :> es, Monad (Eff ff es), Free c ff) => Eff ff es (w -> w, a) -> Eff ff es a
- sub :: forall ref a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (CC ref :> es, Monad (Eff ff es), Free c ff) => (ref a -> Eff ff es b) -> (a -> Eff ff es b) -> Eff ff es b
- callCC_ :: forall (ref :: Type -> Type) a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (CC ref :> es, Monad (Eff ff es), Free c ff) => ((a -> Eff ff es b) -> Eff ff es a) -> Eff ff es a
- class (forall (f :: Type -> Type). c (ff f)) => Free (c :: (Type -> Type) -> Constraint) (ff :: (Type -> Type) -> Type -> Type) | ff -> c where
- convertEff :: forall (ff :: (Type -> Type) -> Type -> Type) (gg :: (Type -> Type) -> Type -> Type) (es :: [Effect]) a (c :: (Type -> Type) -> Constraint) (c' :: (Type -> Type) -> Constraint). (Free c ff, Free c' gg, forall (r :: Type -> Type). c (gg r)) => Eff ff es a -> Eff gg es a
- convertFree :: forall (c :: (Type -> Type) -> Constraint) ff (c' :: (Type -> Type) -> Constraint) gg (r :: Type -> Type) a. (Free c ff, Free c' gg, c (gg r)) => ff r a -> gg r a
Documentation
newtype Eff (ff :: (Type -> Type) -> Type -> Type) (es :: [Effect]) a Source #
Instances
perform :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (e :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a Source #
perform' :: forall {k} (key :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Has key e es, Free c ff) => e (Eff ff es) a -> Eff ff es a Source #
perform'' :: forall {k} (tag :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). ((e # tag) :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a Source #
send :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => e (Eff ff es) a -> Eff ff es a Source #
sendAt :: forall (i :: Nat) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownIndex i es, Free c ff) => At i es (Eff ff es) a -> Eff ff es a Source #
sendFor :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownOrder e, Free c ff) => Membership e es -> e (Eff ff es) a -> Eff ff es a Source #
emb :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb f :> es, Free c ff) => f a -> Eff ff es a Source #
type (~>) (f :: Type -> Type) (g :: Type -> Type) = forall x. f x -> g x infixr 2 Source #
A natural transformation.
type ($$) (h :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) = h f infixr 4 Source #
Type-level infix applcation for higher-order functors.
pass :: forall w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Tell w :> es, WriterH w :> es, Monad (Eff ff es), Free c ff) => Eff ff es (w -> w, a) -> Eff ff es a Source #
For a given scope, uses the function (the first component of the pair returned by that scope) to modify the accumulated value of that scope, and then accumulates the result into the current outer scope.
pass m = do (w, (f, a)) <- listen m tell $ f w pure a
sub :: forall ref a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (CC 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 #
callCC_ :: forall (ref :: Type -> Type) a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (CC ref :> es, Monad (Eff ff es), Free c ff) => ((a -> Eff ff es b) -> Eff ff es a) -> Eff ff es a Source #
class (forall (f :: Type -> Type). c (ff f)) => Free (c :: (Type -> Type) -> Constraint) (ff :: (Type -> Type) -> Type -> Type) | ff -> c where Source #
Methods
liftFree :: f a -> ff f a Source #
runFree :: c g => (forall x. f x -> g x) -> ff f a -> g a Source #
retract :: c f => ff f a -> f a Source #
hoist :: (forall x. f x -> g x) -> ff f a -> ff g a Source #
convertEff :: forall (ff :: (Type -> Type) -> Type -> Type) (gg :: (Type -> Type) -> Type -> Type) (es :: [Effect]) a (c :: (Type -> Type) -> Constraint) (c' :: (Type -> Type) -> Constraint). (Free c ff, Free c' gg, forall (r :: Type -> Type). c (gg r)) => Eff ff es a -> Eff gg es a Source #
convertFree :: forall (c :: (Type -> Type) -> Constraint) ff (c' :: (Type -> Type) -> Constraint) gg (r :: Type -> Type) a. (Free c ff, Free c' gg, c (gg r)) => ff r a -> gg r a Source #