broadcast-chan-pipes-0.2.1.1: Pipes-based parallel streaming code for broadcast-chan
Copyright(C) 2014-2021 Merijn Verstraaten
LicenseBSD-style (see the file LICENSE)
MaintainerMerijn Verstraaten <merijn@inconsistent.nl>
Stabilityexperimental
Portabilityhaha
Safe HaskellSafe
LanguageHaskell2010

BroadcastChan.Pipes.Throw

Description

This module is identical to BroadcastChan.Throw, but replaces the parallel processing operations with functions for creating producers and effects that process in parallel.

Synopsis

Documentation

data Action #

Constructors

Drop 
Retry 
Terminate 

Instances

Instances details
Eq Action 
Instance details

Defined in BroadcastChan.Extra

Methods

(==) :: Action -> Action -> Bool #

(/=) :: Action -> Action -> Bool #

Show Action 
Instance details

Defined in BroadcastChan.Extra

data Handler (m :: Type -> Type) a #

Constructors

Simple Action 
Handle (a -> SomeException -> m Action) 

parMapM Source #

Arguments

:: forall a b m. MonadSafe m 
=> Handler IO a

Exception handler

-> Int

Number of parallel threads to use

-> (a -> IO b)

Function to run in parallel

-> Producer a m ()

Input producer

-> Producer b m () 

Create a producer that processes its inputs in parallel.

This function does NOT guarantee that input elements are processed or output in a deterministic order!

parMapM_ Source #

Arguments

:: MonadSafe m 
=> Handler IO a

Exception handler

-> Int

Number of parallel threads to use

-> (a -> IO ())

Function to run in parallel

-> Producer a m r

Input producer

-> Effect m r 

Create an Effect that processes its inputs in parallel.

This function does NOT guarantee that input elements are processed or output in a deterministic order!

Re-exports from BroadcastChan.Throw

Datatypes

data BroadcastChan (dir :: Direction) a #

Instances

Instances details
Eq (BroadcastChan dir a) 
Instance details

Defined in BroadcastChan.Internal

Methods

(==) :: BroadcastChan dir a -> BroadcastChan dir a -> Bool #

(/=) :: BroadcastChan dir a -> BroadcastChan dir a -> Bool #

data Direction #

Constructors

In 
Out 

type In = 'In #

type Out = 'Out #

Construction

newBChanListener :: forall m (dir :: Direction) a. MonadIO m => BroadcastChan dir a -> m (BroadcastChan Out a) #

Basic Operations

isClosedBChan :: forall m (dir :: Direction) a. MonadIO m => BroadcastChan dir a -> m Bool #

getBChanContents :: forall (dir :: Direction) a. BroadcastChan dir a -> IO [a] #

Foldl combinators

Combinators for use with Tekmo's foldl package.

foldBChan :: forall m n x a b (d :: Direction). (MonadIO m, MonadIO n) => (x -> a -> x) -> x -> (x -> b) -> BroadcastChan d a -> n (m b) #

foldBChanM :: forall m n x a b (d :: Direction). (MonadIO m, MonadIO n) => (x -> a -> m x) -> m x -> (x -> m b) -> BroadcastChan d a -> n (m b) #