broadcast-chan-0.2.0.1: Closable, fair, single-wakeup channel type that avoids 0 reader space leaks.

Copyright(C) 2014-2018 Merijn Verstraaten
LicenseBSD-style (see the file LICENSE)
MaintainerMerijn Verstraaten <merijn@inconsistent.nl>
Stabilityexperimental
Portabilityhaha
Safe HaskellSafe
LanguageHaskell2010

BroadcastChan.Throw

Contents

Description

This module is identical to BroadcastChan, but with BroadcastChan.writeBChan and BroadcastChan.readBChan replaced with versions that throw an exception, rather than returning results that the user has to inspect to check for success.

Synopsis

Documentation

data BChanError Source #

Exception type for BroadcastChan operations.

Constructors

WriteFailed

Attempted to write to closed BroadcastChan

ReadFailed

Attempted to read from an empty closed BroadcastChan

readBChan :: BroadcastChan Out a -> IO a Source #

Like readBChan, but throws a ReadFailed exception when reading from a closed and empty BroadcastChan.

writeBChan :: BroadcastChan In a -> a -> IO () Source #

Like writeBChan, but throws a WriteFailed exception when writing to closed BroadcastChan.

Re-exports from BroadcastChan

Datatypes

data BroadcastChan (dir :: Direction) a Source #

The abstract type representing the read or write end of a BroadcastChan.

Instances
Eq (BroadcastChan dir a) Source # 
Instance details

Methods

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

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

data Direction Source #

Used with DataKinds as phantom type indicating whether a BroadcastChan value is a read or write end.

Constructors

In

Indicates a write BroadcastChan

Out

Indicates a read BroadcastChan

type In = In Source #

Alias for the In type from the Direction kind, allows users to write the BroadcastChan In a type without enabling DataKinds.

type Out = Out Source #

Alias for the Out type from the Direction kind, allows users to write the BroadcastChan Out a type without enabling DataKinds.

Construction

newBroadcastChan :: MonadIO m => m (BroadcastChan In a) Source #

Creates a new BroadcastChan write end.

newBChanListener :: MonadIO m => BroadcastChan dir a -> m (BroadcastChan Out a) Source #

Create a new read end for a BroadcastChan.

BroadcastChan In:

Will receive all messages written to the channel after this read end is created.

BroadcastChan Out:

Will receive all currently unread messages and all future messages.

Basic Operations

closeBChan :: MonadIO m => BroadcastChan In a -> m Bool Source #

Close a BroadcastChan, disallowing further writes. Returns True if the BroadcastChan was closed. Returns False if the BroadcastChan was already closed.

isClosedBChan :: MonadIO m => BroadcastChan dir a -> m Bool Source #

Check whether a BroadcastChan is closed. True meaning that future read/write operations on the channel will always fail.

BroadcastChan In:

True indicates the channel is closed and writes will always fail.

Beware of TOC-TOU races: It is possible for a BroadcastChan to be closed by another thread. If multiple threads use the same channel a closeBChan from another thread can result in the channel being closed right after isClosedBChan returns.

BroadcastChan Out:

True indicates the channel is both closed and empty, meaning reads will always fail.

getBChanContents :: BroadcastChan dir a -> IO [a] Source #

Return a lazy list representing the messages written to the channel.

Uses unsafeInterleaveIO to defer the IO operations.

BroadcastChan In:

The list contains every message written to the channel after this IO action completes.

BroadcastChan Out:

The list contains every currently unread message and all future messages. It's safe to keep using the original channel in any thread.

Unlike getChanContents from Control.Concurrent, the list resulting from this function is not affected by reads on the input channel. Every message that is unread or written after the IO action completes will end up in the result list.

Parallel processing

data Action Source #

Action to take when an exception occurs while processing an element.

Constructors

Drop

Drop the current element and continue processing.

Retry

Retry by appending the current element to the queue of remaining elements.

Terminate

Stop all processing and reraise the exception.

Instances
Eq Action Source # 
Instance details

Methods

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

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

Show Action Source # 
Instance details

data Handler m a Source #

Exception handler for parallel processing.

Constructors

Simple Action

Always take the specified Action.

Handle (a -> SomeException -> m Action)

Allow inspection of the element, exception, and execution of monadic actions before deciding the Action to take.

parMapM_ Source #

Arguments

:: (Foldable f, MonadUnliftIO m) 
=> Handler m a

Exception handler

-> Int

Number of parallel threads to use

-> (a -> m ())

Function to run in parallel

-> f a

The Foldable to process in parallel

-> m () 

Map a monadic function over a Foldable, processing elements in parallel.

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

parFoldMap Source #

Arguments

:: (Foldable f, MonadUnliftIO m) 
=> Handler m a

Exception handler

-> Int

Number of parallel threads to use

-> (a -> m b)

Function to run in parallel

-> (r -> b -> r)

Function to fold results with

-> r

Zero element for the fold

-> f a

The Foldable to process

-> m r 

Like parMapM_, but folds the individual results into single result value.

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

parFoldMapM Source #

Arguments

:: (Foldable f, MonadUnliftIO m) 
=> Handler m a

Exception handler

-> Int

Number of parallel threads to use

-> (a -> m b)

Function to run in parallel

-> (r -> b -> m r)

Monadic function to fold results with

-> r

Zero element for the fold

-> f a

The Foldable to process

-> m r 

Like parFoldMap, but uses a monadic fold function.

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

Foldl combinators

Combinators for use with Tekmo's foldl package.

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

Strict fold of the BroadcastChan's messages. Can be used with Control.Foldl from Tekmo's foldl package:

Control.Foldl.purely foldBChan :: (MonadIO m, MonadIO n) => Fold a b -> BroadcastChan d a -> n (m b)

The result of this function is a nested monadic value to give more fine-grained control/separation between the start of listening for messages and the start of processing. The inner action folds the actual messages and completes when the channel is closed and exhausted. The outer action controls from when on messages are received. Specifically:

BroadcastChan In:

Will process all messages sent after the outer action completes.

BroadcastChan Out:

Will process all messages that are unread when the outer action completes, as well as all future messages.

After the outer action completes the fold is unaffected by other (concurrent) reads performed on the original channel. So it's safe to reuse the channel.

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

Strict, monadic fold of the BroadcastChan's messages. Can be used with Control.Foldl from Tekmo's foldl package:

Control.Foldl.impurely foldBChanM :: (MonadIO m, MonadIO n) => FoldM m a b -> BroadcastChan d a -> n (m b)

Has the same behaviour and guarantees as foldBChan.