Parallel executing of actions

Hi! Is there a parallel version of mapM_? Like it is for map (parMap)? I would like to execute actions in parallel as the computation of necessary data for actions is quite computational heavy. But it does not matter in which order those actions are executed. (I am rendering pixels with OpenGL and it does not matter in which order I draw them, but it matters that for one pixel it takes some time to calculate its color.) The example would be: main :: IO () main = do -- the order of printed characters is not important -- instead of putStrLn there will be a computationally big function -- so it would be great if those computations would be done in parallel -- and results printed out as they come mapM_ rwhnf (putStrLn) ["a","b","c","d"] Is this possible? Without unsafe functions? And without changing the semantics of the program. Mitar

On Sun, 15 Apr 2007 18:01:44 +0200
Mitar
Hi!
Is there a parallel version of mapM_? Like it is for map (parMap)?
This version will fork a new thread for each action: \begin{code} import Control.Concurrent import Control.Monad parSequence_ xs = do m <- newEmptyMVar mapM_ (\x -> forkIO x >> putMVar m ()) xs replicateM_ (length xs) (takeMVar m) parMapM_ f xs = parSequence_ $ map f xs \end{code}
I would like to execute actions in parallel as the computation of necessary data for actions is quite computational heavy. But it does not matter in which order those actions are executed. (I am rendering pixels with OpenGL and it does not matter in which order I draw them, but it matters that for one pixel it takes some time to calculate its color.)
The example would be:
main :: IO () main = do -- the order of printed characters is not important -- instead of putStrLn there will be a computationally big function -- so it would be great if those computations would be done in parallel -- and results printed out as they come mapM_ rwhnf (putStrLn) ["a","b","c","d"]
Is this possible? Without unsafe functions? And without changing the semantics of the program.
Of course the semantics of the program will change, the order in which the actions are executed is unknown! Cheers, Spencer Janssen

Hi!
On 4/15/07, Spencer Janssen
This version will fork a new thread for each action:
\begin{code} import Control.Concurrent import Control.Monad
parSequence_ xs = do m <- newEmptyMVar mapM_ (\x -> forkIO x >> putMVar m ()) xs replicateM_ (length xs) (takeMVar m)
parMapM_ f xs = parSequence_ $ map f xs \end{code}
OpenGL bindings successfully crash. The functional calculations in f should be done in parallel, but those few OpenGL actions should still be done sequentially. I am attaching the code in question. It is a simple voxel raycasting engine. (Any suggestions on other memory/performance improvements are more than welcome.) Mitar

I may be talking out of my other end here, but... if you want something
like parMap to calculate all the pixels in parallel, then... can't you use
parMap itself?
Something like:
weirdParMap action = sequence_ . map action . parMap (id $!)
This evaluates all the elements of the list using parMap (the expensive
part, right?), and then sequentially applies the action on the current
thread.
JCAB
On Sun, 15 Apr 2007 12:56:02 -0700, Mitar
Hi!
On 4/15/07, Spencer Janssen
wrote: This version will fork a new thread for each action:
\begin{code} import Control.Concurrent import Control.Monad
parSequence_ xs = do m <- newEmptyMVar mapM_ (\x -> forkIO x >> putMVar m ()) xs replicateM_ (length xs) (takeMVar m)
parMapM_ f xs = parSequence_ $ map f xs \end{code}
OpenGL bindings successfully crash. The functional calculations in f should be done in parallel, but those few OpenGL actions should still be done sequentially. I am attaching the code in question. It is a simple voxel raycasting engine.
(Any suggestions on other memory/performance improvements are more than welcome.)
Mitar

On Tue, Apr 17, 2007 at 05:49:11PM -0700, Juan Carlos Arevalo Baeza wrote:
I may be talking out of my other end here, but... if you want something like parMap to calculate all the pixels in parallel, then... can't you use parMap itself?
Something like:
weirdParMap action = sequence_ . map action . parMap (id $!)
This evaluates all the elements of the list using parMap (the expensive part, right?), and then sequentially applies the action on the current thread.
You are. I'm devoting most of my brain cells to automatic deriving of TTypeable atm, but note that id is already strict, so (id $!) is equivalent to id. Stefan

:-) Thank you for your kindness. I mean... your frankness.
I had another issue in that code which clearly shows that I don't know
how to use parMap or strategies in general. Maybe this is better:
weirdParMap action = sequence_ . map action . parMap rwhnf (\x -> x `seq`
x)
or maybe that's overkill and this is sufficient:
weirdParMap action = sequence_ . map action . parMap rwhnf id
or this:
weirdParMap action list = sequence_ $ map action (list `using` rnf)
(which I guess would require the appropriate NFData instanbe for the
pixel type)
or maybe I still don't know enough about this Parallel Haskell thingy.
In any case... couldn't something like this be what was needed in the
OP?
JCAB
On Tue, 17 Apr 2007 17:56:27 -0700, Stefan O'Rear
On Tue, Apr 17, 2007 at 05:49:11PM -0700, Juan Carlos Arevalo Baeza wrote:
I may be talking out of my other end here, but... if you want something like parMap to calculate all the pixels in parallel, then... can't you use parMap itself?
Something like:
weirdParMap action = sequence_ . map action . parMap (id $!)
This evaluates all the elements of the list using parMap (the expensive part, right?), and then sequentially applies the action on the current thread.
You are. I'm devoting most of my brain cells to automatic deriving of TTypeable atm, but note that id is already strict, so (id $!) is equivalent to id.
Stefan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi!
On 4/18/07, Juan Carlos Arevalo Baeza
This evaluates all the elements of the list using parMap (the expensive part, right?), and then sequentially applies the action on the current thread.
True. But currently I have the "main" function I would like to parallel something like this: drawPixel x y = do openGLDrawPixel x y color where color = calcColor x y But it is probably really better if I first calculate everything and then just draw it. It is easier to parallelize (will have only pure functions) and also I will not have those OpenGL errors. Thanks everybody Mitar

On Apr 15, 2007, at 8:23 PM, Spencer Janssen wrote:
parSequence_ xs = do m <- newEmptyMVar mapM_ (\x -> forkIO x >> putMVar m ()) xs replicateM_ (length xs) (takeMVar m)
mapM_ above spawns (length xs) threads blocking on a single "lock", right? replicateM_ then makes sure that the lock is "unlocked" as many times as threads spawned, right? Since all the threads block on a single MVar how do they run in parallel? Thanks, Joel -- http://wagerlabs.com/

Joel Reymont wrote:
On Apr 15, 2007, at 8:23 PM, Spencer Janssen wrote:
parSequence_ xs = do m <- newEmptyMVar mapM_ (\x -> forkIO x >> putMVar m ()) xs
should be mapM_ (\x -> forkIO (x >> putMVar m ())) xs
replicateM_ (length xs) (takeMVar m)
mapM_ above spawns (length xs) threads blocking on a single "lock", right?
yes.
replicateM_ then makes sure that the lock is "unlocked" as many times as threads spawned, right?
right.
Since all the threads block on a single MVar how do they run in parallel?
The idea is that before the threads block on the MVar, they run their action x to completion. Bertram

Hi!
On 4/16/07, Bertram Felgenhauer
Since all the threads block on a single MVar how do they run in parallel?
The idea is that before the threads block on the MVar, they run their action x to completion.
The rendering crashes. I will have to precompute the values in threads someway and then sequentially draw it? Any suggestion how to do that? Mitar

On 16/04/2007, at 12:30, Mitar wrote:
Hi!
On 4/16/07, Bertram Felgenhauer
wrote: Since all the threads block on a single MVar how do they run in parallel?
The idea is that before the threads block on the MVar, they run their action x to completion.
The rendering crashes. I will have to precompute the values in threads someway and then sequentially draw it? Any suggestion how to do that?
Could it be that you are launching 400x300=120.000 new threads all at once? If you are not doing it already, it would be sensible to implement some pooling of threads. This is what I use myself, don't worry about the unsafeness IF you know that the sequence of computations doesn't matter: \begin{code} unsafeParMapM :: (a -> IO b) -> [a] -> IO [b] unsafeParMapM f = return . parMap rwhnf (unsafePerformIO . f) unsafeParMapMn :: Integral bound => bound -> (a -> IO b) -> [a] -> IO [b] unsafeParMapMn max f xx = return (map (unsafePerformIO . f) xx `using` parListChunk (fromIntegral max) rwhnf) unsafeParSeqn :: Integral bound => bound -> [IO a] -> IO [a] unsafeParSeqn max cc = return ((map unsafePerformIO cc) `using` parListChunk (fromIntegral max) rwhnf) \begin{code}

Mitar wrote:
Hi!
On 4/16/07, Bertram Felgenhauer
wrote: Since all the threads block on a single MVar how do they run in parallel?
The idea is that before the threads block on the MVar, they run their action x to completion.
The rendering crashes. I will have to precompute the values in threads someway and then sequentially draw it? Any suggestion how to do that?
I'm guessing this is becuase of the thread-local state used by OpenGL, which is the reason we have forkOS. All your OpenGL calls must be executed by the same Haskell thread, and it must be a bound thread (i.e. either the main thread, or a thread created with forkOS). Cheers, Simon

On 4/16/07, Mitar
Hi!
On 4/16/07, Bertram Felgenhauer
wrote: Since all the threads block on a single MVar how do they run in parallel?
The idea is that before the threads block on the MVar, they run their action x to completion.
The rendering crashes. I will have to precompute the values in threads someway and then sequentially draw it? Any suggestion how to do that?
Rendering into the same rendering context from multiple threads at the same time is a baaad idea. I would suggest chunking up your work (assuming that calculating your colour is indeed a significant amount of work) in tiles or something, then fork off a thread for each of them, sticking the final colours in a Chan. Then you have another thread just pick tiles off the Chan and copy the results to the frame buffer. -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

Hi!
On 4/17/07, Sebastian Sylvan
I would suggest chunking up your work (assuming that calculating your colour is indeed a significant amount of work) in tiles or something, then fork off a thread for each of them, sticking the final colours in a Chan. Then you have another thread just pick tiles off the Chan and copy the results to the frame buffer.
Is there some completely different and maybe better way of rendering the image? Because I noticed that in fact I do not really have any use for OpenGL (I draw pixels on a 2D plane). So maybe is there some other portable way of rendering a 2D image, which would be easier to parallelize? Maybe of precomputing the image in completely functional way and then only draw the whole image at once to the screen buffer (now I call OpenGL draw pixel function for every pixel I want to draw - this is probably not the best way). Mitar
participants (9)
-
Bertram Felgenhauer
-
Joel Reymont
-
Juan Carlos Arevalo Baeza
-
Mitar
-
Pepe Iborra
-
Sebastian Sylvan
-
Simon Marlow
-
Spencer Janssen
-
Stefan O'Rear