data-effects-0.1.2.0: A basic framework for effect systems based on effects represented by GADTs.
Copyright(c) 2016 Allele Dev; 2017 Ixperta Solutions s.r.o.; 2017 Alexis King
(c) 2023-2024 Yamada Ryo
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Effect.Coroutine

Description

This module provides the Coroutine effect, 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) .

Documentation

data Yield a b (c :: Type) where Source #

Constructors

Yield :: a -> Yield a b b 

type LYield a b = LiftIns (Yield a b) Source #

pattern LYield :: () => (a ~ b, ()) => a -> LiftIns (Yield a b) f a Source #

yield'' :: forall key (a :: Type) (b :: Type) f. SendInsBy key (Yield a b) f => a -> f b Source #

yield' :: forall tag (a :: Type) (b :: Type) f. SendIns (Tag (Yield a b) tag) f => a -> f b Source #

yield :: forall (a :: Type) (b :: Type) f. SendIns (Yield a b) f => a -> f b Source #

yield_ :: Yield a () <: f => a -> f () Source #

data Status f a b r Source #

Constructors

Done r 
Coroutine a (b -> f (Status f a b r)) 

Instances

Instances details
Functor f => Functor (Status f a b) Source # 
Instance details

Defined in Data.Effect.Coroutine

Methods

fmap :: (a0 -> b0) -> Status f a b a0 -> Status f a b b0 #

(<$) :: a0 -> Status f a b b0 -> Status f a b a0 #

continueStatus :: Monad m => (x -> m (Status m a b r)) -> Status m a b x -> m (Status m a b r) Source #

loopStatus :: Monad m => (a -> m b) -> Status m a b r -> m r Source #