[Haskell-cafe] Re: how to user mergeIO

Brock Peabody brock.peabody at gmail.com
Sun Mar 14 19:26:02 EDT 2010


OK, I think I figured it out. If I understand correctly, I was just
computing the input lists in parallel. The actual values were computed in
the main thread lazily, later. This seems unintuitive to me. Shouldn't the
merge functions force the evaluation of their arguments? Surely one wouldn't
be calling them if they wanted to compute the results lazily.

On Sun, Mar 14, 2010 at 6:25 PM, Brock Peabody <brock.peabody at gmail.com>wrote:

> Hi,
> I've been trying to use Control.Concurrent.mergeIO to parallelize
> computation, and can't make it work.  In the sample program below, I expect
> the function 'parallelTest' to be almost twice as fast as 'sequentialTest',
> and to compute its results in two threads, as implied by the documentation
> for mergeIO.  This is not what happens.  If I link my program with the
> option '-threaded', the running process does have three threads.  If I run
> with the option "+RTS -N2", the process will have 5 threads.  In no case
> does the process appear to be using more than one CPU, and in fact it is
> slower with the threading options turned on.
>
> I'm sure I am doing something obviously (to someone else) wrong. Any ideas?
>
> I am running the latest version of Mac OSX on a core2 duo machine with 2
> cores, using ghc version 6.10.4.
>
> Cheers, Brock
>
> My test program follows:
>
> {-# OPTIONS_GHC -fglasgow-exts #-}
> module Main where
>
> import Control.Concurrent
> import Random
>
> doSum :: RandomGen g => g -> Int -> Integer
> doSum g count
>   = let runner curG sum numDone
>           | numDone == count = sum
>           | otherwise
>               = let (newNum :: Integer, newG) = random curG
>                     newSum = sum + newNum
>                     newNumDone = numDone + 1
>                 in ((runner $! newG) $! newSum) $! newNumDone
>     in runner g 0 0
>
> sequentialTest
>   = do let gen = mkStdGen 0
>            (g0,g1) = split gen
>            count = 10000000
>            sum0 = doSum g0 count
>            sum1 = doSum g1 count
>            total = sum0 + sum1
>        putStrLn $ "total: " ++ show total
>
> parallelTest
>   = do let gen = mkStdGen 0
>            (g0,g1) = split gen
>            count = 10000000
>            sum0 = doSum g0 count
>            sum1 = doSum g1 count
>        [res0, res1] <- mergeIO [sum0] [sum1]
>        let total = res0 + res1
>        putStrLn $ "total: " ++ show total
> main
>   = parallelTest
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100314/eeedb637/attachment.html


More information about the Haskell-Cafe mailing list