Copyright | (c) 2016 Allele Dev; 2017 Ixperta Solutions s.r.o.; 2017 Alexis King (c) 2023-2025 Sayo contributors |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Data.Effect.Coroutine
Description
This module provides effects for the coroutine, comes
from Control.Monad.Freer.Coroutine
in the freer-simple
package (The continuation part (b -> c)
has been removed. If necessary, please manually compose the Coyoneda
) .
Synopsis
- data Yield a b (c :: Type -> Type) d where
- data YieldLabel
- yield :: forall a b f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Yield a b :> es) => a -> f b
- yield' :: forall {k} (key :: k) a b f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Yield a b) es) => a -> f b
- yield'' :: forall {k} (tag :: k) a b f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Yield a b) :> es) => a -> f b
- yield'_ :: forall a b f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Yield a b) es) => a -> f b
- data Status (f :: Type -> Type) a b r
- continueStatus :: Monad m => (x -> m (Status m a b r)) -> Status m a b x -> m (Status m a b r)
- loopStatus :: Monad m => (a -> m b) -> Status m a b r -> m r
- inputToYield :: forall i (f :: Type -> Type) a. Input i f a -> Yield () i f a
- outputToYield :: forall o (f :: Type -> Type) a. Output o f a -> Yield o () f a
Documentation
data Yield a b (c :: Type -> Type) d where Source #
An effect for coroutines.
Realizes an operation that transfers control to the caller of the computation with coroutines along with a value of type a
,
and receives a value of type b
from the caller.
Constructors
Yield :: forall a b (c :: Type -> Type). a -> Yield a b c b | Transfers control to the caller of the computation with coroutines along with a value of type |
Instances
FirstOrder (Yield a b) Source # | |
Defined in Data.Effect.Coroutine | |
PolyHFunctor (Yield a b) Source # | |
Defined in Data.Effect.Coroutine | |
HFunctor (Yield a b) Source # | |
Defined in Data.Effect.Coroutine | |
type FormOf (Yield a b) Source # | |
Defined in Data.Effect.Coroutine | |
type LabelOf (Yield a b) Source # | |
Defined in Data.Effect.Coroutine | |
type OrderOf (Yield a b) Source # | |
Defined in Data.Effect.Coroutine |
data YieldLabel Source #
yield :: forall a b f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Yield a b :> es) => a -> f b Source #
Transfers control to the caller of the computation with coroutines along with a value of type a
, and receives a value of type b
from the caller.
yield' :: forall {k} (key :: k) a b f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Yield a b) es) => a -> f b Source #
Transfers control to the caller of the computation with coroutines along with a value of type a
, and receives a value of type b
from the caller.
yield'' :: forall {k} (tag :: k) a b f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Yield a b) :> es) => a -> f b Source #
Transfers control to the caller of the computation with coroutines along with a value of type a
, and receives a value of type b
from the caller.
yield'_ :: forall a b f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Yield a b) es) => a -> f b Source #
Transfers control to the caller of the computation with coroutines along with a value of type a
, and receives a value of type b
from the caller.
data Status (f :: Type -> Type) a b r Source #
The execution result when handling a computation that includes the Yield
effect. A computation that may include suspension.
If the computation does not include yield
, the completed result of the computation is obtained as Done
.
If the computation includes yield
, execution is suspended at that point, and the value of type a
thrown by yield
and the continuation of the computation from the point of yield
are obtained as Continue
.
By re-executing this continuation, you can resume the computation.
Arguments
:: Monad m | |
=> (x -> m (Status m a b r)) | Additional continuation |
-> Status m a b x | Computation status to extend |
-> m (Status m a b r) |
Extends the computation result by appending the specified continuation.
Arguments
:: Monad m | |
=> (a -> m b) | Handler to resume computation from a suspended state. |
-> Status m a b r | A computation that may include suspension. |
-> m r |
Repeats the computation until the final result is obtained by continuing the computation using the specified handler each time it suspends.