[commit: ghc] master: Add T11747 as a test (1161932)
git at git.haskell.org
git at git.haskell.org
Sun May 1 21:56:25 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/116193225465186ceb8471a007eff15692af903a/ghc
>---------------------------------------------------------------
commit 116193225465186ceb8471a007eff15692af903a
Author: Ömer Sinan Ağacan <omeragacan at gmail.com>
Date: Sun May 1 18:03:05 2016 +0200
Add T11747 as a test
Reviewers: bgamari, austin
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2163
GHC Trac Issues: #11747
>---------------------------------------------------------------
116193225465186ceb8471a007eff15692af903a
testsuite/tests/deSugar/should_run/T11747.hs | 12 ++++++++++++
.../T1735.stdout => deSugar/should_run/T11747.stdout} | 0
testsuite/tests/deSugar/should_run/all.T | 1 +
3 files changed, 13 insertions(+)
diff --git a/testsuite/tests/deSugar/should_run/T11747.hs b/testsuite/tests/deSugar/should_run/T11747.hs
new file mode 100644
index 0000000..a0085b7
--- /dev/null
+++ b/testsuite/tests/deSugar/should_run/T11747.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE GADTs, RankNTypes, ScopedTypeVariables, Strict, TypeApplications
+ #-}
+
+import Data.Typeable
+
+zero :: forall x. Typeable x => Maybe x
+zero = do
+ Refl <- eqT @Int @x
+ pure 0
+
+main :: IO ()
+main = print (zero @())
diff --git a/testsuite/tests/typecheck/should_run/T1735.stdout b/testsuite/tests/deSugar/should_run/T11747.stdout
similarity index 100%
copy from testsuite/tests/typecheck/should_run/T1735.stdout
copy to testsuite/tests/deSugar/should_run/T11747.stdout
diff --git a/testsuite/tests/deSugar/should_run/all.T b/testsuite/tests/deSugar/should_run/all.T
index c8a9c93..7bc911e 100644
--- a/testsuite/tests/deSugar/should_run/all.T
+++ b/testsuite/tests/deSugar/should_run/all.T
@@ -52,3 +52,4 @@ test('DsStrictLet', normal, compile_and_run, ['-O'])
test('T11193', exit_code(1), compile_and_run, [''])
test('T11572', exit_code(1), compile_and_run, [''])
test('T11601', exit_code(1), compile_and_run, [''])
+test('T11747', normal, compile_and_run, ['-dcore-lint'])
More information about the ghc-commits
mailing list