#5471: Incorrect InterruptibleFFI test
---------------------------------+------------------------------------------
    Reporter:  shelarcy          |       Owner:            
        Type:  bug               |      Status:  new       
    Priority:  normal            |   Component:  Test Suite
     Version:  7.2.1             |    Keywords:            
    Testcase:                    |   Blockedby:            
          Os:  Unknown/Multiple  |    Blocking:            
Architecture:  Unknown/Multiple  |     Failure:  Other     
---------------------------------+------------------------------------------
 It seems that
 testsuite/tests/concurrent/should_run/foreignInterruptible.hs's test is
 wrong.
 Because safe foreign call with -threaded also returns same result.

 {{{
 {-# LANGUAGE ForeignFunctionInterface, CPP #-}
 module Main where

 import Control.Concurrent
 import Control.Exception
 import Prelude hiding (catch)
 import Foreign
 import System.IO

 #ifdef mingw32_HOST_OS
 sleep n = sleepBlock (n*1000)
 foreign import stdcall safe "Sleep" sleepBlock :: Int -> IO ()
 #else
 sleep n = sleepBlock n
 foreign import ccall safe "sleep" sleepBlock :: Int -> IO ()
 #endif

 main :: IO ()
 main = do
   newStablePtr stdout -- prevent stdout being finalized
   th <- newEmptyMVar
   tid <- forkIO $ do
      putStrLn "newThread started"
      (sleep 2 >> putStrLn "fail") `catch` (\ThreadKilled -> putStrLn
 "pass")
      putMVar th "child"
   yield
   threadDelay 500000
   killThread tid
   x <- takeMVar th
   putStrLn x
   putStrLn "\nshutting down"

 }}}

 {{{
 newThread started
 pass
 child

 shutting down
 }}}

 Windows and Mac OS X return this result.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5471>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to