[commit: ghc] master: Demonstrate that inferring Typeable for type literals works (77e5ec8)

git at git.haskell.org git at git.haskell.org
Mon Jun 15 11:35:11 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/77e5ec83617fce4cec530c744a435535bf06130b/ghc

>---------------------------------------------------------------

commit 77e5ec83617fce4cec530c744a435535bf06130b
Author: Gabor Greif <ggreif at gmail.com>
Date:   Mon Jun 15 13:30:24 2015 +0200

    Demonstrate that inferring Typeable for type literals works
    
    So #10348 is only missing the variable case:
      Known{Nat,Symbol} lit => Typeable lit


>---------------------------------------------------------------

77e5ec83617fce4cec530c744a435535bf06130b
 compiler/typecheck/TcEvidence.hs                   | 2 +-
 compiler/typecheck/TcInstDcls.hs                   | 2 +-
 testsuite/tests/typecheck/should_compile/T10348.hs | 3 +++
 3 files changed, 5 insertions(+), 2 deletions(-)

diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs
index 6e02694..e7ab902 100644
--- a/compiler/typecheck/TcEvidence.hs
+++ b/compiler/typecheck/TcEvidence.hs
@@ -733,7 +733,7 @@ data EvTerm
 -- | Instructions on how to make a 'Typeable' dictionary.
 data EvTypeable
   = EvTypeableTyCon TyCon [Kind]
-    -- ^ Dicitionary for concrete type constructors.
+    -- ^ Dictionary for concrete type constructors.
 
   | EvTypeableTyApp (EvTerm,Type) (EvTerm,Type)
     -- ^ Dictionary for type applications;  this is used when we have
diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs
index 9ce2d2f..c815d2d 100644
--- a/compiler/typecheck/TcInstDcls.hs
+++ b/compiler/typecheck/TcInstDcls.hs
@@ -433,7 +433,7 @@ tcInstDecls1 tycl_decls inst_decls deriv_decls
                      2 (pprInstanceHdr (iSpec i))
 
     -- Report an error or a warning for a `Typeable` instances.
-    -- If we are workikng on an .hs-boot file, we just report a warning,
+    -- If we are working on an .hs-boot file, we just report a warning,
     -- and ignore the instance.  We do this, to give users a chance to fix
     -- their code.
     typeable_err i =
diff --git a/testsuite/tests/typecheck/should_compile/T10348.hs b/testsuite/tests/typecheck/should_compile/T10348.hs
index e8ec37c..213079b 100644
--- a/testsuite/tests/typecheck/should_compile/T10348.hs
+++ b/testsuite/tests/typecheck/should_compile/T10348.hs
@@ -18,3 +18,6 @@ deriving instance Show (T n)
 hey :: (Typeable n, KnownNat n) => T (Foo n)
 -- SHOULD BE: hey :: KnownNat n => T (Foo n)
 hey = T Hey
+
+ho :: T (Foo 42)
+ho = T Hey



More information about the ghc-commits mailing list