summaryrefslogtreecommitdiff
path: root/testsuite/tests/codeGen
diff options
context:
space:
mode:
authorReid Barton <rwbarton@gmail.com>2015-07-06 19:24:31 +0200
committerBen Gamari <ben@smart-cactus.org>2015-07-07 10:07:23 +0200
commitaaa0cd20fdaf8e923e3a083befc2612154cba629 (patch)
treed24962bb4a53f0946eed4e68df27c19c96e36eb6 /testsuite/tests/codeGen
parent9180df19dd938901791b84ef7f260f7e2f1f894f (diff)
downloadhaskell-aaa0cd20fdaf8e923e3a083befc2612154cba629.tar.gz
Don't eagerly blackhole single-entry thunks (#10414)
In a parallel program they can actually be entered more than once, leading to deadlock. Reviewers: austin, simonmar Subscribers: michaelt, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1040 GHC Trac Issues: #10414
Diffstat (limited to 'testsuite/tests/codeGen')
-rw-r--r--testsuite/tests/codeGen/should_run/T10414.hs38
-rw-r--r--testsuite/tests/codeGen/should_run/T10414.stdout1
-rw-r--r--testsuite/tests/codeGen/should_run/all.T2
3 files changed, 41 insertions, 0 deletions
diff --git a/testsuite/tests/codeGen/should_run/T10414.hs b/testsuite/tests/codeGen/should_run/T10414.hs
new file mode 100644
index 0000000000..197206a6ab
--- /dev/null
+++ b/testsuite/tests/codeGen/should_run/T10414.hs
@@ -0,0 +1,38 @@
+{-# LANGUAGE MagicHash, UnboxedTuples #-}
+import GHC.Exts
+newtype Eval a = Eval {runEval :: State# RealWorld -> (# State# RealWorld, a #)}
+
+-- inline sequence :: [Eval a] -> Eval [a]
+well_sequenced :: [Eval a] -> Eval [a]
+well_sequenced = foldr cons nil where
+ cons e es = Eval $ \s -> case runEval e s of
+ (# s', a #) -> case runEval es s' of
+ (# s'', as #) -> (# s'', a : as #)
+ nil = Eval $ \s -> (# s, [] #)
+
+-- seemingly demonic use of spark#
+ill_sequenced :: [Eval a] -> Eval [a]
+ill_sequenced as = Eval $ spark# (case well_sequenced as of
+ Eval f -> case f realWorld# of (# _, a' #) -> a')
+
+-- 'parallelized' version of (show >=> show >=> show >=> show >=> show)
+main :: IO ()
+main = putStrLn ((layer . layer . layer . layer . layer) (:[]) 'y')
+ where
+ layer :: (Char -> String) -> (Char -> String)
+ layer f = (\(Eval x) -> case x realWorld# of (# _, as #) -> concat as)
+ . well_sequenced -- [Eval String] -> Eval [String]
+ . map ill_sequenced -- [[Eval Char]] -> [Eval String];
+ -- 'map well_sequenced' is fine
+ . map (map (\x -> Eval $ \s -> (# s, x #))) -- wrap each Char in Eval
+ . chunk' -- String -> [String]
+ . concatMap f
+ . show -- add single quotes
+
+ chunk' :: String -> [String]
+ chunk' [] = []
+ chunk' xs = as : chunk' bs where (as,bs) = splitAt 3 xs
+
+ -- this doesn't work:
+ -- chunk (a:b:c:xs) = [a,b,c]:chunk xs
+ -- chunk xs = [xs]
diff --git a/testsuite/tests/codeGen/should_run/T10414.stdout b/testsuite/tests/codeGen/should_run/T10414.stdout
new file mode 100644
index 0000000000..8e22b0cb67
--- /dev/null
+++ b/testsuite/tests/codeGen/should_run/T10414.stdout
@@ -0,0 +1 @@
+'\'''\\''\'''\'''\'''\\''\\''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\\''\'''\'''\\''\\''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\\''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\\''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\\''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''y''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\\''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\\''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\\''\'''\'''\\''\\''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\\''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\'''\'''\'''\\''\\''\'''\'''\\''\'''\'''\'''\\''\'''\''
diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T
index db2d04ed95..bae6d10fde 100644
--- a/testsuite/tests/codeGen/should_run/all.T
+++ b/testsuite/tests/codeGen/should_run/all.T
@@ -133,5 +133,7 @@ test('cgrun074', normal, compile_and_run, [''])
test('CmmSwitchTest', when(fast(), skip), compile_and_run, [''])
test('T10245', expect_broken(10246), compile_and_run, [''])
test('T10246', expect_broken(10246), compile_and_run, [''])
+test('T10414', [only_ways(['threaded2']), extra_ways(['threaded2'])],
+ compile_and_run, ['-feager-blackholing'])
test('T10521', normal, compile_and_run, [''])
test('T10521b', normal, compile_and_run, [''])