[commit: ghc] master: Test Trac #15114 (6742ce2)
git at git.haskell.org
git at git.haskell.org
Thu May 3 07:51:51 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/6742ce2d8e0919dd75b5ecb0e2b5f891c442bdd3/ghc
>---------------------------------------------------------------
commit 6742ce2d8e0919dd75b5ecb0e2b5f891c442bdd3
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu May 3 08:51:29 2018 +0100
Test Trac #15114
>---------------------------------------------------------------
6742ce2d8e0919dd75b5ecb0e2b5f891c442bdd3
testsuite/tests/simplCore/should_run/T15114.hs | 23 ++++++++++++++++++++++
testsuite/tests/simplCore/should_run/T15114.stdout | 1 +
testsuite/tests/simplCore/should_run/all.T | 1 +
3 files changed, 25 insertions(+)
diff --git a/testsuite/tests/simplCore/should_run/T15114.hs b/testsuite/tests/simplCore/should_run/T15114.hs
new file mode 100644
index 0000000..ef0e77c
--- /dev/null
+++ b/testsuite/tests/simplCore/should_run/T15114.hs
@@ -0,0 +1,23 @@
+{-# OPTIONS_GHC -O #-}
+-- Bug only showed up with optimisation on
+
+module Main where
+
+import qualified Control.Exception as Exception
+
+main :: IO ()
+main = do
+ unserialize
+ putStrLn "all is well"
+
+unserialize :: IO Char
+unserialize =
+ if definitelyTrue
+ then do
+ return 'a'
+ else do
+ Exception.evaluate (error "wrong place")
+
+{-# NOINLINE definitelyTrue #-}
+definitelyTrue :: Bool
+definitelyTrue = True
diff --git a/testsuite/tests/simplCore/should_run/T15114.stdout b/testsuite/tests/simplCore/should_run/T15114.stdout
new file mode 100644
index 0000000..0b9e820
--- /dev/null
+++ b/testsuite/tests/simplCore/should_run/T15114.stdout
@@ -0,0 +1 @@
+all is well
diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T
index ca69565..3d8f540 100644
--- a/testsuite/tests/simplCore/should_run/all.T
+++ b/testsuite/tests/simplCore/should_run/all.T
@@ -84,3 +84,4 @@ test('T14868',
compile_and_run, [''])
test('T14894', normal, compile_and_run, [''])
test('T14965', normal, compile_and_run, [''])
+test('T15114', only_ways('optasm'), compile_and_run, [''])
More information about the ghc-commits
mailing list