[commit: ghc] master: Testsuite: simplify T8089 (#8089) (d0cf8f1)

git at git.haskell.org git at git.haskell.org
Mon Jul 20 20:53:55 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/d0cf8f1a41957a0d30475f7220facdec9efaa3a0/ghc

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

commit d0cf8f1a41957a0d30475f7220facdec9efaa3a0
Author: Thomas Miedema <thomasmiedema at gmail.com>
Date:   Thu Jul 16 20:16:17 2015 +0200

    Testsuite: simplify T8089 (#8089)
    
    The previous implementation wasn't working for the `ghci` test way,
    causing a fulltest failure.
    
    Differential Revision: https://phabricator.haskell.org/D1075


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

d0cf8f1a41957a0d30475f7220facdec9efaa3a0
 libraries/base/tests/T8089.hs | 30 +-----------------------------
 libraries/base/tests/all.T    | 13 ++++++++++++-
 2 files changed, 13 insertions(+), 30 deletions(-)

diff --git a/libraries/base/tests/T8089.hs b/libraries/base/tests/T8089.hs
index 2b98f94..3273bdb 100644
--- a/libraries/base/tests/T8089.hs
+++ b/libraries/base/tests/T8089.hs
@@ -1,32 +1,4 @@
-import Control.Applicative
 import Control.Concurrent
-import Control.Exception
-import Control.Monad
-import System.Environment
-import System.Exit
-import System.Process
-import System.Timeout
-
-testLoop :: Int -> IO (Maybe a) -> IO (Maybe a)
-testLoop 0 _ = return Nothing
-testLoop i act = do
-    result <- act
-    case result of
-        Nothing -> threadDelay 100000 >> testLoop (i-1) act
-        Just x -> return (Just x)
-
-
-forkTestChild :: IO ()
-forkTestChild = do
-    (_, _, _, hnd) <- createProcess (proc "./T8089" ["test"])
-    result <- testLoop 50 $ getProcessExitCode hnd
-    case result of
-        Nothing -> terminateProcess hnd >> exitSuccess
-        Just exitCode -> exitWith exitCode
 
 main :: IO ()
-main = do
-    numArgs <- length <$> getArgs
-    if numArgs > 0
-       then threadDelay maxBound
-       else forkTestChild
+main = threadDelay maxBound
diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T
index 1c90d14..34176d0 100644
--- a/libraries/base/tests/all.T
+++ b/libraries/base/tests/all.T
@@ -178,5 +178,16 @@ test('T9395', normal, compile_and_run, [''])
 test('T9532', omit_ways(['debug']), compile_and_run, [''])
 test('T9586', normal, compile, [''])
 test('T9681', normal, compile_fail, [''])
-test('T8089', normal, compile_and_run, [''])
+# Test no runtime crash. Report success and kill with `timeout` (exit code 99)
+# after a few seconds. From https://phabricator.haskell.org/D1075:
+#
+#   "I used a fairly conservative timeout. IF there is a regression it will
+#   crash as soon as the timeout's C call is done. The tricky bit is
+#   guesstimating how much time it needs to run to guarantee it's reached the
+#   C call.
+#   Probably something like 1s is already enough, but I don't know enough to
+#   make an educated guess how long it needs to be guaranteed to reach the C
+#   call."
+test('T8089', [exit_code(99), run_timeout_multiplier(0.01)],
+              compile_and_run, [''])
 test('T9826',normal, compile_and_run,[''])



More information about the ghc-commits mailing list