Copyright | (C) 2014-2022 Merijn Verstraaten |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Merijn Verstraaten <merijn@inconsistent.nl> |
Stability | experimental |
Portability | haha |
Safe Haskell | Safe |
Language | Haskell2010 |
BroadcastChan.Pipes
Description
This module is identical to BroadcastChan, but replaces the parallel processing operations with functions for creating producers and effects that process in parallel.
Synopsis
- data Action
- data Handler (m :: Type -> Type) a
- = Simple Action
- | Handle (a -> SomeException -> m Action)
- parMapM :: forall a b m. MonadSafe m => Handler IO a -> Int -> (a -> IO b) -> Producer a m () -> Producer b m ()
- parMapM_ :: MonadSafe m => Handler IO a -> Int -> (a -> IO ()) -> Producer a m r -> Effect m r
- data BroadcastChan (dir :: Direction) a
- data Direction
- type In = 'In
- type Out = 'Out
- newBroadcastChan :: MonadIO m => m (BroadcastChan In a)
- newBChanListener :: forall m (dir :: Direction) a. MonadIO m => BroadcastChan dir a -> m (BroadcastChan Out a)
- readBChan :: MonadIO m => BroadcastChan Out a -> m (Maybe a)
- tryReadBChan :: MonadIO m => BroadcastChan Out a -> m (Maybe (Maybe a))
- writeBChan :: MonadIO m => BroadcastChan In a -> a -> m Bool
- closeBChan :: MonadIO m => BroadcastChan In a -> m Bool
- isClosedBChan :: forall m (dir :: Direction) a. MonadIO m => BroadcastChan dir a -> m Bool
- getBChanContents :: forall (dir :: Direction) a. BroadcastChan dir a -> IO [a]
- 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)
Documentation
data Handler (m :: Type -> Type) a #
Constructors
Simple Action | |
Handle (a -> SomeException -> m Action) |
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!
Since: 0.2.0
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!
Since: 0.2.0
Re-exports from BroadcastChan
Datatypes
data BroadcastChan (dir :: Direction) a #
Instances
Eq (BroadcastChan dir a) | |
Defined in BroadcastChan.Internal Methods (==) :: BroadcastChan dir a -> BroadcastChan dir a -> Bool # (/=) :: BroadcastChan dir a -> BroadcastChan dir a -> Bool # |
Construction
newBroadcastChan :: MonadIO m => m (BroadcastChan In a) #
newBChanListener :: forall m (dir :: Direction) a. MonadIO m => BroadcastChan dir a -> m (BroadcastChan Out a) #
Basic Operations
tryReadBChan :: MonadIO m => BroadcastChan Out a -> m (Maybe (Maybe a)) #
writeBChan :: MonadIO m => BroadcastChan In a -> a -> m Bool #
closeBChan :: MonadIO m => BroadcastChan In a -> m Bool #
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) #