[commit: ghc] wip/T15809: Comments and alpha-renaming (8be7e73)
git at git.haskell.org
git at git.haskell.org
Fri Nov 23 17:34:12 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T15809
Link : http://ghc.haskell.org/trac/ghc/changeset/8be7e73c6881b5a73e0799e9e6602f30445cd12a/ghc
>---------------------------------------------------------------
commit 8be7e73c6881b5a73e0799e9e6602f30445cd12a
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Wed Nov 7 23:26:05 2018 +0000
Comments and alpha-renaming
>---------------------------------------------------------------
8be7e73c6881b5a73e0799e9e6602f30445cd12a
compiler/typecheck/TcHsType.hs | 2 --
compiler/typecheck/TcInstDcls.hs | 10 +++++-----
compiler/typecheck/TcMType.hs | 2 +-
compiler/typecheck/TcSimplify.hs | 7 ++++---
4 files changed, 10 insertions(+), 11 deletions(-)
diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index 2ce23e7..dd2995e 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -1744,7 +1744,6 @@ kcImplicitTKBndrs = kcImplicitTKBndrsX newFlexiKindedTyVarTyVar
-- | Bring implicitly quantified type/kind variables into scope during
-- kind checking. The returned TcTyVars are in 1-1 correspondence
--- with the names passed in.
--- Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls.
kcImplicitTKBndrsX :: (Name -> TcM TcTyVar) -- new_tv function
-> [Name] -- of the vars
-> TcM a
@@ -2065,7 +2064,6 @@ kcLookupTcTyCon nm
-- Never emits constraints, though the thing_inside might.
kcTyClTyVars :: Name -> TcM a -> TcM a
kcTyClTyVars tycon_name thing_inside
- -- See Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls
= do { tycon <- kcLookupTcTyCon tycon_name
; tcExtendNameTyVarEnv (tcTyConScopedTyVars tycon) $ thing_inside }
diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs
index 84f43e9..63c565d 100644
--- a/compiler/typecheck/TcInstDcls.hs
+++ b/compiler/typecheck/TcInstDcls.hs
@@ -465,14 +465,14 @@ tcLocalInstDecl (L _ (XInstDecl _)) = panic "tcLocalInstDecl"
tcClsInstDecl :: LClsInstDecl GhcRn
-> TcM ([InstInfo GhcRn], [FamInst], [DerivInfo])
-- The returned DerivInfos are for any associated data families
-tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds
+tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = hs_ty, cid_binds = binds
, cid_sigs = uprags, cid_tyfam_insts = ats
, cid_overlap_mode = overlap_mode
, cid_datafam_insts = adts }))
= setSrcSpan loc $
- addErrCtxt (instDeclCtxt1 poly_ty) $
+ addErrCtxt (instDeclCtxt1 hs_ty) $
do { (tyvars, theta, clas, inst_tys)
- <- tcHsClsInstType (InstDeclCtxt False) poly_ty
+ <- tcHsClsInstType (InstDeclCtxt False) hs_ty
-- NB: tcHsClsInstType does checkValidInstance
; tcExtendTyVarEnv tyvars $
@@ -481,7 +481,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds
mb_info = Just (clas, tyvars, mini_env)
-- Next, process any associated types.
- ; traceTc "tcLocalInstDecl" (ppr poly_ty)
+ ; traceTc "tcLocalInstDecl" (ppr hs_ty)
; tyfam_insts0 <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats
; datafam_stuff <- mapAndRecoverM (tcDataFamInstDecl mb_info) adts
; let (datafam_insts, m_deriv_infos) = unzip datafam_stuff
@@ -500,7 +500,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds
-- Finally, construct the Core representation of the instance.
-- (This no longer includes the associated types.)
- ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType poly_ty))
+ ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType hs_ty))
-- Dfun location is that of instance *header*
; ispec <- newClsInst (fmap unLoc overlap_mode) dfun_name tyvars theta
diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs
index 8192f75..9edad0f 100644
--- a/compiler/typecheck/TcMType.hs
+++ b/compiler/typecheck/TcMType.hs
@@ -1499,7 +1499,7 @@ defaultTyVar default_kind tv
-- Do not default TyVarTvs. Doing so would violate the invariants
-- on TyVarTvs; see Note [Signature skolems] in TcType.
-- Trac #13343 is an example; #14555 is another
- -- See Note [Kind generalisation and TyVarTvs]
+ -- See Note [Inferring kinds for type declarations] in TcTyClsDecls
= return False
diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs
index 750b621..e1a3532 100644
--- a/compiler/typecheck/TcSimplify.hs
+++ b/compiler/typecheck/TcSimplify.hs
@@ -2008,9 +2008,10 @@ promoteTyVarTcS tv
defaultTyVarTcS :: TcTyVar -> TcS Bool
defaultTyVarTcS the_tv
| isRuntimeRepVar the_tv
- , not (isTyVarTyVar the_tv) -- TyVarTvs should only be unified with a tyvar
- -- never with a type; c.f. TcMType.defaultTyVar
- -- See Note [Kind generalisation and TyVarTvs]
+ , not (isTyVarTyVar the_tv)
+ -- TyVarTvs should only be unified with a tyvar
+ -- never with a type; c.f. TcMType.defaultTyVar
+ -- and Note [Inferring kinds for type declarations] in TcTyClsDecls
= do { traceTcS "defaultTyVarTcS RuntimeRep" (ppr the_tv)
; unifyTyVar the_tv liftedRepTy
; return True }
More information about the ghc-commits
mailing list