[Haskell-cafe] forkSequence, runPar, parallelize (was: Re: You are in a twisty maze of concurrency libraries, all different ...)

Antoine Latter aslatter at gmail.com
Wed Dec 9 15:43:37 EST 2009


On Wed, Dec 9, 2009 at 2:17 PM, Mario Blazevic <mblazevic at stilo.com> wrote:
>        It appears there are several implementations existing on Hackage of
> the following function, in various disguises:
>
>   runPar :: [IO a] -> IO [a]
>
>
> the idea being that the IO computations are run in parallel, rather than
> sequentially. My own Streaming Component Combinators package contains a
> similar function, but somewhat generalized:
>
>
>   class Monad m => ParallelizableMonad m where
>      parallelize :: m a -> m b -> m (a, b)
>
>   instance ParallelizableMonad IO  -- implemented using forkIO
>   instance ParallelizableMonad Identity  -- implemented using par
>   instance ParallelizableMonad Maybe  -- implemented using par
>
>
>        Would there be any interest in having this class packaged in a
> separate library? If so, can you sugest a better name or some additional
> functionality?

A similar function that I'm fond of:

forkExec :: IO a -> IO (IO a)
forkExec k
    = do
  result <- newEmptyMVar
  _ <- forkIO $ k >>= putMVar result
  return (takeMVar result)

Although I don't think it can be generalized to non-IO monads.

Antoine


More information about the Haskell-Cafe mailing list