[Haskell-cafe] a parallel mapM?

Greg Fitzgerald garious at gmail.com
Fri Sep 28 21:17:38 CEST 2012


> Check out the parallel combinators in parallel-io:

Cool, that's the library I'm looking for!  I see it uses
'numCapabilities' to get the command-line value for '-N' and not
'getNumCapabilities' to query the system for how many cores are
available.  So using the 'Local' module, this works:

parMapM f xs = do
   n <- getNumCapabilities
   withPool n $ \pool -> parallel pool (map f xs)

Thanks,
Greg

On Fri, Sep 28, 2012 at 11:58 AM, Patrick Mylund Nielsen
<haskell at patrickmylund.com> wrote:
> Check out the parallel combinators in parallel-io:
> http://hackage.haskell.org/packages/archive/parallel-io/0.3.2/doc/html/Control-Concurrent-ParallelIO-Global.html
>
> On Fri, Sep 28, 2012 at 1:01 PM, Greg Fitzgerald <garious at gmail.com> wrote:
>>
>> I'm new to concurrent programming in Haskell.  I'm looking for a
>> drop-in replacement for 'mapM' to parallelize a set of independent IO
>> operations.  I hoped 'mapConcurrently' might be it, but I need
>> something that will only spawn as many threads as I have CPUs
>> available [1].
>>
>> I also tried Control.Parallel.Strategies [2].  While that route works,
>> I had to use unsafePerformIO.  Considering that IO is for sequencing
>> effects and my IO operation doesn't cause any side-effects (besides
>> hogging a file handle), is this a proper use of unsafePerformIO?
>>
>>
>> Attempt 1
>> --------------
>>
>> import System.Process(readProcess)
>> import Control.Concurrent.Async(mapConcurrently)
>>
>> main :: IO [String]
>> main = mapConcurrently (\n -> readProcess "echo" ["test: " ++ show n]
>> "") [0..1000]
>>
>>
>> $ ghc --version
>> The Glorious Glasgow Haskell Compilation System, version 7.6.1
>>
>> $ runghc test.hs
>> test.hs: runInteractiveProcess: pipe: Too many open files
>> test.hs: runInteractiveProcess: pipe: Too many open files
>> test.hs: runInteractiveProcess: pipe: Too many open files
>> test.hs: runInteractiveProcess: pipe: Too many open files
>> test.hs: runInteractiveProcess: pipe: Too many open files
>> test.hs: runInteractiveProcess: pipe: Too many open files
>> test.hs: runInteractiveProcess: pipe: Too many open files
>> test.hs: runInteractiveProcess: pipe: Too many open files
>> test.hs: runInteractiveProcess: pipe: Too many open files
>> test.hs: echo: createProcess: resource exhausted (Too many open files)
>>
>>
>> Attempt 2
>> --------------
>>
>> import System.Process(readProcess)
>> import Control.Parallel.Strategies(parMap, rpar)
>> import System.IO.Unsafe(unsafePerformIO)
>>
>> main :: IO [String]
>> main = myMapConcurrently (\n -> readProcess "echo" ["test: " ++ show
>> n] "") [0..1000]
>>   where
>>     myMapConcurrently f = return . parMap rpar (unsafePerformIO . f)
>>
>> $ runghc test.hs > /dev/null && echo Success
>> Success
>>
>>
>> Thanks,
>> Greg
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



More information about the Haskell-Cafe mailing list