[commit: ghc] ghc-8.2: testsuite: Add testcase for T13658 (3906a0c)
git at git.haskell.org
git at git.haskell.org
Tue May 16 01:12:23 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.2
Link : http://ghc.haskell.org/trac/ghc/changeset/3906a0c0c95f4c9a36479c38776de74b36013a99/ghc
>---------------------------------------------------------------
commit 3906a0c0c95f4c9a36479c38776de74b36013a99
Author: Ben Gamari <ben at smart-cactus.org>
Date: Mon May 15 20:15:11 2017 -0400
testsuite: Add testcase for T13658
(cherry picked from commit efd113f72f07908e57c62cbce71f8d4a1e1d2819)
>---------------------------------------------------------------
3906a0c0c95f4c9a36479c38776de74b36013a99
testsuite/tests/simplCore/should_compile/T13658.hs | 39 ++++++++++++++++++++++
testsuite/tests/simplCore/should_compile/all.T | 1 +
2 files changed, 40 insertions(+)
diff --git a/testsuite/tests/simplCore/should_compile/T13658.hs b/testsuite/tests/simplCore/should_compile/T13658.hs
new file mode 100644
index 0000000..0890e89
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T13658.hs
@@ -0,0 +1,39 @@
+{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE BangPatterns #-}
+
+{- # OPTIONS_GHC -Werror #-}
+{-# OPTIONS_GHC -g -O2 #-}
+
+module Bug (bug) where
+
+-- import GHC.Base (seq)
+import Unsafe.Coerce (unsafeCoerce)
+
+undefined :: a
+undefined = undefined
+
+data TypeRep (a :: k) where
+ TrTyCon :: TypeRep (a :: k)
+ TrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1).
+ TypeRep (a b)
+
+data SomeTypeRep where
+ SomeTypeRep :: forall k (a :: k).
+ TypeRep a
+ -> SomeTypeRep
+
+mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1).
+ TypeRep (a :: k1 -> k2)
+ -> TypeRep (a b)
+mkTrApp TrTyCon = undefined
+mkTrApp TrApp = undefined
+
+bug :: SomeTypeRep
+-- bug = f x -- this works
+bug = f (f x)
+ where x = SomeTypeRep TrTyCon
+ f :: SomeTypeRep -> SomeTypeRep
+ f (SomeTypeRep acc) = SomeTypeRep (mkTrApp (unsafeCoerce acc))
diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T
index 7a079c7..3e25b87 100644
--- a/testsuite/tests/simplCore/should_compile/all.T
+++ b/testsuite/tests/simplCore/should_compile/all.T
@@ -259,3 +259,4 @@ test('T13468',
normal,
run_command,
['$MAKE -s --no-print-directory T13468'])
+test('T13658', normal, compile, ['-dcore-lint'])
More information about the ghc-commits
mailing list