Copyright | (c) 2024 Sayo Koyoneda |
---|---|
License | MPL-2.0 (see the LICENSE file) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Control.Monad.Hefty.Concurrent.Stream
Description
Coroutine-based, composable, and resumable concurrent streams.
Synopsis
- data Machinery (eh :: [EffectH]) (ef :: [Type -> Type]) ans i o where
- data MachineStatus (f :: Type -> Type) ans i o
- = Terminated ans
- | Waiting (i -> Machine f ans i o)
- | Produced o (Machine f ans i o)
- machine :: forall i o (ef :: [Type -> Type]) ans (eh :: [EffectH]). Eff ('[] :: [EffectH]) (Input i ': (Output o ': ef)) ans -> Machine (Eff eh ef) ans i o
- buffering :: forall b c d ans (eh :: [EffectH]) (ef :: [Type -> Type]). Eff eh (Input b ': (Output c ': ef)) ans -> Eff eh (State (Either (Seq c) d) ': (Input (b, d) ': (Output (c, d) ': ef))) ans
- leftMachinery :: forall b c d ans (eh :: [EffectH]) (ef :: [Type -> Type]). Machinery eh ef ans b c -> Machinery eh ef ans (Either b d) (Either c d)
- newtype Machine (f :: Type -> Type) ans i o = Machine {
- runMachine :: f (MachineStatus f ans i o)
- runMachinery :: forall i o ans (eh :: [EffectH]) (ef :: [Type -> Type]). (Parallel <<| eh, Semigroup ans) => Machinery ('[] :: [EffectH]) ef ans i o -> Eff eh ef (MachineStatus (Eff eh ef) ans i o)
- runMachineryL :: forall i o ans (eh :: [EffectH]) (ef :: [Type -> Type]). (Parallel <<| eh, Semigroup ans) => MachineryViewL ('[] :: [EffectH]) ef ans i o -> Eff eh ef (MachineStatus (Eff eh ef) ans i o)
- mviewl :: forall (eh :: [EffectH]) (ef :: [Type -> Type]) ans i o. Machinery eh ef ans i o -> MachineryViewL eh ef ans i o
- data MachineryViewL (eh :: [EffectH]) (ef :: [Type -> Type]) ans i o where
- MOne :: forall i o ans (eh :: [EffectH]) (ef :: [Type -> Type]). Eff eh (Input i ': (Output o ': ef)) ans -> MachineryViewL eh ef ans i o
- MCons :: forall i b o ans (eh :: [EffectH]) (ef :: [Type -> Type]). Eff eh (Input i ': (Output b ': ef)) ans -> Machinery eh ef ans b o -> MachineryViewL eh ef ans i o
- newtype MachineryIO (eh :: [EffectH]) (ef :: [Type -> Type]) ans i o = MachineryIO {
- unMachineryIO :: Machinery eh ef ans i o
- runMachineryIO :: forall i o ans (eh :: [EffectH]) (ef :: [EffectF]). (UnliftIO <<| eh, IO <| ef) => Eff eh ef i -> (o -> Eff eh ef ()) -> Machinery eh ef ans i o -> Eff eh ef ans
- runMachineryIOL :: forall i o ans (eh :: [EffectH]) (ef :: [EffectF]). (UnliftIO <<| eh, IO <| ef) => Eff eh ef i -> (o -> Eff eh ef ()) -> MachineryViewL eh ef ans i o -> Eff eh ef ans
- runMachineryIO_ :: forall ans (eh :: [EffectH]) (ef :: [EffectF]). (UnliftIO <<| eh, IO <| ef) => Machinery eh ef ans () () -> Eff eh ef ans
- module Control.Monad.Hefty.Input
- module Control.Monad.Hefty.Output
Documentation
data Machinery (eh :: [EffectH]) (ef :: [Type -> Type]) ans i o where Source #
Constructors
Unit :: forall i o ans (eh :: [EffectH]) (ef :: [Type -> Type]). Eff eh (Input i ': (Output o ': ef)) ans -> Machinery eh ef ans i o | |
Connect :: forall i b o ans (eh :: [EffectH]) (ef :: [Type -> Type]). Machinery eh ef ans i b -> Machinery eh ef ans b o -> Machinery eh ef ans i o |
Instances
Category (Machinery eh ef ans :: Type -> Type -> Type) Source # | |
Arrow (Machinery ('[] :: [EffectH]) ef ans) Source # | |
Defined in Control.Monad.Hefty.Concurrent.Stream Methods arr :: (b -> c) -> Machinery ('[] :: [EffectH]) ef ans b c # first :: Machinery ('[] :: [EffectH]) ef ans b c -> Machinery ('[] :: [EffectH]) ef ans (b, d) (c, d) # second :: Machinery ('[] :: [EffectH]) ef ans b c -> Machinery ('[] :: [EffectH]) ef ans (d, b) (d, c) # (***) :: Machinery ('[] :: [EffectH]) ef ans b c -> Machinery ('[] :: [EffectH]) ef ans b' c' -> Machinery ('[] :: [EffectH]) ef ans (b, b') (c, c') # (&&&) :: Machinery ('[] :: [EffectH]) ef ans b c -> Machinery ('[] :: [EffectH]) ef ans b c' -> Machinery ('[] :: [EffectH]) ef ans b (c, c') # | |
ArrowChoice (Machinery ('[] :: [EffectH]) ef ans) Source # | |
Defined in Control.Monad.Hefty.Concurrent.Stream Methods left :: Machinery ('[] :: [EffectH]) ef ans b c -> Machinery ('[] :: [EffectH]) ef ans (Either b d) (Either c d) # right :: Machinery ('[] :: [EffectH]) ef ans b c -> Machinery ('[] :: [EffectH]) ef ans (Either d b) (Either d c) # (+++) :: Machinery ('[] :: [EffectH]) ef ans b c -> Machinery ('[] :: [EffectH]) ef ans b' c' -> Machinery ('[] :: [EffectH]) ef ans (Either b b') (Either c c') # (|||) :: Machinery ('[] :: [EffectH]) ef ans b d -> Machinery ('[] :: [EffectH]) ef ans c d -> Machinery ('[] :: [EffectH]) ef 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 i o (ef :: [Type -> Type]) ans (eh :: [EffectH]). Eff ('[] :: [EffectH]) (Input i ': (Output o ': ef)) ans -> Machine (Eff eh ef) ans i o Source #
buffering :: forall b c d ans (eh :: [EffectH]) (ef :: [Type -> Type]). Eff eh (Input b ': (Output c ': ef)) ans -> Eff eh (State (Either (Seq c) d) ': (Input (b, d) ': (Output (c, d) ': ef))) ans Source #
leftMachinery :: forall b c d ans (eh :: [EffectH]) (ef :: [Type -> Type]). Machinery eh ef ans b c -> Machinery eh ef 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 (eh :: [EffectH]) (ef :: [Type -> Type]). (Parallel <<| eh, Semigroup ans) => Machinery ('[] :: [EffectH]) ef ans i o -> Eff eh ef (MachineStatus (Eff eh ef) ans i o) Source #
runMachineryL :: forall i o ans (eh :: [EffectH]) (ef :: [Type -> Type]). (Parallel <<| eh, Semigroup ans) => MachineryViewL ('[] :: [EffectH]) ef ans i o -> Eff eh ef (MachineStatus (Eff eh ef) ans i o) Source #
mviewl :: forall (eh :: [EffectH]) (ef :: [Type -> Type]) ans i o. Machinery eh ef ans i o -> MachineryViewL eh ef ans i o Source #
Left view deconstruction for Machinery Pipeline. [average O(1)]
data MachineryViewL (eh :: [EffectH]) (ef :: [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 (eh :: [EffectH]) (ef :: [Type -> Type]). Eff eh (Input i ': (Output o ': ef)) ans -> MachineryViewL eh ef ans i o | |
MCons :: forall i b o ans (eh :: [EffectH]) (ef :: [Type -> Type]). Eff eh (Input i ': (Output b ': ef)) ans -> Machinery eh ef ans b o -> MachineryViewL eh ef ans i o |
newtype MachineryIO (eh :: [EffectH]) (ef :: [Type -> Type]) ans i o Source #
Constructors
MachineryIO | |
Fields
|
Instances
Category (MachineryIO eh ef ans :: Type -> Type -> Type) Source # | |
Defined in Control.Monad.Hefty.Concurrent.Stream Methods id :: MachineryIO eh ef ans a a # (.) :: MachineryIO eh ef ans b c -> MachineryIO eh ef ans a b -> MachineryIO eh ef ans a c # | |
IO <| ef => Arrow (MachineryIO eh ef ans) Source # | |
Defined in Control.Monad.Hefty.Concurrent.Stream Methods arr :: (b -> c) -> MachineryIO eh ef ans b c # first :: MachineryIO eh ef ans b c -> MachineryIO eh ef ans (b, d) (c, d) # second :: MachineryIO eh ef ans b c -> MachineryIO eh ef ans (d, b) (d, c) # (***) :: MachineryIO eh ef ans b c -> MachineryIO eh ef ans b' c' -> MachineryIO eh ef ans (b, b') (c, c') # (&&&) :: MachineryIO eh ef ans b c -> MachineryIO eh ef ans b c' -> MachineryIO eh ef ans b (c, c') # | |
IO <| ef => ArrowChoice (MachineryIO eh ef ans) Source # | |
Defined in Control.Monad.Hefty.Concurrent.Stream Methods left :: MachineryIO eh ef ans b c -> MachineryIO eh ef ans (Either b d) (Either c d) # right :: MachineryIO eh ef ans b c -> MachineryIO eh ef ans (Either d b) (Either d c) # (+++) :: MachineryIO eh ef ans b c -> MachineryIO eh ef ans b' c' -> MachineryIO eh ef ans (Either b b') (Either c c') # (|||) :: MachineryIO eh ef ans b d -> MachineryIO eh ef ans c d -> MachineryIO eh ef ans (Either b c) d # |
runMachineryIO :: forall i o ans (eh :: [EffectH]) (ef :: [EffectF]). (UnliftIO <<| eh, IO <| ef) => Eff eh ef i -> (o -> Eff eh ef ()) -> Machinery eh ef ans i o -> Eff eh ef ans Source #
runMachineryIOL :: forall i o ans (eh :: [EffectH]) (ef :: [EffectF]). (UnliftIO <<| eh, IO <| ef) => Eff eh ef i -> (o -> Eff eh ef ()) -> MachineryViewL eh ef ans i o -> Eff eh ef ans Source #
runMachineryIO_ :: forall ans (eh :: [EffectH]) (ef :: [EffectF]). (UnliftIO <<| eh, IO <| ef) => Machinery eh ef ans () () -> Eff eh ef ans Source #
module Control.Monad.Hefty.Input
module Control.Monad.Hefty.Output