X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Frename%2FRnEnv.lhs;h=2ecaf612954c63302e2c74cf2c979ab4a69ce752;hp=2a1ae6b2e9aa16a85a3475b2871169c108c9e767;hb=7bb3d1fc79521d591cd9f824893963141a7997b6;hpb=57984dc34dcb242772bb81f1795c9afa3b7c36c1 diff --git a/compiler/rename/RnEnv.lhs b/compiler/rename/RnEnv.lhs index 2a1ae6b..2ecaf61 100644 --- a/compiler/rename/RnEnv.lhs +++ b/compiler/rename/RnEnv.lhs @@ -1,4 +1,4 @@ -\% +% % (c) The GRASP/AQUA Project, Glasgow University, 1992-2006 % \section[RnEnv]{Environment manipulation for the renamer monad} @@ -8,14 +8,14 @@ module RnEnv ( newTopSrcBinder, lookupFamInstDeclBndr, lookupLocatedTopBndrRn, lookupTopBndrRn, lookupLocatedOccRn, lookupOccRn, - lookupLocatedGlobalOccRn, lookupGlobalOccRn, - lookupLocalDataTcNames, lookupSrcOcc_maybe, - lookupSigOccRn, + lookupLocatedGlobalOccRn, + lookupGlobalOccRn, lookupGlobalOccRn_maybe, + lookupLocalDataTcNames, lookupSigOccRn, lookupFixityRn, lookupTyFixityRn, lookupInstDeclBndr, lookupRecordBndr, lookupConstructorFields, - lookupSyntaxName, lookupSyntaxTable, lookupImportedName, + lookupSyntaxName, lookupSyntaxTable, lookupGreRn, lookupGreLocalRn, lookupGreRn_maybe, - getLookupOccRn, + getLookupOccRn, addUsedRdrNames, newLocalsRn, newIPNameRn, bindLocalNames, bindLocalNamesFV, @@ -30,7 +30,9 @@ module RnEnv ( mapFvRn, mapFvRnCPS, warnUnusedMatches, warnUnusedModules, warnUnusedImports, warnUnusedTopBinds, warnUnusedLocalBinds, - dataTcOccs, unknownNameErr, perhapsForallMsg + dataTcOccs, unknownNameErr, kindSigErr, perhapsForallMsg, + + checkM ) where #include "HsVersions.h" @@ -66,6 +68,7 @@ import List ( nubBy ) import DynFlags import FastString import Control.Monad +import qualified Data.Set as Set \end{code} \begin{code} @@ -162,6 +165,18 @@ newTopSrcBinder this_mod (L loc rdr_name) Looking up a name in the RnEnv. +Note [Type and class operator definitions] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We want to reject all of these unless we have -XTypeOperators (Trac #3265) + data a :*: b = ... + class a :*: b where ... + data (:*:) a b = .... + class (:*:) a b where ... +The latter two mean that we are not just looking for a +*syntactically-infix* declaration, but one that uses an operator +OccName. We use OccName.isSymOcc to detect that case, which isn't +terribly efficient, but there seems to be no better way. + \begin{code} lookupTopBndrRn :: RdrName -> RnM Name lookupTopBndrRn n = do nopt <- lookupTopBndrRn_maybe n @@ -203,7 +218,14 @@ lookupTopBndrRn_maybe rdr_name ; return (Just n)} | otherwise - = do { mb_gre <- lookupGreLocalRn rdr_name + = do { -- Check for operators in type or class declarations + -- See Note [Type and class operator definitions] + let occ = rdrNameOcc rdr_name + ; when (isTcOcc occ && isSymOcc occ) + (do { op_ok <- doptM Opt_TypeOperators + ; checkM op_ok (addErr (opDeclErr rdr_name)) }) + + ; mb_gre <- lookupGreLocalRn rdr_name ; case mb_gre of Nothing -> returnM Nothing Just gre -> returnM (Just $ gre_name gre) } @@ -286,6 +308,7 @@ 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 + ; addUsedRdrName rdr_name ; env <- getGlobalRdrEnv ; case filter is_good (lookupGlobalRdrEnv env (rdrNameOcc rdr_name)) of -- NB: lookupGlobalRdrEnv, not lookupGRE_RdrName! @@ -300,30 +323,25 @@ lookup_sub_bndr is_good doc rdr_name } | otherwise -- Occurs in derived instances, where we just - -- refer directly to the right method - = ASSERT2( not (isQual rdr_name), ppr rdr_name ) - -- NB: qualified names are rejected by the parser - lookupImportedName rdr_name + -- refer directly to the right method with an Orig + -- And record fields can be Quals: C { F.f = x } + = lookupGlobalOccRn rdr_name newIPNameRn :: IPName RdrName -> TcRnIf m n (IPName Name) newIPNameRn ip_rdr = newIPName (mapIPName rdrNameOcc ip_rdr) --- Looking up family names in type instances is a subtle affair. The family --- may be imported, in which case we need to lookup the occurence of a global --- name. Alternatively, the family may be in the same binding group (and in --- fact in a declaration processed later), and we need to create a new top --- source binder. +-- If the family is declared locally, it will not yet be in the main +-- environment; hence, we pass in an extra one here, which we check first. +-- See "Note [Looking up family names in family instances]" in 'RnNames'. -- --- So, also this is strictly speaking an occurence, we cannot raise an error --- message yet for instances without a family declaration. This will happen --- during renaming the type instance declaration in RnSource.rnTyClDecl. --- -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) - Nothing -> newTopSrcBinder mod lrdr_name } +lookupFamInstDeclBndr :: GlobalRdrEnv -> Located RdrName -> RnM Name +lookupFamInstDeclBndr tyclGroupEnv (L loc rdr_name) + = setSrcSpan loc $ + case lookupGRE_RdrName rdr_name tyclGroupEnv of + (gre:_) -> return $ gre_name gre + -- if there is more than one, an error will be raised elsewhere + [] -> lookupOccRn rdr_name + -------------------------------------------------- -- Occurrences @@ -350,54 +368,43 @@ lookupLocatedGlobalOccRn = wrapLocM lookupGlobalOccRn lookupGlobalOccRn :: RdrName -> RnM Name -- lookupGlobalOccRn is like lookupOccRn, except that it looks in the global --- environment. It's called directly only for --- record field names --- class op names in class and instance decls --- names in export lists +-- environment. Adds an error message if the RdrName is not in scope. +-- Also has a special case for GHCi. lookupGlobalOccRn rdr_name - | not (isSrcRdrName rdr_name) - = lookupImportedName rdr_name - - | otherwise - = 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 -> 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. - allow_qual <- doptM Opt_ImplicitImportQualified - mod <- getModule + = do { -- First look up the name in the normal environment. + mb_name <- lookupGlobalOccRn_maybe rdr_name + ; case mb_name of { + Just n -> return n ; + 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. + 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 unboundName rdr_name - } - -lookupImportedName :: RdrName -> TcRnIf m n Name --- Lookup the occurrence of an imported name --- The RdrName is *always* qualified or Exact --- Treat it as an original name, and conjure up the Name --- Usually it's Exact or Orig, but it can be Qual if it --- comes from an hi-boot file. (This minor infelicity is --- just to reduce duplication in the parser.) -lookupImportedName rdr_name - | Just n <- isExact_maybe rdr_name - -- This happens in derived code - = returnM n - - -- Always Orig, even when reading a .hi-boot file + ; if isQual rdr_name && allow_qual && mod == iNTERACTIVE + then lookupQualifiedName rdr_name + else unboundName rdr_name } } } + +lookupGlobalOccRn_maybe :: RdrName -> RnM (Maybe Name) +-- No filter function; does not report an error on failure + +lookupGlobalOccRn_maybe rdr_name + | Just n <- isExact_maybe rdr_name -- This happens in derived code + = return (Just n) + | Just (rdr_mod, rdr_occ) <- isOrig_maybe rdr_name - = lookupOrig rdr_mod rdr_occ + = do { n <- lookupOrig rdr_mod rdr_occ; return (Just n) } | otherwise - = pprPanic "RnEnv.lookupImportedName" (ppr rdr_name) + = do { mb_gre <- lookupGreRn_maybe rdr_name + ; case mb_gre of + Nothing -> return Nothing + Just gre -> return (Just (gre_name gre)) } + unboundName :: RdrName -> RnM Name unboundName rdr_name @@ -412,19 +419,30 @@ unboundName rdr_name -- Lookup in the Global RdrEnv of the module -------------------------------------------------- -lookupSrcOcc_maybe :: RdrName -> RnM (Maybe Name) --- No filter function; does not report an error on failure -lookupSrcOcc_maybe rdr_name - = do { mb_gre <- lookupGreRn_maybe rdr_name - ; case mb_gre of - Nothing -> returnM Nothing - Just gre -> returnM (Just (gre_name gre)) } - -------------------------- lookupGreRn_maybe :: RdrName -> RnM (Maybe GlobalRdrElt) -- Just look up the RdrName in the GlobalRdrEnv lookupGreRn_maybe rdr_name - = lookupGreRn_help rdr_name (lookupGRE_RdrName rdr_name) + = do { mGre <- lookupGreRn_help rdr_name (lookupGRE_RdrName rdr_name) + ; case mGre of + Just gre -> + case gre_prov gre of + LocalDef -> return () + Imported _ -> addUsedRdrName rdr_name + Nothing -> + return () + ; return mGre } + +addUsedRdrName :: RdrName -> RnM () +addUsedRdrName rdr + = do { env <- getGblEnv + ; updMutVar (tcg_used_rdrnames env) + (\s -> Set.insert rdr s) } + +addUsedRdrNames :: [RdrName] -> RnM () +addUsedRdrNames rdrs + = do { env <- getGblEnv + ; updMutVar (tcg_used_rdrnames env) + (\s -> foldr Set.insert s rdrs) } lookupGreRn :: RdrName -> RnM GlobalRdrElt -- If not found, add error message, and return a fake GRE @@ -843,13 +861,15 @@ bindTyVarsRn :: SDoc -> [LHsTyVarBndr RdrName] -> RnM a -- Haskell-98 binding of type variables; e.g. within a data type decl bindTyVarsRn doc_str tyvar_names enclosed_scope - = let - located_tyvars = hsLTyVarLocNames tyvar_names - in - bindLocatedLocalsRn doc_str located_tyvars $ \ names -> - enclosed_scope (zipWith replace tyvar_names names) - where - replace (L loc n1) n2 = L loc (replaceTyVarName n1 n2) + = bindLocatedLocalsRn doc_str located_tyvars $ \ names -> + do { kind_sigs_ok <- doptM Opt_KindSignatures + ; checkM (null kinded_tyvars || kind_sigs_ok) + (mapM_ (addErr . kindSigErr) kinded_tyvars) + ; enclosed_scope (zipWith replace tyvar_names names) } + where + replace (L loc n1) n2 = L loc (replaceTyVarName n1 n2) + located_tyvars = hsLTyVarLocNames tyvar_names + kinded_tyvars = [n | L _ (KindedTyVar n _) <- tyvar_names] bindPatSigTyVars :: [LHsType RdrName] -> ([Name] -> RnM a) -> RnM a -- Find the type variables in the pattern type @@ -921,6 +941,8 @@ checkShadowedNames doc_str (global_env,local_env) loc_rdr_names ; mappM_ check_shadow loc_rdr_names } where check_shadow (loc, occ) + | startsWithUnderscore occ = return () -- Do not report shadowing for "_x" + -- See Trac #3262 | Just n <- mb_local = complain [ptext (sLit "bound at") <+> ppr (nameSrcLoc n)] | otherwise = do { gres' <- filterM is_shadowed_gre gres ; complain (map pprNameProvenance gres') } @@ -1024,7 +1046,7 @@ warnUnusedBinds names = mappM_ warnUnusedName (filter reportable names) | isWiredInName name = False -- Don't report unused wired-in names -- Otherwise we get a zillion warnings -- from Data.Tuple - | otherwise = reportIfUnused (nameOccName name) + | otherwise = not (startsWithUnderscore (nameOccName name)) ------------------------- @@ -1106,7 +1128,18 @@ dupNamesErr get_loc descriptor names | otherwise = ptext (sLit "Bound at:") <+> vcat (map ppr (sortLe (<=) locs)) +kindSigErr :: Outputable a => a -> SDoc +kindSigErr thing + = hang (ptext (sLit "Illegal kind signature for") <+> quotes (ppr thing)) + 2 (ptext (sLit "Perhaps you intended to use -XKindSignatures")) + + badQualBndrErr :: RdrName -> SDoc badQualBndrErr rdr_name = ptext (sLit "Qualified name in binding position:") <+> ppr rdr_name + +opDeclErr :: RdrName -> SDoc +opDeclErr n + = hang (ptext (sLit "Illegal declaration of a type or class operator") <+> quotes (ppr n)) + 2 (ptext (sLit "Use -XTypeOperators to declare operators in type and declarations")) \end{code}