[commit: ghc] master: Check KnownSymbol => Typeable deduction (e60dbf3)
git at git.haskell.org
git at git.haskell.org
Mon Jun 22 13:44:45 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/e60dbf30adfcc0ba90ed9271239c0c8a7bc14f06/ghc
>---------------------------------------------------------------
commit e60dbf30adfcc0ba90ed9271239c0c8a7bc14f06
Author: Gabor Greif <ggreif at gmail.com>
Date: Mon Jun 22 15:40:01 2015 +0200
Check KnownSymbol => Typeable deduction
verifying fix for #10348
>---------------------------------------------------------------
e60dbf30adfcc0ba90ed9271239c0c8a7bc14f06
testsuite/tests/typecheck/should_compile/T10348.hs | 6 ++++--
1 file changed, 4 insertions(+), 2 deletions(-)
diff --git a/testsuite/tests/typecheck/should_compile/T10348.hs b/testsuite/tests/typecheck/should_compile/T10348.hs
index 7380d81..dadb8aa 100644
--- a/testsuite/tests/typecheck/should_compile/T10348.hs
+++ b/testsuite/tests/typecheck/should_compile/T10348.hs
@@ -1,9 +1,10 @@
-{-# LANGUAGE AutoDeriveTypeable, GADTs, DataKinds, KindSignatures, StandaloneDeriving #-}
+{-# LANGUAGE AutoDeriveTypeable, GADTs, DataKinds, KindSignatures, StandaloneDeriving, TypeOperators #-}
module T10348 where
import GHC.TypeLits
import Data.Typeable
+import Data.Proxy
data Foo (n :: Nat) where
Hey :: KnownNat n => Foo n
@@ -27,4 +28,5 @@ f1 = typeRep
g2 :: KnownSymbol a => Proxy a -> TypeRep
g2 = typeRep
-
+pEqT :: (KnownSymbol a, KnownSymbol b) => Proxy a -> Proxy b -> Maybe (a :~: b)
+pEqT Proxy Proxy = eqT
More information about the ghc-commits
mailing list