From 111ff6327c79b343f73ab640e33a42b3bf4e3943 Mon Sep 17 00:00:00 2001
From: Austin Seipp <austin@well-typed.com>
Date: Thu, 19 Mar 2015 17:41:08 -0500
Subject: [PATCH] testsuite: add a regression test for #10011

Signed-off-by: Austin Seipp <austin@well-typed.com>
(cherry picked from commit e02ef0e6d4eefa5f065cc1c33795dfa2114cd58e)
---
 testsuite/.gitignore                             |  1 +
 testsuite/tests/numeric/should_run/T10011.hs     | 14 ++++++++++++++
 testsuite/tests/numeric/should_run/T10011.stdout |  1 +
 testsuite/tests/numeric/should_run/all.T         |  1 +
 4 files changed, 17 insertions(+)
 create mode 100644 testsuite/tests/numeric/should_run/T10011.hs
 create mode 100644 testsuite/tests/numeric/should_run/T10011.stdout

diff --git a/testsuite/.gitignore b/testsuite/.gitignore
index bbb2174e740d..4750b04c7978 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 000000000000..91a0ecdba848
--- /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/testsuite/tests/numeric/should_run/T10011.stdout b/testsuite/tests/numeric/should_run/T10011.stdout
new file mode 100644
index 000000000000..0ca95142bb71
--- /dev/null
+++ b/testsuite/tests/numeric/should_run/T10011.stdout
@@ -0,0 +1 @@
+True
diff --git a/testsuite/tests/numeric/should_run/all.T b/testsuite/tests/numeric/should_run/all.T
index 62622799b801..4369430e8cef 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, [''])
-- 
GitLab