STM experiment

Carsten Schultz carsten at codimi.de
Mon Oct 12 07:34:36 EDT 2009


Brent Yorgey schrieb:
> On Fri, Oct 02, 2009 at 06:16:49PM +0200, Luca Ciciriello wrote:
>> Compiling this module with:
>>
>> ghc --make Main.hs -o Main
>>
>> and launcing ./Main the result is just:
>>
>> Terminal> world
> 
> Also, the reason you only get "world" here is likely because the main
> thread prints "world" and exits before the forked thread even gets a
> chance to run.  If you want the main thread to wait for the forked
> thread you must explicitly synchronize them; the most common way to do
> this is to set up an MVar (or a TVar in STM code) which the main
> thread reads from, and the forked thread writes to when it is
> finished in order to signal the main thread.

For example, using a utility function I wrote some time ago:


module Main(main) where

import IO
import Control.Concurrent

parallel :: [IO a] -> IO [a]
parallel = foldr (\a c ->
		  do
                  v <- newEmptyMVar
                  forkIO (a >>= putMVar v)
		  xs <- c
		  x <- takeMVar v
		  return (x:xs))
	   (return [])

main = parallel [hPutStr stdout "Hello", hPutStr stdout " world\n"]



There might be better ways to do this, but I hope that this will also be
interesting because of the functional abstractions that are used.  Note
that this will execute two forkIOs, not one as the original code.  If
that is not desirable, foldr1 could have been used.

Best

Carsten




More information about the Glasgow-haskell-users mailing list