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

Control.Monad.Hefty.Concurrent.Parallel

Description

Interpreters for the Parallel effects.

Documentation

runConcurrentIO :: forall (eh :: [EffectH]) (ef :: [EffectF]). (UnliftIO <<| eh, IO <| ef) => Eff (Parallel ': (Race ': (Poll ': eh))) (Halt ': ef) ~> Eff eh ef Source #

runHaltIO :: forall (ef :: [EffectF]) (eh :: [EffectH]). IO <| ef => Eff eh (Halt ': ef) ~> Eff eh ef Source #

runPollIO :: forall (ef :: [EffectF]) (eh :: [EffectH]). (IO <| ef, UnliftIO <<| eh) => Eff (Poll ': eh) ef ~> Eff eh ef Source #

runRaceIO :: forall (ef :: [EffectF]) (eh :: [EffectH]). (IO <| ef, UnliftIO <<| eh) => Eff (Race ': eh) ef ~> Eff eh ef Source #

runParallelIO :: forall (eh :: [EffectH]) (ef :: [EffectF]). (UnliftIO <<| eh, IO <| ef) => Eff (Parallel ': eh) ef ~> Eff eh ef Source #

parallelToIO :: forall (m :: Type -> Type). MonadUnliftIO m => Parallel ~~> m Source #

pollToIO :: forall (m :: Type -> Type). MonadUnliftIO m => Poll ~~> m Source #

raceToIO :: forall (m :: Type -> Type). MonadUnliftIO m => Race ~~> m Source #

haltToIO :: forall (m :: Type -> Type). MonadIO m => Halt ~> m Source #

runParallelAsSequential :: forall (eh :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]) x. Eff (Parallel ': eh) ef x -> Eff eh ef x Source #

parallelToSequential :: forall (eh :: [EffectH]) (ef :: [EffectF]) x. Parallel (Eff eh ef) x -> Eff eh ef x Source #

polling :: forall (eh :: [EffectH]) (ef :: [EffectF]) a r. Poll <<| eh => Eff eh ef a -> Eff ('[] :: [EffectH]) (Input (Maybe a) ': ef) r -> Eff eh ef r Source #

runForAsParallel :: forall (eh :: [EffectH]) (t :: Type -> Type) (ef :: [EffectF]). (Parallel <<| eh, Traversable t) => Eff (For t ': eh) ef ~> Eff eh ef Source #