[commit: ghc] master: rename tcInstBinder(s)X to tcInstBinder(s) (544ac0d)

git at git.haskell.org git at git.haskell.org
Mon Jul 3 10:29:04 UTC 2017


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/544ac0d2e8fcd22d1761586436422c2b9396fac7/ghc

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

commit 544ac0d2e8fcd22d1761586436422c2b9396fac7
Author: Gabor Greif <ggreif at gmail.com>
Date:   Fri Jun 30 14:49:03 2017 +0200

    rename tcInstBinder(s)X to tcInstBinder(s)
    
    Summary: Simplify naming scheme of tcInstBinder(s)X
    
    Test Plan: Eyeball and compile
    
    Reviewers: austin, goldfire, bgamari
    
    Subscribers: goldfire, rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D3690


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

544ac0d2e8fcd22d1761586436422c2b9396fac7
 compiler/typecheck/Inst.hs     | 16 ++++++++--------
 compiler/typecheck/TcHsType.hs | 10 +++++-----
 compiler/typecheck/TcMType.hs  |  2 +-
 3 files changed, 14 insertions(+), 14 deletions(-)

diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs
index 093c004..a565959 100644
--- a/compiler/typecheck/Inst.hs
+++ b/compiler/typecheck/Inst.hs
@@ -15,7 +15,7 @@ module Inst (
        instCall, instDFunType, instStupidTheta,
        newWanted, newWanteds,
 
-       tcInstBindersX, tcInstBinderX,
+       tcInstBinders, tcInstBinder,
 
        newOverloadedLit, mkOverLit,
 
@@ -380,19 +380,19 @@ instStupidTheta orig theta
 -- | This is used to instantiate binders when type-checking *types* only.
 -- The @VarEnv Kind@ gives some known instantiations.
 -- See also Note [Bidirectional type checking]
-tcInstBindersX :: TCvSubst -> Maybe (VarEnv Kind)
+tcInstBinders :: TCvSubst -> Maybe (VarEnv Kind)
                -> [TyBinder] -> TcM (TCvSubst, [TcType])
-tcInstBindersX subst mb_kind_info bndrs
-  = do { (subst, args) <- mapAccumLM (tcInstBinderX mb_kind_info) subst bndrs
+tcInstBinders subst mb_kind_info bndrs
+  = do { (subst, args) <- mapAccumLM (tcInstBinder mb_kind_info) subst bndrs
        ; traceTc "instantiating tybinders:"
            (vcat $ zipWith (\bndr arg -> ppr bndr <+> text ":=" <+> ppr arg)
                            bndrs args)
        ; return (subst, args) }
 
 -- | Used only in *types*
-tcInstBinderX :: Maybe (VarEnv Kind)
+tcInstBinder :: Maybe (VarEnv Kind)
               -> TCvSubst -> TyBinder -> TcM (TCvSubst, TcType)
-tcInstBinderX mb_kind_info subst (Named (TvBndr tv _))
+tcInstBinder mb_kind_info subst (Named (TvBndr tv _))
   = case lookup_tv tv of
       Just ki -> return (extendTvSubstAndInScope subst tv ki, ki)
       Nothing -> do { (subst', tv') <- newMetaTyVarX subst tv
@@ -402,7 +402,7 @@ tcInstBinderX mb_kind_info subst (Named (TvBndr tv _))
                       ; lookupVarEnv env tv }
 
 
-tcInstBinderX _ subst (Anon ty)
+tcInstBinder _ subst (Anon ty)
      -- This is the *only* constraint currently handled in types.
   | Just (mk, role, k1, k2) <- get_pred_tys_maybe substed_ty
   = do { let origin = TypeEqOrigin { uo_actual   = k1
@@ -411,7 +411,7 @@ tcInstBinderX _ subst (Anon ty)
        ; co <- case role of
                  Nominal          -> unifyKind noThing k1 k2
                  Representational -> emitWantedEq origin KindLevel role k1 k2
-                 Phantom          -> pprPanic "tcInstBinderX Phantom" (ppr ty)
+                 Phantom          -> pprPanic "tcInstBinder Phantom" (ppr ty)
        ; arg' <- mk co k1 k2
        ; return (subst, arg') }
 
diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index 11e4b48..9653685 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -56,7 +56,7 @@ import TcIface
 import TcSimplify ( solveEqualities )
 import TcType
 import TcHsSyn( zonkSigType )
-import Inst   ( tcInstBindersX, tcInstBinderX )
+import Inst   ( tcInstBinders, tcInstBinder )
 import Type
 import Kind
 import RdrName( lookupLocalRdrOcc )
@@ -422,7 +422,7 @@ metavariable.
 In types, however, we're not so lucky, because *we cannot re-generalize*!
 There is no lambda. So, we must be careful only to instantiate at the last
 possible moment, when we're sure we're never going to want the lost polymorphism
-again. This is done in calls to tcInstBindersX.
+again. This is done in calls to tcInstBinders.
 
 To implement this behavior, we use bidirectional type checking, where we
 explicitly think about whether we know the kind of the type we're checking
@@ -810,7 +810,7 @@ tcInferArgs fun tc_binders mb_kind_info args
         -- now, we need to instantiate any remaining invisible arguments
        ; let (invis_bndrs, other_binders) = break isVisibleBinder leftover_binders
        ; (subst', invis_args)
-           <- tcInstBindersX subst mb_kind_info invis_bndrs
+           <- tcInstBinders subst mb_kind_info invis_bndrs
        ; return ( subst'
                 , other_binders
                 , args' `chkAppend` invis_args
@@ -838,7 +838,7 @@ tc_infer_args mode orig_ty binders mb_kind_info orig_args n0
     go subst (binder:binders) all_args@(arg:args) n acc
       | isInvisibleBinder binder
       = do { traceTc "tc_infer_args (invis)" (ppr binder)
-           ; (subst', arg') <- tcInstBinderX mb_kind_info subst binder
+           ; (subst', arg') <- tcInstBinder mb_kind_info subst binder
            ; go subst' binders all_args n (arg' : acc) }
 
       | otherwise
@@ -932,7 +932,7 @@ instantiateTyN n ty ki
         empty_subst = mkEmptyTCvSubst (mkInScopeSet (tyCoVarsOfType ki))
     in
     if num_to_inst <= 0 then return (ty, ki) else
-    do { (subst, inst_args) <- tcInstBindersX empty_subst Nothing inst_bndrs
+    do { (subst, inst_args) <- tcInstBinders empty_subst Nothing inst_bndrs
        ; let rebuilt_ki = mkPiTys leftover_bndrs inner_ki
              ki'        = substTy subst rebuilt_ki
        ; traceTc "instantiateTyN" (vcat [ ppr ty <+> dcolon <+> ppr ki
diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs
index d26b257..0a1de44 100644
--- a/compiler/typecheck/TcMType.hs
+++ b/compiler/typecheck/TcMType.hs
@@ -843,7 +843,7 @@ new_meta_tv_x info subst tv
                        -- is not yet fixed so leaving as unchecked for now.
                        -- OLD NOTE:
                        -- Unchecked because we call newMetaTyVarX from
-                       -- tcInstBinderX, which is called from tc_infer_args
+                       -- tcInstBinder, which is called from tc_infer_args
                        -- which does not yet take enough trouble to ensure
                        -- the in-scope set is right; e.g. Trac #12785 trips
                        -- if we use substTy here



More information about the ghc-commits mailing list