[commit: ghc] master: Simplify variable naming in tcDataKindSig (c8295c0)

git at git.haskell.org git at git.haskell.org
Wed Jun 11 19:57:22 UTC 2014


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

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

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

commit c8295c0bd58485db5572d3c35427d321bdf1b7d0
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Jun 11 19:49:50 2014 +0100

    Simplify variable naming in tcDataKindSig
    
    Now that we are very consistent about tidying when converting
    to IfaceSyn, we don't need to worry about accidental capture
    of the "extra" type variables in tcDataKindSig.  (Previously
    we gave them weird names like $a.)
    
    However, it is nicer for the user if we don't gratuitously
    re-use an in-scope name, so we take care not to do that
    .


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

c8295c0bd58485db5572d3c35427d321bdf1b7d0
 compiler/typecheck/TcHsType.lhs | 46 +++++++++++++++++++++--------------------
 1 file changed, 24 insertions(+), 22 deletions(-)

diff --git a/compiler/typecheck/TcHsType.lhs b/compiler/typecheck/TcHsType.lhs
index cf00a36..69579ad 100644
--- a/compiler/typecheck/TcHsType.lhs
+++ b/compiler/typecheck/TcHsType.lhs
@@ -54,6 +54,7 @@ import TcType
 import Type
 import TypeRep( Type(..) )  -- For the mkNakedXXX stuff
 import Kind
+import RdrName( lookupLocalRdrOcc )
 import Var
 import VarSet
 import TyCon
@@ -73,6 +74,7 @@ import Outputable
 import FastString
 import Util
 
+import Data.Maybe( isNothing )
 import Control.Monad ( unless, when, zipWithM )
 import PrelNames( ipClassName, funTyConKey )
 \end{code}
@@ -1318,20 +1320,22 @@ tcDataKindSig kind
   = do	{ checkTc (isLiftedTypeKind res_kind) (badKindSig kind)
 	; span <- getSrcSpanM
 	; us   <- newUniqueSupply 
+        ; rdr_env <- getLocalRdrEnv
 	; let uniqs = uniqsFromSupply us
-	; return [ mk_tv span uniq str kind 
-		 | ((kind, str), uniq) <- arg_kinds `zip` dnames `zip` uniqs ] }
+              occs  = [ occ | str <- strs
+                            , let occ = mkOccName tvName str
+                            , isNothing (lookupLocalRdrOcc rdr_env occ) ]
+                 -- Note [Avoid name clashes for associated data types]
+
+	; return [ mk_tv span uniq occ kind 
+		 | ((kind, occ), uniq) <- arg_kinds `zip` occs `zip` uniqs ] }
   where
     (arg_kinds, res_kind) = splitKindFunTys kind
-    mk_tv loc uniq str kind = mkTyVar name kind
-	where
-	   name = mkInternalName uniq occ loc
-	   occ  = mkOccName tvName str
-	  
-    dnames = map ('$' :) names	-- Note [Avoid name clashes for associated data types]
+    mk_tv loc uniq occ kind 
+      = mkTyVar (mkInternalName uniq occ loc) kind
 	  
-    names :: [String]
-    names = [ c:cs | cs <- "" : names, c <- ['a'..'z'] ] 
+    strs :: [String]
+    strs = [ c:cs | cs <- "" : strs, c <- ['a'..'z'] ] 
 
 badKindSig :: Kind -> SDoc
 badKindSig kind 
@@ -1343,19 +1347,17 @@ Note [Avoid name clashes for associated data types]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Consider    class C a b where
                data D b :: * -> *
-When typechecking the decl for D, we'll invent an extra type variable for D,
-to fill out its kind.  We *don't* want this type variable to be 'a', because
-in an .hi file we'd get
+When typechecking the decl for D, we'll invent an extra type variable
+for D, to fill out its kind.  Ideally we don't want this type variable
+to be 'a', because when pretty printing we'll get
             class C a b where
-               data D b a 
-which makes it look as if there are *two* type indices.  But there aren't!
-So we use $a instead, which cannot clash with a user-written type variable.
-Remember that type variable binders in interface files are just FastStrings,
-not proper Names.
-
-(The tidying phase can't help here because we don't tidy TyCons.  Another
-alternative would be to record the number of indexing parameters in the 
-interface file.)
+               data D b a0 
+(NB: the tidying happens in the conversion to IfaceSyn, which happens
+as part of pretty-printing a TyThing.)
+
+That's why we look in the LocalRdrEnv to see what's in scope. This is
+important only to get nice-looking output when doing ":info C" in GHCi.
+It isn't essential for correctness.
 
 
 %************************************************************************



More information about the ghc-commits mailing list