Skip to content
Snippets Groups Projects
Commit 12752342 authored by Ben Gamari's avatar Ben Gamari
Browse files

testsuite: Add T5611a

This is the same as T5611 but with an unsafe call to sleep.
parent 58e84b30
No related branches found
No related tags found
No related merge requests found
-- The same as T5611 but with unsafe calls.
{-# LANGUAGE CPP,ForeignFunctionInterface #-}
import Control.Concurrent
import Foreign.C
import System.IO
#if defined(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
T5611a: user error (Exception delivered successfully)
T5611a: <stdout>: commitBuffer: user error (Exception delivered successfully)
child: Sleeping
parent: Done throwing exception
......@@ -74,10 +74,8 @@ test('T5558',
compile_and_run, [''])
test('T5421', normal, compile_and_run, [''])
test('T5611',
[expect_broken_for(16845, ['ghci']),
when(opsys('darwin'), fragile(12751))],
compile_and_run, [''])
test('T5611', when(opsys('darwin'), fragile(12751)) , compile_and_run, [''])
test('T5611a', when(opsys('darwin'), fragile(12751)) , compile_and_run, [''])
test('T5238', normal, compile_and_run, [''])
test('T5866', exit_code(1), compile_and_run, [''])
......
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