X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FdeSugar%2FDesugar.lhs;h=1a5d7e82253dacffae7563432427742cf7af068f;hb=f4c9d2b23bd63b48566e0ca3b13c8bdfc4cd0c0b;hp=d95ca8ceb62d2c3eb90b4b27588329717f805253;hpb=550421384b8364cdaf3135f7859c9f7d7ee1fff1;p=ghc-hetmet.git diff --git a/ghc/compiler/deSugar/Desugar.lhs b/ghc/compiler/deSugar/Desugar.lhs index d95ca8c..1a5d7e8 100644 --- a/ghc/compiler/deSugar/Desugar.lhs +++ b/ghc/compiler/deSugar/Desugar.lhs @@ -10,8 +10,7 @@ module Desugar ( deSugar, deSugarExpr ) where import CmdLineOpts ( DynFlag(..), dopt, opt_SccProfilingOn ) import HscTypes ( ModGuts(..), ModGuts, HscEnv(..), GhciMode(..), - Dependencies(..), TypeEnv, - unQualInScope, availsToNameSet ) + Dependencies(..), TypeEnv, IsBootInterface, unQualInScope ) import HsSyn ( RuleDecl(..), RuleBndr(..), HsExpr(..), LHsExpr, HsBindGroup(..), LRuleDecl, HsBind(..) ) import TcRnTypes ( TcGblEnv(..), ImportAvails(..) ) @@ -20,30 +19,32 @@ import Id ( Id, setIdLocalExported, idName ) import Name ( Name, isExternalName ) import CoreSyn import PprCore ( pprIdRules, pprCoreExpr ) -import Subst ( substExpr, mkSubst, mkInScopeSet ) +import Subst ( SubstResult(..), substExpr, mkSubst, extendIdSubstList ) import DsMonad import DsExpr ( dsLExpr ) import DsBinds ( dsHsBinds, AutoScc(..) ) import DsForeign ( dsForeigns ) import DsExpr () -- Forces DsExpr to be compiled; DsBinds only -- depends on DsExpr.hi-boot. -import Module ( Module, moduleEnvElts, emptyModuleEnv ) +import Module ( Module, ModuleName, moduleEnvElts, delModuleEnv, moduleNameFS ) import Id ( Id ) import RdrName ( GlobalRdrEnv ) import NameSet import VarEnv import VarSet -import Bag ( isEmptyBag, mapBag, emptyBag, bagToList ) +import Bag ( Bag, isEmptyBag, mapBag, emptyBag, bagToList ) import CoreLint ( showPass, endPass ) import CoreFVs ( ruleRhsFreeVars ) +import Packages ( thPackage ) import ErrUtils ( doIfSet, dumpIfSet_dyn, pprBagOfWarnings, mkWarnMsg, errorsFound, WarnMsg ) +import ListSetOps ( insertList ) import Outputable -import qualified Pretty import UniqSupply ( mkSplitUniqSupply ) import SrcLoc ( Located(..), SrcSpan, unLoc ) import DATA_IOREF ( readIORef ) import FastString +import Util ( sortLe ) \end{code} %************************************************************************ @@ -53,7 +54,7 @@ import FastString %************************************************************************ \begin{code} -deSugar :: HscEnv -> TcGblEnv -> IO (Maybe ModGuts) +deSugar :: HscEnv -> TcGblEnv -> IO (Bag WarnMsg, Maybe ModGuts) -- Can modify PCS by faulting in more declarations deSugar hsc_env @@ -63,6 +64,7 @@ deSugar hsc_env tcg_exports = exports, tcg_dus = dus, tcg_inst_uses = dfun_uses_var, + tcg_th_used = th_var, tcg_rdr_env = rdr_env, tcg_fix_env = fix_env, tcg_deprecs = deprecs, @@ -70,21 +72,16 @@ deSugar hsc_env = do { showPass dflags "Desugar" -- Do desugaring - ; let { is_boot = imp_dep_mods imports } - ; (results, warnings) <- initDs hsc_env mod type_env is_boot $ + ; (results, warnings) <- initDs hsc_env mod type_env $ dsProgram ghci_mode tcg_env ; let { (ds_binds, ds_rules, ds_fords) = results ; warns = mapBag mk_warn warnings - ; warn_doc = pprBagOfWarnings warns } - - -- Display any warnings - ; doIfSet (not (isEmptyBag warnings)) - (printErrs warn_doc) + } -- If warnings are considered errors, leave. ; if errorsFound dflags (warns, emptyBag) - then return Nothing + then return (warns, Nothing) else do -- Lint result if necessary @@ -95,18 +92,42 @@ deSugar hsc_env (printDump (ppr_ds_rules ds_rules)) ; dfun_uses <- readIORef dfun_uses_var -- What dfuns are used + ; th_used <- readIORef th_var ; let used_names = allUses dus `unionNameSets` dfun_uses - ; usages <- mkUsageInfo hsc_env imports used_names + pkgs | th_used = insertList thPackage (imp_dep_pkgs imports) + | otherwise = imp_dep_pkgs imports + + dep_mods = moduleEnvElts (delModuleEnv (imp_dep_mods imports) mod) + -- M.hi-boot can be in the imp_dep_mods, but we must remove + -- it before recording the modules on which this one depends! + -- (We want to retain M.hi-boot in imp_dep_mods so that + -- loadHiBootInterface can see if M's direct imports depend + -- on M.hi-boot, and hence that we should do the hi-boot consistency + -- check.) + + dir_imp_mods = imp_mods imports + + ; usages <- mkUsageInfo hsc_env dir_imp_mods dep_mods used_names + ; let - deps = Deps { dep_mods = moduleEnvElts (imp_dep_mods imports), - dep_pkgs = imp_dep_pkgs imports, - dep_orphs = imp_orphs imports } + -- ModuleNames don't compare lexicographically usually, + -- but we want them to do so here. + le_mod :: ModuleName -> ModuleName -> Bool + le_mod m1 m2 = moduleNameFS m1 <= moduleNameFS m2 + le_dep_mod :: (ModuleName, IsBootInterface) -> (ModuleName, IsBootInterface) -> Bool + le_dep_mod (m1,_) (m2,_) = m1 `le_mod` m2 + + deps = Deps { dep_mods = sortLe le_dep_mod dep_mods, + dep_pkgs = sortLe (<=) pkgs, + dep_orphs = sortLe le_mod (imp_orphs imports) } + -- sort to get into canonical order + mod_guts = ModGuts { mg_module = mod, mg_exports = exports, mg_deps = deps, mg_usages = usages, - mg_dir_imps = [m | (m,_) <- moduleEnvElts (imp_mods imports)], + mg_dir_imps = [m | (m,_,_) <- moduleEnvElts dir_imp_mods], mg_rdr_env = rdr_env, mg_fix_env = fix_env, mg_deprecs = deprecs, @@ -116,7 +137,7 @@ deSugar hsc_env mg_binds = ds_binds, mg_foreign = ds_fords } - ; return (Just mod_guts) + ; return (warns, Just mod_guts) }} where @@ -139,9 +160,7 @@ deSugarExpr hsc_env this_mod rdr_env type_env tc_expr ; us <- mkSplitUniqSupply 'd' -- Do desugaring - ; let { is_boot = emptyModuleEnv } -- Assume no hi-boot files when - -- doing stuff from the command line - ; (core_expr, ds_warns) <- initDs hsc_env this_mod type_env is_boot $ + ; (core_expr, ds_warns) <- initDs hsc_env this_mod type_env $ dsLExpr tc_expr -- Display any warnings @@ -234,9 +253,7 @@ addExportFlags ghci_mode exports keep_alive bndrs prs rules -- introduced by the type checker. is_exported :: Name -> Bool is_exported | ghci_mode == Interactive = isExternalName - | otherwise = (`elemNameSet` export_fvs) - - export_fvs = availsToNameSet exports + | otherwise = (`elemNameSet` exports) ppr_ds_rules [] = empty ppr_ds_rules rules @@ -261,7 +278,7 @@ dsRule in_scope (L loc (HsRule name act vars lhs rhs)) returnDs (fn, Rule name act tpl_vars args core_rhs) where tpl_vars = [var | RuleBndr (L _ var) <- vars] - all_vars = mkInScopeSet (in_scope `unionVarSet` mkVarSet tpl_vars) + all_vars = mkInScopeSet (extendVarSetList in_scope tpl_vars) ds_lhs all_vars lhs = let @@ -276,12 +293,10 @@ ds_lhs all_vars lhs -- Substitute the dict bindings eagerly, -- and take the body apart into a (f args) form let - subst_env = mkSubstEnv [id | (id,rhs) <- dict_binds'] - [ContEx subst_env rhs | (id,rhs) <- dict_binds'] + subst = extendIdSubstList (mkSubst all_vars) pairs + pairs = [(id, ContEx subst rhs) | (id,rhs) <- dict_binds'] -- Note recursion here... substitution won't terminate -- if there is genuine recursion... which there isn't - - subst = mkSubst all_vars subst_env body'' = substExpr subst body' in