2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
6 The Desugarer: turning HsSyn into Core.
9 module Desugar ( deSugar, deSugarExpr ) where
11 #include "HsVersions.h"
28 import DsExpr () -- Forces DsExpr to be compiled; DsBinds only
29 -- depends on DsExpr.hi-boot.
51 %************************************************************************
53 %* The main function: deSugar
55 %************************************************************************
58 deSugar :: HscEnv -> ModLocation -> TcGblEnv -> IO (Maybe ModGuts)
59 -- Can modify PCS by faulting in more declarations
63 tcg_env@(TcGblEnv { tcg_mod = mod,
65 tcg_type_env = type_env,
66 tcg_imports = imports,
67 tcg_exports = exports,
69 tcg_inst_uses = dfun_uses_var,
72 tcg_rdr_env = rdr_env,
73 tcg_fix_env = fix_env,
74 tcg_fam_inst_env = fam_inst_env,
75 tcg_deprecs = deprecs,
80 tcg_fam_insts = fam_insts })
82 = do { let dflags = hsc_dflags hsc_env
83 ; showPass dflags "Desugar"
85 -- Desugar the program
86 ; let export_set = availsToNameSet exports
87 ; let auto_scc = mkAutoScc mod export_set
88 ; let target = hscTarget dflags
89 ; mb_res <- case target of
90 HscNothing -> return (Just ([], [], NoStubs, noHpcInfo, emptyModBreaks))
91 _ -> do (binds_cvr,ds_hpc_info, modBreaks)
92 <- if opt_Hpc || target == HscInterpreted
93 then addCoverageTicksToBinds dflags mod mod_loc binds
94 else return (binds, noHpcInfo, emptyModBreaks)
95 initDs hsc_env mod rdr_env type_env $ do
96 { core_prs <- dsTopLHsBinds auto_scc binds_cvr
97 ; (ds_fords, foreign_prs) <- dsForeigns fords
98 ; let all_prs = foreign_prs ++ core_prs
99 local_bndrs = mkVarSet (map fst all_prs)
100 ; ds_rules <- mappM (dsRule mod local_bndrs) rules
101 ; return (all_prs, catMaybes ds_rules, ds_fords, ds_hpc_info, modBreaks)
104 Nothing -> return Nothing ;
105 Just (all_prs, ds_rules, ds_fords,ds_hpc_info, modBreaks) -> do
107 { -- Add export flags to bindings
108 keep_alive <- readIORef keep_var
109 ; let final_prs = addExportFlags target export_set
110 keep_alive all_prs ds_rules
111 ds_binds = [Rec final_prs]
112 -- Notice that we put the whole lot in a big Rec, even the foreign binds
113 -- When compiling PrelFloat, which defines data Float = F# Float#
114 -- we want F# to be in scope in the foreign marshalling code!
115 -- You might think it doesn't matter, but the simplifier brings all top-level
116 -- things into the in-scope set before simplifying; so we get no unfolding for F#!
118 -- Lint result if necessary
119 ; endPass dflags "Desugar" Opt_D_dump_ds ds_binds
122 ; doIfSet (dopt Opt_D_dump_ds dflags)
123 (printDump (ppr_ds_rules ds_rules))
125 ; dfun_uses <- readIORef dfun_uses_var -- What dfuns are used
126 ; th_used <- readIORef th_var -- Whether TH is used
127 ; let used_names = allUses dus `unionNameSets` dfun_uses
128 pkgs | th_used = insertList thPackageId (imp_dep_pkgs imports)
129 | otherwise = imp_dep_pkgs imports
131 dep_mods = eltsUFM (delFromUFM (imp_dep_mods imports) (moduleName mod))
132 -- M.hi-boot can be in the imp_dep_mods, but we must remove
133 -- it before recording the modules on which this one depends!
134 -- (We want to retain M.hi-boot in imp_dep_mods so that
135 -- loadHiBootInterface can see if M's direct imports depend
136 -- on M.hi-boot, and hence that we should do the hi-boot consistency
139 dir_imp_mods = imp_mods imports
141 ; usages <- mkUsageInfo hsc_env dir_imp_mods dep_mods used_names
144 -- Modules don't compare lexicographically usually,
145 -- but we want them to do so here.
146 le_mod :: Module -> Module -> Bool
147 le_mod m1 m2 = moduleNameFS (moduleName m1)
148 <= moduleNameFS (moduleName m2)
149 le_dep_mod :: (ModuleName, IsBootInterface) -> (ModuleName, IsBootInterface) -> Bool
150 le_dep_mod (m1,_) (m2,_) = moduleNameFS m1 <= moduleNameFS m2
152 deps = Deps { dep_mods = sortLe le_dep_mod dep_mods,
153 dep_pkgs = sortLe (<=) pkgs,
154 dep_orphs = sortLe le_mod (imp_orphs imports),
155 dep_finsts = sortLe le_mod (imp_finsts imports) }
156 -- sort to get into canonical order
160 mg_boot = isHsBoot hsc_src,
161 mg_exports = exports,
164 mg_dir_imps = [m | (m,_,_) <- moduleEnvElts dir_imp_mods],
165 mg_rdr_env = rdr_env,
166 mg_fix_env = fix_env,
167 mg_deprecs = deprecs,
170 mg_fam_insts = fam_insts,
171 mg_fam_inst_env = fam_inst_env,
174 mg_foreign = ds_fords,
175 mg_hpc_info = ds_hpc_info,
176 mg_modBreaks = modBreaks,
177 mg_vect_info = noVectInfo
179 ; return (Just mod_guts)
182 mkAutoScc :: Module -> NameSet -> AutoScc
183 mkAutoScc mod exports
184 | not opt_SccProfilingOn -- No profiling
186 | opt_AutoSccsOnAllToplevs -- Add auto-scc on all top-level things
187 = AddSccs mod (\id -> True)
188 | opt_AutoSccsOnExportedToplevs -- Only on exported things
189 = AddSccs mod (\id -> idName id `elemNameSet` exports)
194 deSugarExpr :: HscEnv
195 -> Module -> GlobalRdrEnv -> TypeEnv
197 -> IO (Maybe CoreExpr)
198 -- Prints its own errors; returns Nothing if error occurred
200 deSugarExpr hsc_env this_mod rdr_env type_env tc_expr
201 = do { let dflags = hsc_dflags hsc_env
202 ; showPass dflags "Desugar"
205 ; mb_core_expr <- initDs hsc_env this_mod rdr_env type_env $
208 ; case mb_core_expr of {
209 Nothing -> return Nothing ;
213 dumpIfSet_dyn dflags Opt_D_dump_ds "Desugared" (pprCoreExpr expr)
215 ; return (Just expr) } } }
218 -- Set the no-discard flag if either
219 -- a) the Id is exported
220 -- b) it's mentioned in the RHS of an orphan rule
221 -- c) it's in the keep-alive set
223 -- It means that the binding won't be discarded EVEN if the binding
224 -- ends up being trivial (v = w) -- the simplifier would usually just
225 -- substitute w for v throughout, but we don't apply the substitution to
226 -- the rules (maybe we should?), so this substitution would make the rule
229 -- You might wonder why exported Ids aren't already marked as such;
230 -- it's just because the type checker is rather busy already and
231 -- I didn't want to pass in yet another mapping.
233 addExportFlags target exports keep_alive prs rules
234 = [(add_export bndr, rhs) | (bndr,rhs) <- prs]
237 | dont_discard bndr = setIdExported bndr
240 orph_rhs_fvs = unionVarSets [ ruleRhsFreeVars rule
242 not (isLocalRule rule) ]
243 -- A non-local rule keeps alive the free vars of its right-hand side.
244 -- (A "non-local" is one whose head function is not locally defined.)
245 -- Local rules are (later, after gentle simplification)
246 -- attached to the Id, and that keeps the rhs free vars alive.
248 dont_discard bndr = is_exported name
249 || name `elemNameSet` keep_alive
250 || bndr `elemVarSet` orph_rhs_fvs
254 -- In interactive mode, we don't want to discard any top-level
255 -- entities at all (eg. do not inline them away during
256 -- simplification), and retain them all in the TypeEnv so they are
257 -- available from the command line.
259 -- isExternalName separates the user-defined top-level names from those
260 -- introduced by the type checker.
261 is_exported :: Name -> Bool
262 is_exported | target == HscInterpreted = isExternalName
263 | otherwise = (`elemNameSet` exports)
265 ppr_ds_rules [] = empty
267 = text "" $$ text "-------------- DESUGARED RULES -----------------" $$
273 %************************************************************************
275 %* Desugaring transformation rules
277 %************************************************************************
280 dsRule :: Module -> IdSet -> LRuleDecl Id -> DsM (Maybe CoreRule)
281 dsRule mod in_scope (L loc (HsRule name act vars lhs tv_lhs rhs fv_rhs))
283 do { let bndrs = [var | RuleBndr (L _ var) <- vars]
284 ; lhs' <- dsLExpr lhs
285 ; rhs' <- dsLExpr rhs
287 ; case decomposeRuleLhs (occurAnalyseExpr lhs') of {
288 Nothing -> do { warnDs msg; return Nothing } ;
289 Just (fn_id, args) -> do
291 -- Substitute the dict bindings eagerly,
292 -- and take the body apart into a (f args) form
293 { let local_rule = isLocalId fn_id
294 -- NB: isLocalId is False of implicit Ids. This is good becuase
295 -- we don't want to attach rules to the bindings of implicit Ids,
296 -- because they don't show up in the bindings until just before code gen
297 fn_name = idName fn_id
299 rule = Rule { ru_name = name, ru_fn = fn_name, ru_act = act,
300 ru_bndrs = bndrs, ru_args = args, ru_rhs = rhs',
301 ru_rough = roughTopNames args,
302 ru_local = local_rule }
306 msg = hang (ptext SLIT("RULE left-hand side too complicated to desugar; ignored"))