X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Frename%2FRnEnv.lhs;h=63db61ccb646e766e7529786b62f29d50d03b17d;hb=d1984e439154e95b2804ee83897e740b1713c53d;hp=aa477c98a6cd0b26093bc867ecbf7a49e7ab9443;hpb=dda6198504b9160d42331f5a64fd45fa552a82e9;p=ghc-hetmet.git diff --git a/compiler/rename/RnEnv.lhs b/compiler/rename/RnEnv.lhs index aa477c9..63db61c 100644 --- a/compiler/rename/RnEnv.lhs +++ b/compiler/rename/RnEnv.lhs @@ -4,21 +4,14 @@ \section[RnEnv]{Environment manipulation for the renamer monad} \begin{code} -{-# OPTIONS -w #-} --- The above warning supression flag is a temporary kludge. --- While working on this module you are encouraged to remove it and fix --- any warnings in the module. See --- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings --- for details - module RnEnv ( newTopSrcBinder, lookupFamInstDeclBndr, lookupLocatedBndrRn, lookupBndrRn, lookupBndrRn_maybe, - lookupLocatedTopBndrRn, lookupTopBndrRn, lookupBndrRn_maybe, + lookupLocatedTopBndrRn, lookupTopBndrRn, lookupLocatedOccRn, lookupOccRn, lookupLocatedGlobalOccRn, lookupGlobalOccRn, lookupLocalDataTcNames, lookupSrcOcc_maybe, - lookupFixityRn, lookupTyFixityRn, lookupLocatedSigOccRn, + lookupFixityRn, lookupTyFixityRn, lookupInstDeclBndr, lookupRecordBndr, lookupConstructorFields, lookupSyntaxName, lookupSyntaxTable, lookupImportedName, lookupGreRn, lookupGreLocalRn, lookupGreRn_maybe, @@ -44,9 +37,7 @@ module RnEnv ( import LoadIface ( loadInterfaceForName, loadSrcInterface ) import IfaceEnv ( lookupOrig, newGlobalBinder, newIPName ) -import HsSyn ( FixitySig(..), HsExpr(..), SyntaxExpr, SyntaxTable, - LHsTyVarBndr, LHsType, - Fixity, hsLTyVarLocNames, replaceTyVarName ) +import HsSyn import RdrHsSyn ( extractHsTyRdrTyVars ) import RdrName import HscTypes ( availNames, ModIface(..), FixItem(..), lookupFixity) @@ -64,8 +55,7 @@ import PrelNames ( mkUnboundName, rOOT_MAIN, iNTERACTIVE, consDataConKey, hasKey, forall_tv_RDR ) import UniqSupply import BasicTypes ( IPName, mapIPName, Fixity ) -import SrcLoc ( SrcSpan, srcSpanStart, Located(..), eqLocated, unLoc, - srcLocSpan, getLoc, combineSrcSpans, isOneLineSpan ) +import SrcLoc import Outputable import Util import Maybes @@ -225,35 +215,6 @@ lookupTopBndrRn_maybe rdr_name Nothing -> returnM Nothing Just gre -> returnM (Just $ gre_name gre) } --- lookupLocatedSigOccRn is used for type signatures and pragmas --- Is this valid? --- module A --- import M( f ) --- f :: Int -> Int --- f x = x --- It's clear that the 'f' in the signature must refer to A.f --- 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 = 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 :: Name -> Located RdrName -> RnM (Located Name) @@ -271,8 +232,8 @@ lookupInstDeclBndr :: Name -> Located RdrName -> RnM (Located Name) lookupInstDeclBndr cls rdr = lookup_located_sub_bndr is_op doc rdr where doc = ptext (sLit "method of class") <+> quotes (ppr cls) - is_op gre@(GRE {gre_par = ParentIs n}) = n == cls - is_op other = False + is_op (GRE {gre_par = ParentIs n}) = n == cls + is_op _ = False ----------------------------------------------- lookupRecordBndr :: Maybe (Located Name) -> Located RdrName -> RnM (Located Name) @@ -321,6 +282,7 @@ lookup_located_sub_bndr :: (GlobalRdrElt -> Bool) lookup_located_sub_bndr is_good doc rdr_name = wrapLocM (lookup_sub_bndr is_good doc) rdr_name +lookup_sub_bndr :: (GlobalRdrElt -> Bool) -> SDoc -> RdrName -> RnM Name lookup_sub_bndr is_good doc rdr_name | isUnqual rdr_name -- Find all the things the rdr-name maps to = do { -- and pick the one with the right parent name @@ -360,7 +322,7 @@ lookupFamInstDeclBndr :: Module -> Located RdrName -> RnM Name lookupFamInstDeclBndr mod lrdr_name@(L _ rdr_name) = do { mb_gre <- lookupGreRn_maybe rdr_name ; case mb_gre of - Just gre -> returnM (gre_name gre) ; + Just gre -> returnM (gre_name gre) Nothing -> newTopSrcBinder mod lrdr_name } -------------------------------------------------- @@ -397,23 +359,27 @@ lookupGlobalOccRn rdr_name = lookupImportedName rdr_name | otherwise - = -- First look up the name in the normal environment. - lookupGreRn_maybe rdr_name `thenM` \ mb_gre -> + = do + -- First look up the name in the normal environment. + mb_gre <- lookupGreRn_maybe rdr_name case mb_gre of { Just gre -> returnM (gre_name gre) ; - Nothing -> + Nothing -> do -- We allow qualified names on the command line to refer to -- *any* name exported by any module in scope, just as if -- there was an "import qualified M" declaration for every -- module. - getModule `thenM` \ mod -> - if isQual rdr_name && mod == iNTERACTIVE then - -- This test is not expensive, - lookupQualifiedName rdr_name -- and only happens for failed lookups - else do + allow_qual <- doptM Opt_ImplicitImportQualified + mod <- getModule + -- This test is not expensive, + -- and only happens for failed lookups + if isQual rdr_name && allow_qual && mod == iNTERACTIVE + then lookupQualifiedName rdr_name + else do traceRn $ text "lookupGlobalOccRn" - unboundName rdr_name } + unboundName rdr_name + } lookupImportedName :: RdrName -> TcRnIf m n Name -- Lookup the occurrence of an imported name @@ -625,7 +591,7 @@ lookupFixityRn name --------------- lookupTyFixityRn :: Located Name -> RnM Fixity -lookupTyFixityRn (L loc n) = lookupFixityRn n +lookupTyFixityRn (L _ n) = lookupFixityRn n --------------- lookupLocalDataTcNames :: RdrName -> RnM [Name] @@ -901,6 +867,7 @@ checkShadowedNames doc_str (global_env,local_env) loc_rdr_names \begin{code} -- A useful utility +mapFvRn :: (a -> RnM (b, FreeVars)) -> [a] -> RnM ([b], FreeVars) mapFvRn f xs = mappM f xs `thenM` \ stuff -> let (ys, fvs_s) = unzip stuff @@ -954,9 +921,11 @@ check_unused flag bound_names used_names ------------------------- -- Helpers +warnUnusedGREs :: [GlobalRdrElt] -> RnM () warnUnusedGREs gres = warnUnusedBinds [(n,p) | GRE {gre_name = n, gre_prov = p} <- gres] +warnUnusedLocals :: [Name] -> RnM () warnUnusedLocals names = warnUnusedBinds [(n,LocalDef) | n<-names] @@ -984,6 +953,7 @@ warnUnusedName (name, Imported is) pp_mod = quotes (ppr (importSpecModule spec)) msg = ptext (sLit "Imported from") <+> pp_mod <+> ptext (sLit "but not used") +addUnusedWarning :: Name -> SrcSpan -> SDoc -> RnM () addUnusedWarning name span msg = addWarnAt span $ sep [msg <> colon, @@ -992,6 +962,7 @@ addUnusedWarning name span msg \end{code} \begin{code} +addNameClashErrRn :: RdrName -> [GlobalRdrElt] -> RnM () addNameClashErrRn rdr_name names = addErr (vcat [ptext (sLit "Ambiguous occurrence") <+> quotes (ppr rdr_name), ptext (sLit "It could refer to") <+> vcat (msg1 : msgs)]) @@ -1001,12 +972,14 @@ addNameClashErrRn rdr_name names msgs = [ptext (sLit " or") <+> mk_ref np | np <- nps] mk_ref gre = quotes (ppr (gre_name gre)) <> comma <+> pprNameProvenance gre +shadowedNameWarn :: SDoc -> OccName -> [SDoc] -> SDoc shadowedNameWarn doc occ shadowed_locs = sep [ptext (sLit "This binding for") <+> quotes (ppr occ) <+> ptext (sLit "shadows the existing binding") <> plural shadowed_locs, nest 2 (vcat shadowed_locs)] $$ doc +unknownNameErr :: RdrName -> SDoc unknownNameErr rdr_name = vcat [ hang (ptext (sLit "Not in scope:")) 2 (pprNonVarNameSpace (occNameSpace (rdrNameOcc rdr_name)) @@ -1017,10 +990,12 @@ unknownNameErr rdr_name = ptext (sLit "Perhaps you intended to use -XRankNTypes or similar flag") | otherwise = empty +unknownSubordinateErr :: SDoc -> RdrName -> SDoc unknownSubordinateErr doc op -- Doc is "method of class" or -- "field of constructor" = quotes (ppr op) <+> ptext (sLit "is not a (visible)") <+> doc +badOrigBinding :: RdrName -> SDoc badOrigBinding name = ptext (sLit "Illegal binding of built-in syntax:") <+> ppr (rdrNameOcc name) -- The rdrNameOcc is because we don't want to print Prelude.(,) @@ -1038,6 +1013,7 @@ dupNamesErr get_loc descriptor names | otherwise = ptext (sLit "Bound at:") <+> vcat (map ppr (sortLe (<=) locs)) +badQualBndrErr :: RdrName -> SDoc badQualBndrErr rdr_name = ptext (sLit "Qualified name in binding position:") <+> ppr rdr_name \end{code}