[commit: ghc] master: In toHsType, filter out kind variables (803afa3)

git at git.haskell.org git at git.haskell.org
Mon Nov 25 18:43:39 UTC 2013


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/803afa31c5884dbd5f3cffc05f0bda9106352714/ghc

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

commit 803afa31c5884dbd5f3cffc05f0bda9106352714
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Mon Nov 25 18:16:29 2013 +0000

    In toHsType, filter out kind variables
    
    (This fixes #8563)


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

803afa31c5884dbd5f3cffc05f0bda9106352714
 compiler/hsSyn/HsUtils.lhs     |    3 ++-
 compiler/typecheck/TcDeriv.lhs |    1 +
 2 files changed, 3 insertions(+), 1 deletion(-)

diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs
index dd77ac1..7fc354b 100644
--- a/compiler/hsSyn/HsUtils.lhs
+++ b/compiler/hsSyn/HsUtils.lhs
@@ -415,7 +415,8 @@ toHsType ty
 
     to_hs_type (TyVarTy tv) = nlHsTyVar (getRdrName tv)
     to_hs_type (AppTy t1 t2) = nlHsAppTy (toHsType t1) (toHsType t2)
-    to_hs_type (TyConApp tc args) = nlHsTyConApp (getRdrName tc) (map toHsType args)
+    to_hs_type (TyConApp tc args) = nlHsTyConApp (getRdrName tc) (map toHsType args')
+       where args' = filter (not . isKind) args
     to_hs_type (FunTy arg res) = ASSERT( not (isConstraintKind (typeKind arg)) )
                                  nlHsFunTy (toHsType arg) (toHsType res)
     to_hs_type t@(ForAllTy {}) = pprPanic "toHsType" (ppr t)
diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs
index 088615a..025ac07 100644
--- a/compiler/typecheck/TcDeriv.lhs
+++ b/compiler/typecheck/TcDeriv.lhs
@@ -1919,6 +1919,7 @@ genInst standalone_deriv oflag comauxs
                  , ds_name = name, ds_cls = clas, ds_loc = loc })
   | is_newtype
   = do { inst_spec <- mkInstance oflag theta spec
+       ; traceTc "genInst/is_newtype" (vcat [ppr loc, ppr clas, ppr tvs, ppr tys, ppr rhs_ty])
        ; return ( InstInfo
                     { iSpec   = inst_spec
                     , iBinds  = InstBindings



More information about the ghc-commits mailing list