Skip to content
Snippets Groups Projects
Commit 3518dc68 authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 1998-08-17 12:23:00 by simonm]

Fix test to wait for all threads to run before ending.
parent 7d10beb4
No related merge requests found
......@@ -6,8 +6,14 @@ module Main where
import Concurrent
main :: IO ()
main = spawner forkIO 1000000
main = do
mvar <- newEmptyMVar
spawner :: (IO () -> IO ()) -> Int -> IO ()
spawner c 0 = print "done"
spawner c n = do { c (spawner c (n-1)); return ()}
let
spawner :: (IO () -> IO ()) -> Int -> IO ()
spawner c 0 = putMVar mvar ()
spawner c n = do { c (spawner c (n-1)); return ()}
spawner forkIO 1000000
takeMVar mvar
putStr "done"
"done"
done
\ No newline at end of file
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment