[commit: ghc] master: Test Trac #10348 (a607011)
git at git.haskell.org
git at git.haskell.org
Mon Jun 15 09:02:50 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/a607011dbf522c97c9b6428ffa3203c56ab8dde6/ghc
>---------------------------------------------------------------
commit a607011dbf522c97c9b6428ffa3203c56ab8dde6
Author: Gabor Greif <ggreif at gmail.com>
Date: Mon Jun 15 11:00:45 2015 +0200
Test Trac #10348
>---------------------------------------------------------------
a607011dbf522c97c9b6428ffa3203c56ab8dde6
testsuite/tests/typecheck/should_compile/T10348.hs | 20 ++++++++++++++++++++
testsuite/tests/typecheck/should_compile/all.T | 1 +
2 files changed, 21 insertions(+)
diff --git a/testsuite/tests/typecheck/should_compile/T10348.hs b/testsuite/tests/typecheck/should_compile/T10348.hs
new file mode 100644
index 0000000..e8ec37c
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T10348.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE AutoDeriveTypeable, GADTs, DataKinds, KindSignatures, StandaloneDeriving #-}
+
+module T10348 where
+
+import GHC.TypeLits
+import Data.Typeable
+
+data Foo (n :: Nat) where
+ Hey :: KnownNat n => Foo n
+
+deriving instance Show (Foo n)
+
+data T t where
+ T :: (Show t, Typeable t) => t -> T t
+
+deriving instance Show (T n)
+
+hey :: (Typeable n, KnownNat n) => T (Foo n)
+-- SHOULD BE: hey :: KnownNat n => T (Foo n)
+hey = T Hey
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index bd87afb..8f42129 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -458,3 +458,4 @@ test('T8555', normal, compile, [''])
test('T8799', normal, compile, [''])
test('T10423', normal, compile, [''])
test('T10489', normal, compile, [''])
+test('T10348', normal, compile, [''])
More information about the ghc-commits
mailing list