[commit: testsuite] master: Update a couple of tests to use mask rather than block/unblock (bcab545)

Ian Lynagh igloo at earth.li
Tue Feb 19 22:08:00 CET 2013


Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/bcab545325390dc7ca145b9ab2ac9ee1d2b6f0b3

>---------------------------------------------------------------

commit bcab545325390dc7ca145b9ab2ac9ee1d2b6f0b3
Author: Ian Lynagh <ian at well-typed.com>
Date:   Tue Feb 19 18:47:48 2013 +0000

    Update a couple of tests to use mask rather than block/unblock

>---------------------------------------------------------------

 tests/concurrent/should_run/T2910.hs |    2 +-
 tests/concurrent/should_run/T4030.hs |    6 +++---
 2 files changed, 4 insertions(+), 4 deletions(-)

diff --git a/tests/concurrent/should_run/T2910.hs b/tests/concurrent/should_run/T2910.hs
index 2867008..76b8d2f 100644
--- a/tests/concurrent/should_run/T2910.hs
+++ b/tests/concurrent/should_run/T2910.hs
@@ -2,7 +2,7 @@ import Control.Exception
 import GHC.Conc
   
 main = do
-    t1 <- block $ forkIO yield
+    t1 <- mask $ \_ -> forkIO yield
     t2 <- forkIO $ killThread t1
     threadDelay 100000
     threadStatus t1 >>= print
diff --git a/tests/concurrent/should_run/T4030.hs b/tests/concurrent/should_run/T4030.hs
index 1993bad..f160dfd 100644
--- a/tests/concurrent/should_run/T4030.hs
+++ b/tests/concurrent/should_run/T4030.hs
@@ -1,8 +1,8 @@
 module Main where
 
-import Control.Concurrent ( forkIO, killThread )
-import Control.Exception  ( block )
+import Control.Concurrent
+import Control.Exception
 
 main :: IO ()
-main = do tid <- block $ forkIO $ let x = x in x
+main = do tid <- mask $ \_ -> forkIO $ let x = x in x
           killThread tid





More information about the ghc-commits mailing list