Improve error reporting for type signatures
authorsimonpj@microsoft.com <unknown>
Wed, 2 May 2007 11:47:38 +0000 (11:47 +0000)
committersimonpj@microsoft.com <unknown>
Wed, 2 May 2007 11:47:38 +0000 (11:47 +0000)
See Trac #1310

compiler/rename/RnBinds.lhs
compiler/rename/RnEnv.lhs
compiler/typecheck/TcRnTypes.lhs

index d7a5952..1c7bebb 100644 (file)
@@ -33,12 +33,12 @@ import RnEnv                ( bindLocatedLocalsRn, lookupLocatedBndrRn,
                          warnUnusedLocalBinds, mapFvRn, extendTyVarEnvFVRn,
                        )
 import DynFlags        ( DynFlag(..) )
                          warnUnusedLocalBinds, mapFvRn, extendTyVarEnvFVRn,
                        )
 import DynFlags        ( DynFlag(..) )
-import Name            ( Name, nameOccName, nameSrcLoc )
+import Name
 import NameEnv
 import NameSet
 import PrelNames       ( isUnboundName )
 import RdrName         ( RdrName, rdrNameOcc )
 import NameEnv
 import NameSet
 import PrelNames       ( isUnboundName )
 import RdrName         ( RdrName, rdrNameOcc )
-import SrcLoc          ( mkSrcSpan, Located(..), unLoc )
+import SrcLoc          ( Located(..), unLoc )
 import ListSetOps      ( findDupsEq )
 import BasicTypes      ( RecFlag(..) )
 import Digraph         ( SCC(..), stronglyConnComp )
 import ListSetOps      ( findDupsEq )
 import BasicTypes      ( RecFlag(..) )
 import Digraph         ( SCC(..), stronglyConnComp )
@@ -629,10 +629,20 @@ dupSigDeclErr sigs@(L loc sig : _)
     ppr_sig (L loc sig) = ppr loc <> colon <+> ppr sig
 
 unknownSigErr (L loc sig)
     ppr_sig (L loc sig) = ppr loc <> colon <+> ppr sig
 
 unknownSigErr (L loc sig)
-  = addErrAt loc $
-       sep [ptext SLIT("Misplaced") <+> what_it_is <> colon, ppr sig]
+  = do { mod <- getModule
+       ; addErrAt loc $
+               vcat [sep [ptext SLIT("Misplaced") <+> what_it_is <> colon, ppr sig],
+                     extra_stuff mod sig] }
   where
     what_it_is = hsSigDoc sig
   where
     what_it_is = hsSigDoc sig
+    extra_stuff mod  (TypeSig (L _ n) _)
+       | nameIsLocalOrFrom mod n
+       = ptext SLIT("The type signature must be given where")
+               <+> quotes (ppr n) <+> ptext SLIT("is declared")
+       | otherwise
+       = ptext SLIT("You cannot give a type signature for an imported value")
+
+    extra_stuff mod other = empty
 
 methodBindErr mbind
  =  hang (ptext SLIT("Pattern bindings (except simple variables) not allowed in instance declarations"))
 
 methodBindErr mbind
  =  hang (ptext SLIT("Pattern bindings (except simple variables) not allowed in instance declarations"))
index 50b0adb..54a768a 100644 (file)
@@ -195,8 +195,25 @@ lookupTopBndrRn rdr_name
 -- The Haskell98 report does not stipulate this, but it will!
 -- So we must treat the 'f' in the signature in the same way
 -- as the binding occurrence of 'f', using lookupBndrRn
 -- The Haskell98 report does not stipulate this, but it will!
 -- So we must treat the 'f' in the signature in the same way
 -- as the binding occurrence of 'f', using lookupBndrRn
+--
+-- However, consider this case:
+--     import M( f )
+--     f :: Int -> Int
+--     g x = x
+-- We don't want to say 'f' is out of scope; instead, we want to
+-- return the imported 'f', so that later on the reanamer will
+-- correctly report "misplaced type sig".
 lookupLocatedSigOccRn :: Located RdrName -> RnM (Located Name)
 lookupLocatedSigOccRn :: Located RdrName -> RnM (Located Name)
-lookupLocatedSigOccRn = lookupLocatedBndrRn
+lookupLocatedSigOccRn = wrapLocM $ \ rdr_name -> do
+       { local_env <- getLocalRdrEnv
+       ; case lookupLocalRdrEnv local_env rdr_name of {
+               Just n  -> return n ;
+               Nothing -> do
+       { mb_gre <- lookupGreLocalRn rdr_name
+       ; case mb_gre of 
+               Just gre -> return (gre_name gre) 
+               Nothing  -> lookupGlobalOccRn rdr_name
+       }}}
 
 -- lookupInstDeclBndr is used for the binders in an 
 -- instance declaration.   Here we use the class name to
 
 -- lookupInstDeclBndr is used for the binders in an 
 -- instance declaration.   Here we use the class name to
index 9a08e9a..3c23921 100644 (file)
@@ -306,11 +306,15 @@ data TcLclEnv             -- Changes as we move inside an expression
                -- Maintained during renaming, of course, but also during
                -- type checking, solely so that when renaming a Template-Haskell
                -- splice we have the right environment for the renamer.
                -- Maintained during renaming, of course, but also during
                -- type checking, solely so that when renaming a Template-Haskell
                -- splice we have the right environment for the renamer.
+               --
+               -- Used only for names bound within a value binding (bound by
+               -- lambda, case, where, let etc), but *not* for top-level names.
+               -- 
+               -- Does *not* include global name envt; may shadow it
+               -- Includes both ordinary variables and type variables;
+               -- they are kept distinct because tyvar have a different
+               -- occurrence contructor (Name.TvOcc)
                -- 
                -- 
-               --   Does *not* include global name envt; may shadow it
-               --   Includes both ordinary variables and type variables;
-               --   they are kept distinct because tyvar have a different
-               --   occurrence contructor (Name.TvOcc)
                -- We still need the unsullied global name env so that
                --   we can look up record field names
 
                -- We still need the unsullied global name env so that
                --   we can look up record field names