[commit: ghc] wip/T9177: Suggest Int when user writes int (a6735a0)

git at git.haskell.org git at git.haskell.org
Fri Jun 6 10:32:25 UTC 2014


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

On branch  : wip/T9177
Link       : http://ghc.haskell.org/trac/ghc/changeset/a6735a0dc016cca5de0afb2460f23ae972dfd9b8/ghc

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

commit a6735a0dc016cca5de0afb2460f23ae972dfd9b8
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Fri Jun 6 11:47:28 2014 +0200

    Suggest Int when user writes int
    
    and the other way around. This fixes #9177.


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

a6735a0dc016cca5de0afb2460f23ae972dfd9b8
 compiler/basicTypes/OccName.lhs | 25 +++++++++++++++++++++++++
 compiler/rename/RnEnv.lhs       |  1 +
 2 files changed, 26 insertions(+)

diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs
index 487318b..b1fd831 100644
--- a/compiler/basicTypes/OccName.lhs
+++ b/compiler/basicTypes/OccName.lhs
@@ -83,6 +83,8 @@ module OccName (
 	
 	isTcClsNameSpace, isTvNameSpace, isDataConNameSpace, isVarNameSpace, isValNameSpace,
 
+        toRelatedNameSpace,
+
 	-- * The 'OccEnv' type
 	OccEnv, emptyOccEnv, unitOccEnv, extendOccEnv, mapOccEnv,
 	lookupOccEnv, mkOccEnv, mkOccEnv_C, extendOccEnvList, elemOccEnv,
@@ -370,6 +372,29 @@ demoteOccName (OccName space name) = do
   space' <- demoteNameSpace space
   return $ OccName space' name
 
+-- What would this name be if used in the related name space
+-- (variables <-> data construtors, type variables <-> type constructors)
+toRelatedNameSpace :: OccName -> Maybe OccName
+toRelatedNameSpace (OccName space name) = OccName (otherNameSpace space) `fmap` name'
+  where
+    name' | name == fsLit "[]"  = Nothing -- Some special cases first
+          | name == fsLit "->"  = Nothing
+          | hd == '('           = Nothing
+          | hd == ':'           = Just tl
+          | startsVarSym hd     = Just (':' `consFS` name)
+          | isUpper hd          = Just (toLower hd `consFS` tl)
+          | isLower hd          = Just (toUpper hd `consFS` tl)
+          | otherwise           = pprTrace "toRelatedNameSpace" (ppr name)
+                                  Nothing
+    (hd,tl) = (headFS name, tailFS name)
+
+otherNameSpace :: NameSpace -> NameSpace
+otherNameSpace VarName = DataName
+otherNameSpace DataName = VarName
+otherNameSpace TvName = TcClsName
+otherNameSpace TcClsName = TvName
+
+
 {- | Other names in the compiler add aditional information to an OccName.
 This class provides a consistent way to access the underlying OccName. -}
 class HasOccName name where
diff --git a/compiler/rename/RnEnv.lhs b/compiler/rename/RnEnv.lhs
index d79fae4..d0c51d3 100644
--- a/compiler/rename/RnEnv.lhs
+++ b/compiler/rename/RnEnv.lhs
@@ -1478,6 +1478,7 @@ unknownNameSuggestErr where_look tried_rdr_name
 
     correct_name_space occ =  occNameSpace occ == tried_ns
                            && isSymOcc occ == tried_is_sym
+                           || toRelatedNameSpace occ == Just tried_occ
         -- Treat operator and non-operators as non-matching
         -- This heuristic avoids things like
         --      Not in scope 'f'; perhaps you meant '+' (from Prelude)



More information about the ghc-commits mailing list