[commit: ghc] master: Define PrelNames.allNameStrings and use it in TcHsType (f692e8e)

git at git.haskell.org git at git.haskell.org
Tue Jul 15 06:57:15 UTC 2014


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

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

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

commit f692e8e7cde712cc4dce4245d5745063fd8b0626
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Jul 15 07:39:51 2014 +0100

    Define PrelNames.allNameStrings and use it in TcHsType
    
    Refactoring only.


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

f692e8e7cde712cc4dce4245d5745063fd8b0626
 compiler/prelude/PrelNames.lhs  | 13 +++++++++++++
 compiler/typecheck/TcHsType.lhs |  7 ++-----
 2 files changed, 15 insertions(+), 5 deletions(-)

diff --git a/compiler/prelude/PrelNames.lhs b/compiler/prelude/PrelNames.lhs
index 395ffbb..01c5764 100644
--- a/compiler/prelude/PrelNames.lhs
+++ b/compiler/prelude/PrelNames.lhs
@@ -130,6 +130,19 @@ import FastString
 
 %************************************************************************
 %*                                                                      *
+     allNameStrings
+%*                                                                      *
+%************************************************************************
+
+\begin{code}
+allNameStrings :: [String]
+-- Infinite list of a,b,c...z, aa, ab, ac, ... etc
+allNameStrings = [ c:cs | cs <- "" : allNameStrings, c <- ['a'..'z'] ] 
+\end{code}
+
+
+%************************************************************************
+%*                                                                      *
 \subsection{Local Names}
 %*                                                                      *
 %************************************************************************
diff --git a/compiler/typecheck/TcHsType.lhs b/compiler/typecheck/TcHsType.lhs
index 723206b..cdeb191 100644
--- a/compiler/typecheck/TcHsType.lhs
+++ b/compiler/typecheck/TcHsType.lhs
@@ -76,7 +76,7 @@ import Util
 
 import Data.Maybe( isNothing )
 import Control.Monad ( unless, when, zipWithM )
-import PrelNames( ipClassName, funTyConKey )
+import PrelNames( ipClassName, funTyConKey, allNameStrings )
 \end{code}
 
 
@@ -1330,7 +1330,7 @@ tcDataKindSig kind
 	; us   <- newUniqueSupply 
         ; rdr_env <- getLocalRdrEnv
 	; let uniqs = uniqsFromSupply us
-              occs  = [ occ | str <- strs
+              occs  = [ occ | str <- allNameStrings
                             , let occ = mkOccName tvName str
                             , isNothing (lookupLocalRdrOcc rdr_env occ) ]
                  -- Note [Avoid name clashes for associated data types]
@@ -1342,9 +1342,6 @@ tcDataKindSig kind
     mk_tv loc uniq occ kind 
       = mkTyVar (mkInternalName uniq occ loc) kind
 	  
-    strs :: [String]
-    strs = [ c:cs | cs <- "" : strs, c <- ['a'..'z'] ] 
-
 badKindSig :: Kind -> SDoc
 badKindSig kind 
  = hang (ptext (sLit "Kind signature on data type declaration has non-* return kind"))



More information about the ghc-commits mailing list