[commit: ghc] ghc-7.10: testsuite: add a regression test for #10011 (111ff63)
git at git.haskell.org
git at git.haskell.org
Thu Mar 19 22:42:20 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-7.10
Link : http://ghc.haskell.org/trac/ghc/changeset/111ff6327c79b343f73ab640e33a42b3bf4e3943/ghc
>---------------------------------------------------------------
commit 111ff6327c79b343f73ab640e33a42b3bf4e3943
Author: Austin Seipp <austin at well-typed.com>
Date: Thu Mar 19 17:41:08 2015 -0500
testsuite: add a regression test for #10011
Signed-off-by: Austin Seipp <austin at well-typed.com>
(cherry picked from commit e02ef0e6d4eefa5f065cc1c33795dfa2114cd58e)
>---------------------------------------------------------------
111ff6327c79b343f73ab640e33a42b3bf4e3943
testsuite/.gitignore | 1 +
testsuite/tests/numeric/should_run/T10011.hs | 14 ++++++++++++++
.../tests/numeric/should_run/T10011.stdout | 0
testsuite/tests/numeric/should_run/all.T | 1 +
4 files changed, 16 insertions(+)
diff --git a/testsuite/.gitignore b/testsuite/.gitignore
index bbb2174..4750b04 100644
--- a/testsuite/.gitignore
+++ b/testsuite/.gitignore
@@ -1046,6 +1046,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk
/tests/numeric/should_run/T7689
/tests/numeric/should_run/T8726
/tests/numeric/should_run/T9810
+/tests/numeric/should_run/T10011
/tests/numeric/should_run/add2
/tests/numeric/should_run/arith001
/tests/numeric/should_run/arith002
diff --git a/testsuite/tests/numeric/should_run/T10011.hs b/testsuite/tests/numeric/should_run/T10011.hs
new file mode 100644
index 0000000..91a0ecd
--- /dev/null
+++ b/testsuite/tests/numeric/should_run/T10011.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE ScopedTypeVariables, TypeOperators, GADTs #-}
+module Main
+ ( main -- :: IO ()
+ ) where
+import Data.Data
+import Data.Ratio
+
+main :: IO ()
+main =
+ let bad = gmapT (\(x :: b) ->
+ case eqT :: Maybe (b :~: Integer) of
+ Nothing -> x;
+ Just Refl -> x * 2) (1 % 2) :: Rational
+ in print (bad == numerator bad % denominator bad)
diff --git a/libraries/base/tests/IO/IOError002.stdout b/testsuite/tests/numeric/should_run/T10011.stdout
similarity index 100%
copy from libraries/base/tests/IO/IOError002.stdout
copy to testsuite/tests/numeric/should_run/T10011.stdout
diff --git a/testsuite/tests/numeric/should_run/all.T b/testsuite/tests/numeric/should_run/all.T
index 6262279..4369430 100644
--- a/testsuite/tests/numeric/should_run/all.T
+++ b/testsuite/tests/numeric/should_run/all.T
@@ -64,3 +64,4 @@ test('NumDecimals', normal, compile_and_run, [''])
test('T8726', normal, compile_and_run, [''])
test('CarryOverflow', omit_ways(['ghci']), compile_and_run, [''])
test('T9810', normal, compile_and_run, [''])
+test('T10011', normal, compile_and_run, [''])
More information about the ghc-commits
mailing list