X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Frename%2FRnSource.lhs;h=b3fdd2ea167a2140ede2e490f25024c4d96bf589;hb=a27c5f77da8b3b3f00f9902b69a504460f234e8c;hp=8e2094d5a91affa91a2434b63909657889528520;hpb=f3399c446c7507d46d6cc550aa2fe7027dbc1b5b;p=ghc-hetmet.git diff --git a/compiler/rename/RnSource.lhs b/compiler/rename/RnSource.lhs index 8e2094d..b3fdd2e 100644 --- a/compiler/rename/RnSource.lhs +++ b/compiler/rename/RnSource.lhs @@ -36,8 +36,8 @@ import RnEnv ( lookupLocalDataTcNames, bindTyVarsRn, extendTyVarEnvFVRn, bindLocalNames, checkDupRdrNames, mapFvRn, lookupGreLocalRn, ) -import RnNames (importsFromLocalDecls, extendRdrEnvRn) -import HscTypes (GenAvailInfo(..)) +import RnNames ( getLocalNonValBinders, extendGlobalRdrEnvRn ) +import HscTypes ( GenAvailInfo(..) ) import RnHsDoc ( rnHsDoc, rnMbLHsDoc ) import TcRnMonad @@ -46,17 +46,39 @@ import Class ( FunDep ) import Name ( Name, nameOccName ) import NameSet import NameEnv -import UniqFM +import LazyUniqFM import OccName import Outputable +import FastString import SrcLoc ( Located(..), unLoc, noLoc ) import DynFlags ( DynFlag(..) ) -import Maybes ( seqMaybe ) import Maybe ( isNothing ) -import Monad ( liftM, when ) import BasicTypes ( Boxity(..) ) import ListSetOps (findDupsEq, mkLookupFun) + +import Control.Monad +\end{code} + +\begin{code} +-- XXX +thenM :: Monad a => a b -> (b -> a c) -> a c +thenM = (>>=) + +thenM_ :: Monad a => a b -> a c -> a c +thenM_ = (>>) + +returnM :: Monad m => a -> m a +returnM = return + +mappM :: (Monad m) => (a -> m b) -> [a] -> m [b] +mappM = mapM + +mappM_ :: (Monad m) => (a -> m b) -> [a] -> m () +mappM_ = mapM_ + +checkM :: Monad m => Bool -> m () -> m () +checkM = unless \end{code} @rnSourceDecl@ `renames' declarations. @@ -76,10 +98,10 @@ Checks the @(..)@ etc constraints in the export list. \begin{code} --- brings the binders of the group into scope in the appropriate places; +-- Brings the binders of the group into scope in the appropriate places; -- does NOT assume that anything is in scope already -- --- the Bool determines whether (True) names in the group shadow existing +-- The Bool determines whether (True) names in the group shadow existing -- Unquals in the global environment (used in Template Haskell) or -- (False) whether duplicates are reported as an error rnSrcDecls :: Bool -> HsGroup RdrName -> RnM (TcGblEnv, HsGroup Name) @@ -101,8 +123,10 @@ rnSrcDecls shadowP group@(HsGroup {hs_valds = val_decls, local_fix_env <- makeMiniFixityEnv fix_decls; -- (B) Bring top level binders (and their fixities) into scope, - -- except for the value bindings, which get brought in below. - inNewEnv (importsFromLocalDecls shadowP group local_fix_env) $ \ tcg_env -> do { + -- *except* for the value bindings, which get brought in below. + avails <- getLocalNonValBinders group ; + tc_envs <- extendGlobalRdrEnvRn shadowP avails local_fix_env ; + setEnvs tc_envs $ do { failIfErrsM ; -- No point in continuing if (say) we have duplicate declarations @@ -110,7 +134,7 @@ rnSrcDecls shadowP group@(HsGroup {hs_valds = val_decls, -- extend the record field env. -- This depends on the data constructors and field names being in -- scope from (B) above - inNewEnv (extendRecordFieldEnv tycl_decls) $ \ tcg_env -> do { + inNewEnv (extendRecordFieldEnv tycl_decls) $ \ _ -> do { -- (D) Rename the left-hand sides of the value bindings. -- This depends on everything from (B) being in scope, @@ -121,12 +145,8 @@ rnSrcDecls shadowP group@(HsGroup {hs_valds = val_decls, let { lhs_binders = map unLoc $ collectHsValBinders new_lhs; lhs_avails = map Avail lhs_binders } ; - inNewEnv (extendRdrEnvRn shadowP (tcg_rdr_env tcg_env, tcg_fix_env tcg_env) - lhs_avails local_fix_env - >>= \ (new_rdr_env, new_fix_env) -> - return (tcg_env { tcg_rdr_env = new_rdr_env, - tcg_fix_env = new_fix_env - })) $ \tcg_env -> do { + (tcg_env, tcl_env) <- extendGlobalRdrEnvRn shadowP lhs_avails local_fix_env ; + setEnvs (tcg_env, tcl_env) $ do { -- Now everything is in scope, as the remaining renaming assumes. @@ -535,8 +555,8 @@ validRuleLhs foralls lhs where checkl (L loc e) = check e - check (OpApp e1 op _ e2) = checkl op `seqMaybe` checkl_e e1 `seqMaybe` checkl_e e2 - check (HsApp e1 e2) = checkl e1 `seqMaybe` checkl_e e2 + check (OpApp e1 op _ e2) = checkl op `mplus` checkl_e e1 `mplus` checkl_e e2 + check (HsApp e1 e2) = checkl e1 `mplus` checkl_e e2 check (HsVar v) | v `notElem` foralls = Nothing check other = Just other -- Failure @@ -549,14 +569,14 @@ validRuleLhs foralls lhs check_e (HsLit e) = Nothing check_e (HsOverLit e) = Nothing - check_e (OpApp e1 op _ e2) = checkl_e e1 `seqMaybe` checkl_e op `seqMaybe` checkl_e e2 - check_e (HsApp e1 e2) = checkl_e e1 `seqMaybe` checkl_e e2 + check_e (OpApp e1 op _ e2) = checkl_e e1 `mplus` checkl_e op `mplus` checkl_e e2 + check_e (HsApp e1 e2) = checkl_e e1 `mplus` checkl_e e2 check_e (NegApp e _) = checkl_e e check_e (ExplicitList _ es) = checkl_es es check_e (ExplicitTuple es _) = checkl_es es check_e other = Just other -- Fails - checkl_es es = foldr (seqMaybe . checkl_e) Nothing es + checkl_es es = foldr (mplus . checkl_e) Nothing es -} badRuleLhsErr name lhs bad_e @@ -615,7 +635,7 @@ rnTyClDecl (tydecl@TyData {tcdND = new_or_data, tcdCtxt = context, ; (derivs', deriv_fvs) <- rn_derivs derivs ; condecls' <- rnConDecls (unLoc tycon') condecls -- No need to check for duplicate constructor decls - -- since that is done by RnNames.extendRdrEnvRn + -- since that is done by RnNames.extendGlobalRdrEnvRn ; returnM (TyData {tcdND = new_or_data, tcdCtxt = context', tcdLName = tycon', tcdTyVars = tyvars', tcdTyPats = typats', tcdKindSig = Nothing, @@ -643,7 +663,7 @@ rnTyClDecl (tydecl@TyData {tcdND = new_or_data, tcdCtxt = context, ; (derivs', deriv_fvs) <- rn_derivs derivs ; condecls' <- rnConDecls (unLoc tycon') condecls -- No need to check for duplicate constructor decls - -- since that is done by RnNames.extendRdrEnvRn + -- since that is done by RnNames.extendGlobalRdrEnvRn ; returnM (TyData {tcdND = new_or_data, tcdCtxt = noLoc [], tcdLName = tycon', tcdTyVars = tyvars', tcdTyPats = Nothing, tcdKindSig = sig, @@ -708,7 +728,7 @@ rnTyClDecl (ClassDecl {tcdCtxt = context, tcdLName = cname, ; return (tyvars', context', fds', ats', ats_fvs, sigs') } -- No need to check for duplicate associated type decls - -- since that is done by RnNames.extendRdrEnvRn + -- since that is done by RnNames.extendGlobalRdrEnvRn -- Check the signatures -- First process the class op sigs (op_sigs), then the fixity sigs (non_op_sigs). @@ -734,7 +754,7 @@ rnTyClDecl (ClassDecl {tcdCtxt = context, tcdLName = cname, gen_rdr_tyvars_w_locs = [ tv | tv <- extractGenericPatTyVars mbinds, not (unLoc tv `elemLocalRdrEnv` name_env) ] -- No need to check for duplicate method signatures - -- since that is done by RnNames.extendRdrEnvRn + -- since that is done by RnNames.extendGlobalRdrEnvRn -- and the methods are already in scope ; gen_tyvars <- newLocalsRn gen_rdr_tyvars_w_locs ; rnMethodBinds (unLoc cname') (mkSigTvFn sigs') gen_tyvars mbinds } @@ -836,7 +856,7 @@ rnConDeclDetails doc (InfixCon ty1 ty2) rnConDeclDetails doc (RecCon fields) = do { new_fields <- mappM (rnField doc) fields -- No need to check for duplicate fields - -- since that is done by RnNames.extendRdrEnvRn + -- since that is done by RnNames.extendGlobalRdrEnvRn ; return (RecCon new_fields) } rnField doc (ConDeclField name ty haddock_doc)