Hello. I have a question about parallel computation in Haskell. After 
browsing the GHC library documentation, I was left with impression that there 
are two separate mechanisms for expressing concurrency: Control.Parallel.par 
for pure computations and Control.Concurrent.forkIO for computations in IO 
monad.

    This dichotomy becomes a problem when one tries to use concurrency from a 
monad transformer, though I'm sure that's not the only such situation. One 
cannot assume that the base monad is IO so forkIO cannot be used, while 
Control.Parallel.par won't run monads. My first solution was to replace the 
base monad class for the monad transformer by the following ParallelizableMonad 
class:

----------------------------------------------------------------------------
class Monad m => ParallelizableMonad m where
   parallelize :: m a -> m b -> m (a, b)
   parallelize ma mb = do a <- ma
                          b <- mb
                          return (a, b)

instance ParallelizableMonad Identity where
   parallelize (Identity a) (Identity b) = Identity (a `par` (b `pseq` (a, b)))

instance ParallelizableMonad IO where
   parallelize ma mb = do va <- newEmptyMVar
                          vb <- newEmptyMVar
                          forkIO (ma >>= putMVar va)
                          forkIO (mb >>= putMVar vb)
                          a <- takeMVar va
                          b <- takeMVar vb
                          return (a, b)
----------------------------------------------------------------------------

I tested this solution, and it worked for IO computations in the sense that 
they used both CPUs. The test also ran slower on two CPUs that on one, but 
that's beside the point.

Then I realized that par can, in fact, be used on any monad, it just needs a 
little nudge:

----------------------------------------------------------------------------
parallelize :: m a -> m b -> m (a, b)
parallelize ma mb = let a = ma >>= return
                        b = mb >>= return
                    in a `par` (b `pseq` liftM2 (,) a b)
----------------------------------------------------------------------------

However, in this version the IO monadic computations still appear to use only 
one CPU. I cannot get par to parallelize monadic computations. I've used the 
same command-line options in both examples: -O -threaded and +RTS -N2. What am 
I missing?


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to