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

2009-12-09 Thread Mario Blazevic
	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?

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


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

2009-12-09 Thread Antoine Latter
On Wed, Dec 9, 2009 at 2:17 PM, Mario Blazevic mblaze...@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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-12-09 Thread Matthew Brecknell
Antoine Latter wrote:
 A similar function that I'm fond of:
 
 forkExec :: IO a - IO (IO a)

It's cute that forkExec already has a dual operation with just the right
name (specialised to IO):

join :: IO (IO a) - IO a



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


Re: [Haskell-cafe] forkSequence, runPar, parallelize

2009-12-09 Thread Mario Blazevic



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



	I can't test it right now, but wouldn't the following do the job in the 
Identity monad?


forkExec :: Identity a - Identity (Identity a)
forkExec k = let result = runIdentity k
 in result `par` return (Identity result)

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


Re: [Haskell-cafe] forkSequence, runPar, parallelize

2009-12-09 Thread Antoine Latter
On Wed, Dec 9, 2009 at 3:44 PM, Mario Blazevic mblaze...@stilo.com wrote:

        I can't test it right now, but wouldn't the following do the job in
 the Identity monad?

 forkExec :: Identity a - Identity (Identity a)
 forkExec k = let result = runIdentity k
             in result `par` return (Identity result)


Since Identity is a newtype, would that be equivalent to result `par`
result? The forkExec in the IO monad let's other computations keep
going until I need the result from the forked computation.

In a pure computation, I can already get the same result with `par`
and laziness, right?

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


Re: [Haskell-cafe] forkSequence, runPar, parallelize

2009-12-09 Thread Dan Weston
It's a good thing then that forkExec and return are denotationally equal 
(though not operationally). Otherwise, I'd be worried.


Matthew Brecknell wrote:

Antoine Latter wrote:

A similar function that I'm fond of:

forkExec :: IO a - IO (IO a)


It's cute that forkExec already has a dual operation with just the right
name (specialised to IO):

join :: IO (IO a) - IO a



___
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] forkSequence, runPar, parallelize

2009-12-09 Thread Mario Blažević
 
         I can't test it right now, but wouldn't the
  following do the job in the Identity monad?
 
  forkExec :: Identity a - Identity (Identity a)
  forkExec k = let result = runIdentity k
              in result `par` return (Identity result)
 
 
 Since Identity is a newtype, would that be equivalent to result `par`
 result? The forkExec in the IO monad let's other computations keep
 going until I need the result from the forked computation.


You're right, it doesn't seem to work the way I hoped. The equivalent function 
on
Maybe monad works, though, so it is possible to write forkExec in monads other
than IO.

 In a pure computation, I can already get the same result with `par`
 and laziness, right?

Yes. The goal is to enable writing monadic parallel computations which work 
under
any parallelizable monad. For example, I'm using it to run two trampolining
producer/consumer coroutines in parallel. A large majority of interesting
coroutines I have are completely agnostic with respect to the underlying monad.


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