[commit: ghc] wip/rae: Remove redundant anonymiseTyBinders (#11648) (19be538)

git at git.haskell.org git at git.haskell.org
Tue Mar 15 17:21:24 UTC 2016


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

On branch  : wip/rae
Link       : http://ghc.haskell.org/trac/ghc/changeset/19be5385e2875578c3a7d1154238580f0ef3c754/ghc

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

commit 19be5385e2875578c3a7d1154238580f0ef3c754
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Tue Mar 15 11:37:00 2016 -0400

    Remove redundant anonymiseTyBinders (#11648)
    
    This was necessary in an earlier version of the patch for #11648,
    but not in the final version. I forgot to remove it.


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

19be5385e2875578c3a7d1154238580f0ef3c754
 compiler/typecheck/TcTyClsDecls.hs |  5 ++---
 compiler/typecheck/TcType.hs       | 27 ---------------------------
 2 files changed, 2 insertions(+), 30 deletions(-)

diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs
index 2b19b62..cfd9559 100644
--- a/compiler/typecheck/TcTyClsDecls.hs
+++ b/compiler/typecheck/TcTyClsDecls.hs
@@ -317,15 +317,14 @@ kcTyClGroup (TyClGroup { group_tyclds = decls })
                  kc_res_kind = tyConResKind tc
            ; kvs <- kindGeneralize (mkForAllTys kc_binders kc_res_kind)
            ; (kc_binders', kc_res_kind') <- zonkTcKindToKind kc_binders kc_res_kind
-           ; let kc_binders'' = anonymiseTyBinders kc_binders' kc_res_kind'
 
                       -- Make sure kc_kind' has the final, zonked kind variables
            ; traceTc "Generalise kind" $
              vcat [ ppr name, ppr kc_binders, ppr kc_res_kind
-                  , ppr kvs, ppr kc_binders'', ppr kc_res_kind' ]
+                  , ppr kvs, ppr kc_binders', ppr kc_res_kind' ]
 
            ; return (mkTcTyCon name
-                               (map (mkNamedBinder Invisible) kvs ++ kc_binders'')
+                               (map (mkNamedBinder Invisible) kvs ++ kc_binders')
                                kc_res_kind'
                                (mightBeUnsaturatedTyCon tc)) }
 
diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs
index b3bd4ee..40821e5 100644
--- a/compiler/typecheck/TcType.hs
+++ b/compiler/typecheck/TcType.hs
@@ -87,7 +87,6 @@ module TcType (
   orphNamesOfTypes, orphNamesOfCoCon,
   getDFunTyKey,
   evVarPred_maybe, evVarPred,
-  anonymiseTyBinders,
 
   ---------------------------------
   -- Predicate types
@@ -223,7 +222,6 @@ import qualified GHC.LanguageExtensions as LangExt
 import Data.IORef
 import Control.Monad (liftM, ap)
 import Data.Functor.Identity
-import Data.List ( mapAccumR )
 
 {-
 ************************************************************************
@@ -2360,28 +2358,3 @@ sizeType = go
 
 sizeTypes :: [Type] -> TypeSize
 sizeTypes tys = sum (map sizeType tys)
-
-{-
-************************************************************************
-*                                                                      *
-       Binders
-*                                                                      *
-************************************************************************
--}
-
--- | Given a list of binders and a type they bind in, turn any
--- superfluous Named binders into Anon ones.
-anonymiseTyBinders :: [TyBinder] -> Type -> [TyBinder]
-anonymiseTyBinders binders res_ty = binders'
-  where
-    (_, binders') = mapAccumR go (tyCoVarsOfTypeAcc res_ty) binders
-
-    go :: FV -> TyBinder -> (FV, TyBinder)
-    go fv (Named tv Visible)
-      | not (tv `elemVarSet` runFVSet fv)
-      = ( (tv `FV.delFV` fv) `unionFV` tyCoVarsOfTypeAcc kind
-        , Anon kind )
-      where
-        kind = tyVarKind tv
-
-    go fv binder = (tyCoVarsBndrAcc binder fv, binder)



More information about the ghc-commits mailing list