[commit: ghc] master: Fixup test for #10728 (1b72534)
git at git.haskell.org
git at git.haskell.org
Fri Jan 29 04:27:24 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/1b72534b99ea17012746ef97b4892a7c9c3450dd/ghc
>---------------------------------------------------------------
commit 1b72534b99ea17012746ef97b4892a7c9c3450dd
Author: Thomas Miedema <thomasmiedema at gmail.com>
Date: Fri Jan 29 05:19:46 2016 +0100
Fixup test for #10728
It was failing for WAY=ghci.
>---------------------------------------------------------------
1b72534b99ea17012746ef97b4892a7c9c3450dd
testsuite/tests/rts/T10728.hs | 16 ++++++----------
testsuite/tests/rts/all.T | 4 ++--
2 files changed, 8 insertions(+), 12 deletions(-)
diff --git a/testsuite/tests/rts/T10728.hs b/testsuite/tests/rts/T10728.hs
index ff005fa..a7c3d79 100644
--- a/testsuite/tests/rts/T10728.hs
+++ b/testsuite/tests/rts/T10728.hs
@@ -4,13 +4,13 @@ module Main where
import GHC.Conc (getNumProcessors, getNumCapabilities)
import GHC.Environment
-import Data.Char
+import Data.List
main :: IO ()
main = do
-- We're parsing args passed in to make sure things are proper between the
-- cli and the program.
- n <- getN
+ n <- getN <$> getFullArgs
c <- getNumCapabilities
p <- getNumProcessors
@@ -30,11 +30,7 @@ check n c p
check _n _c _p = "maxN Error"
-- Parsing ``-maxN<n>`` from Args to be sure of it.
-getN :: IO Int
-getN = getFullArgs >>= return . go
- where
- go :: [String] -> Int
- go as = case reads (
- dropWhile (not . isDigit) . (!! 2) $ as ) :: [(Int, String)] of
- [x] -> fst x
- _ -> 0
+getN :: [String] -> Int
+getN args = case filter (isPrefixOf "-maxN") (reverse args) of
+ (maxN:_) -> read (drop 5 maxN)
+ _ -> error "Please pass `-maxN<n>` on command-line"
diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T
index 951acbe..5aa296a 100644
--- a/testsuite/tests/rts/all.T
+++ b/testsuite/tests/rts/all.T
@@ -333,5 +333,5 @@ test('T10590', [ignore_output, when(opsys('mingw32'),skip)], compile_and_run, ['
test('T10904', [ omit_ways(['ghci']), extra_run_opts('20000') ],
compile_and_run, ['T10904lib.c'])
-test('T10728', [extra_run_opts('+RTS -maxN3 -RTS'), req_smp],
- compile_and_run, ['-threaded'])
+test('T10728', [extra_run_opts('+RTS -maxN3 -RTS'), only_ways(['threaded2'])],
+ compile_and_run, [''])
More information about the ghc-commits
mailing list