X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Frename%2FRnEnv.lhs;h=c3b5592834f2ac5855cc1707fd281fa5b65ea0b7;hp=20d221857fe780edf13f78d0f51f3ec259c9edea;hb=f1cc3eb980a634e62f2739a7a25387c902fa9d8a;hpb=e17a800817a370fd198831f12cff35122376fa8d diff --git a/compiler/rename/RnEnv.lhs b/compiler/rename/RnEnv.lhs index 20d2218..c3b5592 100644 --- a/compiler/rename/RnEnv.lhs +++ b/compiler/rename/RnEnv.lhs @@ -25,9 +25,9 @@ module RnEnv ( bindSigTyVarsFV, bindPatSigTyVars, bindPatSigTyVarsFV, bindTyVarsRn, extendTyVarEnvFVRn, - checkDupRdrNames, checkDupNames, checkShadowedNames, - checkDupAndShadowedRdrNames, - mapFvRn, mapFvRnCPS, + checkDupRdrNames, checkDupAndShadowedRdrNames, + checkDupNames, checkDupAndShadowedNames, + addFvRn, mapFvRn, mapMaybeFvRn, mapFvRnCPS, warnUnusedMatches, warnUnusedModules, warnUnusedImports, warnUnusedTopBinds, warnUnusedLocalBinds, dataTcOccs, unknownNameErr, kindSigErr, perhapsForallMsg @@ -284,12 +284,12 @@ lookupSubBndr parent doc rdr_name | otherwise -- Find all the things the rdr-name maps to = do { -- and pick the one with the right parent name ; env <- getGlobalRdrEnv - ; let gres = (lookupGlobalRdrEnv env (rdrNameOcc rdr_name)) + ; let gres = lookupGlobalRdrEnv env (rdrNameOcc rdr_name) ; case pick parent gres of -- NB: lookupGlobalRdrEnv, not lookupGRE_RdrName! -- The latter does pickGREs, but we want to allow 'x' -- even if only 'M.x' is in scope - [gre] -> do { addUsedRdrName gre rdr_name + [gre] -> do { addUsedRdrNames (used_rdr_names gre) ; return (gre_name gre) } [] -> do { addErr (unknownSubordinateErr doc rdr_name) ; traceRn (text "RnEnv.lookup_sub_bndr" <+> (ppr rdr_name $$ ppr gres)) @@ -306,6 +306,15 @@ lookupSubBndr parent doc rdr_name right_parent p (GRE { gre_par = ParentIs p' }) = p==p' right_parent _ _ = False + -- Note [Usage for sub-bndrs] + used_rdr_names gre + | isQual rdr_name = [rdr_name] + | otherwise = case gre_prov gre of + LocalDef -> [rdr_name] + Imported is -> map mk_qual_rdr is + mk_qual_rdr imp_spec = mkRdrQual (is_as (is_decl imp_spec)) rdr_occ + rdr_occ = rdrNameOcc rdr_name + newIPNameRn :: IPName RdrName -> TcRnIf m n (IPName Name) newIPNameRn ip_rdr = newIPName (mapIPName rdrNameOcc ip_rdr) @@ -320,12 +329,25 @@ lookupFamInstDeclBndr tyclGroupEnv (L loc rdr_name) (gre:_) -> return $ gre_name gre -- if there is more than one, an error will be raised elsewhere [] -> lookupOccRn rdr_name +\end{code} +Note [Usage for sub-bndrs] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +If you have this + import qualified M( C( f ) ) + intance M.C T where + f x = x +then is the qualified import M.f used? Obviously yes. +But the RdrName used in the instance decl is unqualified. In effect, +we fill in the qualification by looking for f's whose class is M.C +But when adding to the UsedRdrNames we must make that qualification +explicit, otherwise we get "Redundant import of M.C". -------------------------------------------------- -- Occurrences -------------------------------------------------- +\begin{code} getLookupOccRn :: RnM (Name -> Maybe Name) getLookupOccRn = getLocalRdrEnv `thenM` \ local_env -> @@ -629,7 +651,6 @@ type MiniFixityEnv = FastStringEnv (Located Fixity) -------------------------------- -- Used for nested fixity decls to bind names along with their fixities. -- the fixities are given as a UFM from an OccName's FastString to a fixity decl --- Also check for unused binders bindLocalNamesFV_WithFixities :: [Name] -> MiniFixityEnv -> RnM (a, FreeVars) -> RnM (a, FreeVars) @@ -795,20 +816,11 @@ newLocalBndrsRn :: [Located RdrName] -> RnM [Name] newLocalBndrsRn = mapM newLocalBndrRn --------------------- -checkDupAndShadowedRdrNames :: SDoc -> [Located RdrName] -> RnM () -checkDupAndShadowedRdrNames doc loc_rdr_names - = do { checkDupRdrNames doc loc_rdr_names - ; envs <- getRdrEnvs - ; checkShadowedNames doc envs - [(loc,rdrNameOcc rdr) | L loc rdr <- loc_rdr_names] } - ---------------------- -bindLocatedLocalsRn :: SDoc -- Documentation string for error message - -> [Located RdrName] +bindLocatedLocalsRn :: [Located RdrName] -> ([Name] -> RnM a) -> RnM a -bindLocatedLocalsRn doc_str rdr_names_w_loc enclosed_scope - = do { checkDupAndShadowedRdrNames doc_str rdr_names_w_loc +bindLocatedLocalsRn rdr_names_w_loc enclosed_scope + = do { checkDupAndShadowedRdrNames rdr_names_w_loc -- Make fresh Names and extend the environment ; names <- newLocalBndrsRn rdr_names_w_loc @@ -835,20 +847,20 @@ bindLocalNamesFV names enclosed_scope ------------------------------------- -- binLocalsFVRn is the same as bindLocalsRn -- except that it deals with free vars -bindLocatedLocalsFV :: SDoc -> [Located RdrName] +bindLocatedLocalsFV :: [Located RdrName] -> ([Name] -> RnM (a,FreeVars)) -> RnM (a, FreeVars) -bindLocatedLocalsFV doc rdr_names enclosed_scope - = bindLocatedLocalsRn doc rdr_names $ \ names -> +bindLocatedLocalsFV rdr_names enclosed_scope + = bindLocatedLocalsRn rdr_names $ \ names -> enclosed_scope names `thenM` \ (thing, fvs) -> return (thing, delListFromNameSet fvs names) ------------------------------------- -bindTyVarsRn :: SDoc -> [LHsTyVarBndr RdrName] +bindTyVarsRn :: [LHsTyVarBndr RdrName] -> ([LHsTyVarBndr Name] -> RnM a) -> RnM a -- Haskell-98 binding of type variables; e.g. within a data type decl -bindTyVarsRn doc_str tyvar_names enclosed_scope - = bindLocatedLocalsRn doc_str located_tyvars $ \ names -> +bindTyVarsRn tyvar_names enclosed_scope + = bindLocatedLocalsRn located_tyvars $ \ names -> do { kind_sigs_ok <- doptM Opt_KindSignatures ; unless (null kinded_tyvars || kind_sigs_ok) (mapM_ (addErr . kindSigErr) kinded_tyvars) @@ -875,9 +887,7 @@ bindPatSigTyVars tys thing_inside -- f (x :: t) (y :: t) = .... -- We don't want to complain about binding t twice! - ; bindLocatedLocalsRn doc_sig nubbed_tvs thing_inside }} - where - doc_sig = text "In a pattern type-signature" + ; bindLocatedLocalsRn nubbed_tvs thing_inside }} bindPatSigTyVarsFV :: [LHsType RdrName] -> RnM (a, FreeVars) @@ -902,30 +912,42 @@ extendTyVarEnvFVRn :: [Name] -> RnM (a, FreeVars) -> RnM (a, FreeVars) extendTyVarEnvFVRn tyvars thing_inside = bindLocalNamesFV tyvars thing_inside ------------------------------------- -checkDupRdrNames :: SDoc - -> [Located RdrName] - -> RnM () -checkDupRdrNames doc_str rdr_names_w_loc +checkDupRdrNames :: [Located RdrName] -> RnM () +checkDupRdrNames rdr_names_w_loc = -- Check for duplicated names in a binding group - mapM_ (dupNamesErr getLoc doc_str) dups + mapM_ (dupNamesErr getLoc) dups where (_, dups) = removeDups (\n1 n2 -> unLoc n1 `compare` unLoc n2) rdr_names_w_loc -checkDupNames :: SDoc - -> [Name] - -> RnM () -checkDupNames doc_str names +checkDupNames :: [Name] -> RnM () +checkDupNames names = -- Check for duplicated names in a binding group - mapM_ (dupNamesErr nameSrcSpan doc_str) dups + mapM_ (dupNamesErr nameSrcSpan) dups where (_, dups) = removeDups (\n1 n2 -> nameOccName n1 `compare` nameOccName n2) names +--------------------- +checkDupAndShadowedRdrNames :: [Located RdrName] -> RnM () +checkDupAndShadowedRdrNames loc_rdr_names + = do { checkDupRdrNames loc_rdr_names + ; envs <- getRdrEnvs + ; checkShadowedOccs envs loc_occs } + where + loc_occs = [(loc,rdrNameOcc rdr) | L loc rdr <- loc_rdr_names] + +checkDupAndShadowedNames :: (GlobalRdrEnv, LocalRdrEnv) -> [Name] -> RnM () +checkDupAndShadowedNames envs names + = do { checkDupNames names + ; checkShadowedOccs envs loc_occs } + where + loc_occs = [(nameSrcSpan name, nameOccName name) | name <- names] + ------------------------------------- -checkShadowedNames :: SDoc -> (GlobalRdrEnv, LocalRdrEnv) -> [(SrcSpan,OccName)] -> RnM () -checkShadowedNames doc_str (global_env,local_env) loc_rdr_names +checkShadowedOccs :: (GlobalRdrEnv, LocalRdrEnv) -> [(SrcSpan,OccName)] -> RnM () +checkShadowedOccs (global_env,local_env) loc_occs = ifOptM Opt_WarnNameShadowing $ - do { traceRn (text "shadow" <+> ppr loc_rdr_names) - ; mapM_ check_shadow loc_rdr_names } + do { traceRn (text "shadow" <+> ppr loc_occs) + ; mapM_ check_shadow loc_occs } where check_shadow (loc, occ) | startsWithUnderscore occ = return () -- Do not report shadowing for "_x" @@ -935,7 +957,7 @@ checkShadowedNames doc_str (global_env,local_env) loc_rdr_names ; complain (map pprNameProvenance gres') } where complain [] = return () - complain pp_locs = addWarnAt loc (shadowedNameWarn doc_str occ pp_locs) + complain pp_locs = addWarnAt loc (shadowedNameWarn occ pp_locs) mb_local = lookupLocalRdrOcc local_env occ gres = lookupGRE_RdrName (mkRdrUnqual occ) global_env -- Make an Unqualified RdrName and look that up, so that @@ -967,11 +989,19 @@ checkShadowedNames doc_str (global_env,local_env) loc_rdr_names \begin{code} -- A useful utility +addFvRn :: FreeVars -> RnM (thing, FreeVars) -> RnM (thing, FreeVars) +addFvRn fvs1 thing_inside = do { (res, fvs2) <- thing_inside + ; return (res, fvs1 `plusFV` fvs2) } + mapFvRn :: (a -> RnM (b, FreeVars)) -> [a] -> RnM ([b], FreeVars) mapFvRn f xs = do stuff <- mapM f xs case unzip stuff of (ys, fvs_s) -> return (ys, plusFVs fvs_s) +mapMaybeFvRn :: (a -> RnM (b, FreeVars)) -> Maybe a -> RnM (Maybe b, FreeVars) +mapMaybeFvRn _ Nothing = return (Nothing, emptyFVs) +mapMaybeFvRn f (Just x) = do { (y, fvs) <- f x; return (Just y, fvs) } + -- because some of the rename functions are CPSed: -- maps the function across the list from left to right; -- collects all the free vars into one set @@ -1070,12 +1100,11 @@ 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 +shadowedNameWarn :: OccName -> [SDoc] -> SDoc +shadowedNameWarn 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 @@ -1102,18 +1131,15 @@ badOrigBinding name = ptext (sLit "Illegal binding of built-in syntax:") <+> ppr (rdrNameOcc name) -- The rdrNameOcc is because we don't want to print Prelude.(,) -dupNamesErr :: Outputable n => (n -> SrcSpan) -> SDoc -> [n] -> RnM () -dupNamesErr get_loc descriptor names +dupNamesErr :: Outputable n => (n -> SrcSpan) -> [n] -> RnM () +dupNamesErr get_loc names = addErrAt big_loc $ vcat [ptext (sLit "Conflicting definitions for") <+> quotes (ppr (head names)), - locations, descriptor] + locations] where locs = map get_loc names big_loc = foldr1 combineSrcSpans locs - one_line = isOneLineSpan big_loc - locations | one_line = empty - | otherwise = ptext (sLit "Bound at:") <+> - vcat (map ppr (sortLe (<=) locs)) + locations = ptext (sLit "Bound at:") <+> vcat (map ppr (sortLe (<=) locs)) kindSigErr :: Outputable a => a -> SDoc kindSigErr thing