[GHC] #12751: T5611 fails non-deterministically on OSX
GHC
ghc-devs at haskell.org
Fri Oct 21 21:11:18 UTC 2016
#12751: T5611 fails non-deterministically on OSX
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Here is the test.
{{{#!hs
{-# LANGUAGE CPP,ForeignFunctionInterface #-}
import Control.Concurrent
import Foreign.C
import System.IO
#ifdef mingw32_HOST_OS
sleep n = sleepBlock (n*1000)
foreign import stdcall unsafe "Sleep" sleepBlock :: Int -> IO ()
#else
sleep n = sleepBlock n
foreign import ccall unsafe "sleep" sleepBlock :: Int -> IO ()
#endif
main :: IO ()
main = do
hSetBuffering stdout LineBuffering
tid <- forkIO $ do
putStrLn "child: Sleeping"
_ <- sleep 1
-- The following lines should not happen after the killThread
from the
-- parent thread completes. However, they do...
-- putStrLn "child: Done sleeping"
threadDelay 100000
putStrLn "child: Done waiting"
threadDelay 100000
-- putStrLn $ "parent: Throwing exception to thread " ++ show tid
throwTo tid $ userError "Exception delivered successfully"
putStrLn "parent: Done throwing exception"
threadDelay 200000
}}}
It occasionally fails with
{{{
=====> T5611(normal) 1 of 1 [0, 0, 0]
cd "./concurrent/should_run/T5611.run" &&
"/Users/matt/Documents/haskell/ghc/inplace/test spaces/ghc-stage2" -o
T5611 T5611.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-
warn-missed-specialisations -fshow-warning-groups -dno-debug-output
cd "./concurrent/should_run/T5611.run" && ./T5611
Actual stderr output differs from expected:
--- ./concurrent/should_run/T5611.run/T5611.stderr.normalised 2016-10-21
22:08:55.000000000 +0100
+++ ./concurrent/should_run/T5611.run/T5611.run.stderr.normalised
2016-10-21 22:08:55.000000000 +0100
@@ -1 +0,0 @@
-T5611: user error (Exception delivered successfully)
*** unexpected failure for T5611(normal)
Unexpected results from:
TEST="T5611"
}}}
I am marking it broken for now. Does anyone know why it is failing?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12751>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list