heftia-effects-0.7.0.0: higher-order algebraic effects done right
Copyright(c) 2024 Sayo contributors
LicenseMPL-2.0 (see the LICENSE file)
Maintainerymdfield@outlook.jp
Safe HaskellNone
LanguageGHC2021

Control.Monad.Hefty.Concurrent.Stream

Description

Coroutine-based, composable, and resumable concurrent streams.

Synopsis

Documentation

data Machinery (es :: [(Type -> Type) -> Type -> Type]) ans i o where Source #

Constructors

Unit :: forall i o ans (es :: [(Type -> Type) -> Type -> Type]). Eff (Input i ': (Output o ': es)) ans -> Machinery es ans i o 
Connect :: forall i b o ans (es :: [(Type -> Type) -> Type -> Type]). Machinery es ans i b -> Machinery es ans b o -> Machinery es ans i o 

Instances

Instances details
Category (Machinery es ans :: Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Stream

Methods

id :: Machinery es ans a a #

(.) :: Machinery es ans b c -> Machinery es ans a b -> Machinery es ans a c #

FOEs es => Arrow (Machinery es ans) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Stream

Methods

arr :: (b -> c) -> Machinery es ans b c #

first :: Machinery es ans b c -> Machinery es ans (b, d) (c, d) #

second :: Machinery es ans b c -> Machinery es ans (d, b) (d, c) #

(***) :: Machinery es ans b c -> Machinery es ans b' c' -> Machinery es ans (b, b') (c, c') #

(&&&) :: Machinery es ans b c -> Machinery es ans b c' -> Machinery es ans b (c, c') #

FOEs es => ArrowChoice (Machinery es ans) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Stream

Methods

left :: Machinery es ans b c -> Machinery es ans (Either b d) (Either c d) #

right :: Machinery es ans b c -> Machinery es ans (Either d b) (Either d c) #

(+++) :: Machinery es ans b c -> Machinery es ans b' c' -> Machinery es ans (Either b b') (Either c c') #

(|||) :: Machinery es ans b d -> Machinery es ans c d -> Machinery es ans (Either b c) d #

data MachineStatus (f :: Type -> Type) ans i o Source #

Constructors

Terminated ans 
Waiting (i -> Machine f ans i o) 
Produced o (Machine f ans i o) 

machine :: forall (es :: [Effect]) i o ans. WeakenHOEs es => Eff (Input i ': (Output o ': RemoveHOEs es)) ans -> Machine (Eff es) ans i o Source #

buffering :: forall b c d ans (es :: [(Type -> Type) -> Type -> Type]). Eff (Input b ': (Output c ': es)) ans -> Eff (State (Either (Seq c) d) ': (Input (b, d) ': (Output (c, d) ': es))) ans Source #

leftMachinery :: forall b c d ans (es :: [(Type -> Type) -> Type -> Type]). Machinery es ans b c -> Machinery es ans (Either b d) (Either c d) Source #

newtype Machine (f :: Type -> Type) ans i o Source #

Constructors

Machine 

Fields

runMachinery :: forall i o ans (es :: [Effect]). (Parallel :> es, Semigroup ans, WeakenHOEs es) => Machinery (RemoveHOEs es) ans i o -> Eff es (MachineStatus (Eff es) ans i o) Source #

runMachineryL :: forall i o ans (es :: [Effect]). (Parallel :> es, Semigroup ans, WeakenHOEs es) => MachineryViewL (RemoveHOEs es) ans i o -> Eff es (MachineStatus (Eff es) ans i o) Source #

mviewl :: forall (es :: [(Type -> Type) -> Type -> Type]) ans i o. Machinery es ans i o -> MachineryViewL es ans i o Source #

Left view deconstruction for Machinery Pipeline. [average O(1)]

data MachineryViewL (es :: [(Type -> Type) -> Type -> Type]) ans i o where Source #

Left view deconstruction data structure for Machinery Pipeline.

This allows the number of generated threads to be reduced to the number of machine units.

Constructors

MOne :: forall i o ans (es :: [(Type -> Type) -> Type -> Type]). Eff (Input i ': (Output o ': es)) ans -> MachineryViewL es ans i o 
MCons :: forall i b o ans (es :: [(Type -> Type) -> Type -> Type]). Eff (Input i ': (Output b ': es)) ans -> Machinery es ans b o -> MachineryViewL es ans i o 

newtype MachineryIO (es :: [(Type -> Type) -> Type -> Type]) ans i o Source #

Constructors

MachineryIO 

Fields

Instances

Instances details
Category (MachineryIO es ans :: Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Stream

Methods

id :: MachineryIO es ans a a #

(.) :: MachineryIO es ans b c -> MachineryIO es ans a b -> MachineryIO es ans a c #

Emb IO :> es => Arrow (MachineryIO es ans) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Stream

Methods

arr :: (b -> c) -> MachineryIO es ans b c #

first :: MachineryIO es ans b c -> MachineryIO es ans (b, d) (c, d) #

second :: MachineryIO es ans b c -> MachineryIO es ans (d, b) (d, c) #

(***) :: MachineryIO es ans b c -> MachineryIO es ans b' c' -> MachineryIO es ans (b, b') (c, c') #

(&&&) :: MachineryIO es ans b c -> MachineryIO es ans b c' -> MachineryIO es ans b (c, c') #

Emb IO :> es => ArrowChoice (MachineryIO es ans) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Stream

Methods

left :: MachineryIO es ans b c -> MachineryIO es ans (Either b d) (Either c d) #

right :: MachineryIO es ans b c -> MachineryIO es ans (Either d b) (Either d c) #

(+++) :: MachineryIO es ans b c -> MachineryIO es ans b' c' -> MachineryIO es ans (Either b b') (Either c c') #

(|||) :: MachineryIO es ans b d -> MachineryIO es ans c d -> MachineryIO es ans (Either b c) d #

runMachineryIO :: forall i o ans (es :: [Effect]). (UnliftIO :> es, Emb IO :> es) => Eff es i -> (o -> Eff es ()) -> Machinery es ans i o -> Eff es ans Source #

runMachineryIOL :: forall i o ans (es :: [Effect]). (UnliftIO :> es, Emb IO :> es) => Eff es i -> (o -> Eff es ()) -> MachineryViewL es ans i o -> Eff es ans Source #

runMachineryIO_ :: forall ans (es :: [Effect]). (UnliftIO :> es, Emb IO :> es) => Machinery es ans () () -> Eff es ans Source #