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

[project @ 1998-10-08 11:37:15 by simonm]

fix conc004 for new type of forkIO.
add conc007: killThread test.
parent 754f262e
No related merge requests found
......@@ -10,7 +10,7 @@ main = do
mvar <- newEmptyMVar
let
spawner :: (IO () -> IO ()) -> Int -> IO ()
spawner :: (IO () -> IO ThreadId) -> Int -> IO ()
spawner c 0 = putMVar mvar ()
spawner c n = do { c (spawner c (n-1)); return ()}
......
{-# OPTIONS -fglasgow-exts #-}
module Main where
import Concurrent
import IOExts
choose :: a -> a -> IO a
choose a b = do
ready <- newMVar ()
answer <- newEmptyMVar
a_id <- forkIO (a `seq` takeMVar ready >> putMVar answer a)
b_id <- forkIO (b `seq` takeMVar ready >> putMVar answer b)
it <- takeMVar answer
killThread a_id
killThread b_id
return it
main = do
let big = sum [1..]
small = sum [1..42]
test1 <- choose big small
test2 <- choose small big
print (test1,test2)
(903,903)
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