ConcurrentUtils-0.4.5.0: Concurrent utilities

Safe HaskellTrustworthy
LanguageHaskell98

Control.CUtils.Conc

Description

A module of concurrent higher order functions.

Synopsis

Documentation

data ConcException Source #

For internal errors. If a procedure throws this, some threads it created may still be running. It is thrown separately from ExceptionList.

Constructors

ConcException 

assocFold :: (?pool :: BoxedThreadPool, Concurrent (Kleisli m)) => (b -> b -> m b) -> (c -> b) -> (b, Array Int c) -> m b Source #

class Concurrent a where Source #

A type class of arrows that support some form of concurrency.

Minimal complete definition

arr_assocFold, arr_concF_, arr_concF, arr_oneOfF

Methods

arr_assocFold :: (?pool :: BoxedThreadPool) => a (b, b) b -> (c -> b) -> a (b, Array Int c) b Source #

Runs an associative folding function on the given array. Note: this function only spawns enough threads to make effective use of the capabilities. Any two list elements may be processed sequentially or concurrently. To get parallelism, you have to set the numCapabilities value, e.g. using GHC's +RTS -N flag.

arr_concF_ :: (?seq :: Bool, ?pool :: BoxedThreadPool) => a (t, Int) () -> a (t, Int) () Source #

The first parameter is the number of computations which are indexed from 0 to n - 1.

arr_concF :: (?seq :: Bool, ?pool :: BoxedThreadPool) => a (u, Int) t -> a (u, Int) (Array Int t) Source #

arr_oneOfF :: a (u, Int) b -> a (u, Int) b Source #

Instances

Concurrent (->) Source # 

Methods

arr_assocFold :: (?pool :: BoxedThreadPool) => ((b, b) -> b) -> (c -> b) -> (b, Array Int c) -> b Source #

arr_concF_ :: (?seq :: Bool, ?pool :: BoxedThreadPool) => ((t, Int) -> ()) -> (t, Int) -> () Source #

arr_concF :: (?seq :: Bool, ?pool :: BoxedThreadPool) => ((u, Int) -> t) -> (u, Int) -> Array Int t Source #

arr_oneOfF :: ((u, Int) -> b) -> (u, Int) -> b Source #

Concurrent (Kleisli IO) Source # 

Methods

arr_assocFold :: (?pool :: BoxedThreadPool) => Kleisli IO (b, b) b -> (c -> b) -> Kleisli IO (b, Array Int c) b Source #

arr_concF_ :: (?seq :: Bool, ?pool :: BoxedThreadPool) => Kleisli IO (t, Int) () -> Kleisli IO (t, Int) () Source #

arr_concF :: (?seq :: Bool, ?pool :: BoxedThreadPool) => Kleisli IO (u, Int) t -> Kleisli IO (u, Int) (Array Int t) Source #

arr_oneOfF :: Kleisli IO (u, Int) b -> Kleisli IO (u, Int) b Source #

concF_ :: (?seq :: Bool, ?pool :: BoxedThreadPool, Concurrent (Kleisli m)) => Int -> (Int -> m ()) -> m () Source #

concF :: (?seq :: Bool, ?pool :: BoxedThreadPool, Concurrent (Kleisli m)) => Int -> (Int -> m t) -> m (Array Int t) Source #

conc_ :: (?seq :: Bool, ?pool :: BoxedThreadPool, Concurrent (Kleisli m)) => Array Int (m ()) -> m () Source #

conc :: (?seq :: Bool, ?pool :: BoxedThreadPool) => Array Int (IO e) -> IO (Array Int e) Source #

The next function takes an implicit parameter ?seq. Set it to True if you want to only spawn threads for the capabilities (same as assocFold; good for speed). If you need all the actions to be executed concurrently, set it to False.

concP :: (Concurrent (Kleisli m), ?pool :: BoxedThreadPool, Monad m) => m t1 -> m t -> m (t1, t) Source #

Version of concF specialized for two computations.

progressConcF :: (?seq :: Bool, ?pool :: BoxedThreadPool) => Int -> (Int -> IO t) -> IO (Array Int t) Source #

oneOfF :: Concurrent (Kleisli m) => Int -> (Int -> m b) -> m b Source #

oneOf :: Array Int (IO a) -> IO a Source #

Runs several computations in parallel, and returns one of their results (terminating the other computations).