Re: [Haskell-cafe] a parallel mapM?

2012-10-07 Thread Ozgur Akgun
Hi,

On 3 October 2012 19:23, Ryan Newton rrnew...@gmail.com wrote:

 That said, I don't see a reason for not including a separate version of
 runParIO :: ParIO a - IO a for non-deterministic computations. It seems
 really useful!


 Exactly.  I should have been more explicit but that's what I meant about
 adding another module.  You would import Control.Monad.Par.IO and get
 runParIO + liftIO but NOT runPar.  This requires doing a newtype over Par
 to create the liftIO instance for one and not the other (and preserve Safe
 Haskell).  It's a pain but it's no problem.  Both types
 Control.Monad.Par.Par and Control.Monad.Par.IO.ParIO will expose the same
 interface (i.e. have instances of the same classes -- ParFuture,
 ParIVar...), so generic algorithms like parMap will still work for either.

   -Ryan


This sounds like a great idea, I just wanted to ask if anyone is working on
it or not?

Thanks,
Ozgur
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] a parallel mapM?

2012-10-03 Thread Ryan Newton
Several of the monad-par schedulers COULD provide a MonadIO instance and
thus liftIO, which would make them easy to use for this kind of parallel
IO business:


http://hackage.haskell.org/packages/archive/monad-par/0.3/doc/html/Control-Monad-Par-Scheds-Direct.html

And that would be a little more scalable because you wouldn't get a
separate IO thread for each parallel computation.  But, to be safe-haskell
compliant, we don't currently expose IO capabilities. I can add another
module that exposes this capability if you are interested...

  -Ryan

On Fri, Sep 28, 2012 at 4:48 PM, Alexander Solla alex.so...@gmail.comwrote:



 On Fri, Sep 28, 2012 at 11:01 AM, Greg Fitzgerald gari...@gmail.comwrote:


 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?


 That's actually a perfectly fine use for unsafePerformIO, since the IO
 action you are performing is pure and therefore safe (modulo your file
 handle stuff).

 unsafePerformIO is a problem when the IO action being run has side effects
 and their order of evaluation matters (since unsafePerformIO will cause
 them to be run in an unpredictable order)

 One common use for unsafePerformIO is to run a query against an external
 library.  It has to be done in the IO monad, but it is a pure computation
 insofar as it has no side-effects that matter.  Doing this lets us promote
 values defined in external libraries to bona fide pure Haskell values.

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


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


Re: [Haskell-cafe] a parallel mapM?

2012-10-03 Thread Clark Gaebel
I'm not sure that exposing a liftIO for Monad.Par is the best idea. Since
all these parallel computations use runPar :: Par a - a, it advertises
that the result is deterministic. I'm not really comfortable with a hidden
unsafePerformIO hiding in the background.

That said, I don't see a reason for not including a separate version of
runParIO :: ParIO a - IO a for non-deterministic computations. It seems
really useful!

Regards,
  - Clark

On Wed, Oct 3, 2012 at 10:24 AM, Ryan Newton rrnew...@gmail.com wrote:

 Several of the monad-par schedulers COULD provide a MonadIO instance and
 thus liftIO, which would make them easy to use for this kind of parallel
 IO business:


 http://hackage.haskell.org/packages/archive/monad-par/0.3/doc/html/Control-Monad-Par-Scheds-Direct.html

 And that would be a little more scalable because you wouldn't get a
 separate IO thread for each parallel computation.  But, to be safe-haskell
 compliant, we don't currently expose IO capabilities. I can add another
 module that exposes this capability if you are interested...

   -Ryan

 On Fri, Sep 28, 2012 at 4:48 PM, Alexander Solla alex.so...@gmail.comwrote:



 On Fri, Sep 28, 2012 at 11:01 AM, Greg Fitzgerald gari...@gmail.comwrote:


 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?


 That's actually a perfectly fine use for unsafePerformIO, since the IO
 action you are performing is pure and therefore safe (modulo your file
 handle stuff).

 unsafePerformIO is a problem when the IO action being run has side
 effects and their order of evaluation matters (since unsafePerformIO will
 cause them to be run in an unpredictable order)

 One common use for unsafePerformIO is to run a query against an external
 library.  It has to be done in the IO monad, but it is a pure computation
 insofar as it has no side-effects that matter.  Doing this lets us promote
 values defined in external libraries to bona fide pure Haskell values.

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



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


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


Re: [Haskell-cafe] a parallel mapM?

2012-10-03 Thread Ryan Newton


 That said, I don't see a reason for not including a separate version of
 runParIO :: ParIO a - IO a for non-deterministic computations. It seems
 really useful!


Exactly.  I should have been more explicit but that's what I meant about
adding another module.  You would import Control.Monad.Par.IO and get
runParIO + liftIO but NOT runPar.  This requires doing a newtype over Par
to create the liftIO instance for one and not the other (and preserve Safe
Haskell).  It's a pain but it's no problem.  Both types
Control.Monad.Par.Par and Control.Monad.Par.IO.ParIO will expose the same
interface (i.e. have instances of the same classes -- ParFuture,
ParIVar...), so generic algorithms like parMap will still work for either.

  -Ryan


 Regards,
   - Clark

 On Wed, Oct 3, 2012 at 10:24 AM, Ryan Newton rrnew...@gmail.com wrote:

 Several of the monad-par schedulers COULD provide a MonadIO instance and
 thus liftIO, which would make them easy to use for this kind of parallel
 IO business:


 http://hackage.haskell.org/packages/archive/monad-par/0.3/doc/html/Control-Monad-Par-Scheds-Direct.html

 And that would be a little more scalable because you wouldn't get a
 separate IO thread for each parallel computation.  But, to be safe-haskell
 compliant, we don't currently expose IO capabilities. I can add another
 module that exposes this capability if you are interested...

   -Ryan

 On Fri, Sep 28, 2012 at 4:48 PM, Alexander Solla alex.so...@gmail.comwrote:



 On Fri, Sep 28, 2012 at 11:01 AM, Greg Fitzgerald gari...@gmail.comwrote:


 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?


 That's actually a perfectly fine use for unsafePerformIO, since the IO
 action you are performing is pure and therefore safe (modulo your file
 handle stuff).

 unsafePerformIO is a problem when the IO action being run has side
 effects and their order of evaluation matters (since unsafePerformIO will
 cause them to be run in an unpredictable order)

 One common use for unsafePerformIO is to run a query against an external
 library.  It has to be done in the IO monad, but it is a pure computation
 insofar as it has no side-effects that matter.  Doing this lets us promote
 values defined in external libraries to bona fide pure Haskell values.

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



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



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


[Haskell-cafe] a parallel mapM?

2012-09-28 Thread Greg Fitzgerald
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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] a parallel mapM?

2012-09-28 Thread Patrick Mylund Nielsen
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 gari...@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@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] a parallel mapM?

2012-09-28 Thread Claude Heiland-Allen

On 28/09/12 19:58, Patrick Mylund Nielsen 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


also

http://hackage.haskell.org/packages/archive/spawn/latest/doc/html/Control-Concurrent-Spawn.html#v:parMapIO

combined with

http://hackage.haskell.org/packages/archive/spawn/latest/doc/html/Control-Concurrent-Spawn.html#v:pool

might be a solution


Claude
--
http://mathr.co.uk

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


Re: [Haskell-cafe] a parallel mapM?

2012-09-28 Thread Greg Fitzgerald
 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
hask...@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 gari...@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@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



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


Re: [Haskell-cafe] a parallel mapM?

2012-09-28 Thread Alexander Solla
On Fri, Sep 28, 2012 at 11:01 AM, Greg Fitzgerald gari...@gmail.com wrote:


 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?


That's actually a perfectly fine use for unsafePerformIO, since the IO
action you are performing is pure and therefore safe (modulo your file
handle stuff).

unsafePerformIO is a problem when the IO action being run has side effects
and their order of evaluation matters (since unsafePerformIO will cause
them to be run in an unpredictable order)

One common use for unsafePerformIO is to run a query against an external
library.  It has to be done in the IO monad, but it is a pure computation
insofar as it has no side-effects that matter.  Doing this lets us promote
values defined in external libraries to bona fide pure Haskell values.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe