Rationalise GhcMode, HscTarget and GhcLink
[ghc-hetmet.git] / compiler / deSugar / Desugar.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5
6 The Desugarer: turning HsSyn into Core.
7
8 \begin{code}
9 module Desugar ( deSugar, deSugarExpr ) where
10
11 #include "HsVersions.h"
12
13 import DynFlags
14 import StaticFlags
15 import HscTypes
16 import HsSyn
17 import TcRnTypes
18 import MkIface
19 import Id
20 import Name
21 import CoreSyn
22 import PprCore
23 import DsMonad
24 import DsExpr
25 import DsBinds
26 import DsForeign
27 import DsExpr           ()      -- Forces DsExpr to be compiled; DsBinds only
28                                 -- depends on DsExpr.hi-boot.
29 import Module
30 import UniqFM
31 import PackageConfig
32 import RdrName
33 import NameSet
34 import VarSet
35 import Rules
36 import CoreLint
37 import CoreFVs
38 import ErrUtils
39 import ListSetOps
40 import Outputable
41 import SrcLoc
42 import Maybes
43 import FastString
44 import Util
45 import Coverage
46 import IOEnv
47 import Data.IORef
48
49 \end{code}
50
51 %************************************************************************
52 %*                                                                      *
53 %*              The main function: deSugar
54 %*                                                                      *
55 %************************************************************************
56
57 \begin{code}
58 deSugar :: HscEnv -> ModLocation -> TcGblEnv -> IO (Maybe ModGuts)
59 -- Can modify PCS by faulting in more declarations
60
61 deSugar hsc_env 
62         mod_loc
63         tcg_env@(TcGblEnv { tcg_mod          = mod,
64                             tcg_src          = hsc_src,
65                             tcg_type_env     = type_env,
66                             tcg_imports      = imports,
67                             tcg_exports      = exports,
68                             tcg_dus          = dus, 
69                             tcg_inst_uses    = dfun_uses_var,
70                             tcg_th_used      = th_var,
71                             tcg_keep         = keep_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,
76                             tcg_binds        = binds,
77                             tcg_fords        = fords,
78                             tcg_rules        = rules,
79                             tcg_insts        = insts,
80                             tcg_fam_insts    = fam_insts })
81
82   = do  { let dflags = hsc_dflags hsc_env
83         ; showPass dflags "Desugar"
84
85         -- Desugar the program
86         ; let export_set = availsToNameSet exports
87         ; let auto_scc = mkAutoScc mod export_set
88         ; let noDbgSites = []
89         ; let target = hscTarget dflags
90         ; mb_res <- case target of
91                      HscNothing -> return (Just ([], [], NoStubs, noHpcInfo, noDbgSites))
92                      _        -> do (binds_cvr,ds_hpc_info) 
93                                               <- if opt_Hpc
94                                                  then addCoverageTicksToBinds dflags mod mod_loc binds
95                                                  else return (binds, noHpcInfo)
96                                     initDs hsc_env mod rdr_env type_env $ do
97                                         { core_prs <- dsTopLHsBinds auto_scc binds_cvr
98                                         ; (ds_fords, foreign_prs) <- dsForeigns fords
99                                         ; let all_prs = foreign_prs ++ core_prs
100                                               local_bndrs = mkVarSet (map fst all_prs)
101                                         ; ds_rules <- mappM (dsRule mod local_bndrs) rules
102                                         ; return (all_prs, catMaybes ds_rules, ds_fords, ds_hpc_info)
103                                         ; dbgSites_var <- getBkptSitesDs
104                                         ; dbgSites <- ioToIOEnv$ readIORef dbgSites_var
105                                         ; return (all_prs, catMaybes ds_rules, ds_fords, ds_hpc_info, dbgSites)
106                                         }
107         ; case mb_res of {
108            Nothing -> return Nothing ;
109            Just (all_prs, ds_rules, ds_fords,ds_hpc_info, dbgSites) -> do
110
111         {       -- Add export flags to bindings
112           keep_alive <- readIORef keep_var
113         ; let final_prs = addExportFlags target export_set
114                                  keep_alive all_prs ds_rules
115               ds_binds  = [Rec final_prs]
116         -- Notice that we put the whole lot in a big Rec, even the foreign binds
117         -- When compiling PrelFloat, which defines data Float = F# Float#
118         -- we want F# to be in scope in the foreign marshalling code!
119         -- You might think it doesn't matter, but the simplifier brings all top-level
120         -- things into the in-scope set before simplifying; so we get no unfolding for F#!
121
122         -- Lint result if necessary
123         ; endPass dflags "Desugar" Opt_D_dump_ds ds_binds
124
125         -- Dump output
126         ; doIfSet (dopt Opt_D_dump_ds dflags) 
127                   (printDump (ppr_ds_rules ds_rules))
128
129         ; dfun_uses <- readIORef dfun_uses_var          -- What dfuns are used
130         ; th_used   <- readIORef th_var                 -- Whether TH is used
131         ; let used_names = allUses dus `unionNameSets` dfun_uses
132               pkgs | th_used   = insertList thPackageId (imp_dep_pkgs imports)
133                    | otherwise = imp_dep_pkgs imports
134
135               dep_mods = eltsUFM (delFromUFM (imp_dep_mods imports) (moduleName mod))
136                 -- M.hi-boot can be in the imp_dep_mods, but we must remove
137                 -- it before recording the modules on which this one depends!
138                 -- (We want to retain M.hi-boot in imp_dep_mods so that 
139                 --  loadHiBootInterface can see if M's direct imports depend 
140                 --  on M.hi-boot, and hence that we should do the hi-boot consistency 
141                 --  check.)
142
143               dir_imp_mods = imp_mods imports
144
145         ; usages <- mkUsageInfo hsc_env dir_imp_mods dep_mods used_names
146
147         ; let 
148                 -- Modules don't compare lexicographically usually, 
149                 -- but we want them to do so here.
150              le_mod :: Module -> Module -> Bool  
151              le_mod m1 m2 = moduleNameFS (moduleName m1) 
152                                 <= moduleNameFS (moduleName m2)
153              le_dep_mod :: (ModuleName, IsBootInterface) -> (ModuleName, IsBootInterface) -> Bool        
154              le_dep_mod (m1,_) (m2,_) = moduleNameFS m1 <= moduleNameFS m2
155
156              deps = Deps { dep_mods   = sortLe le_dep_mod dep_mods,
157                            dep_pkgs   = sortLe (<=)   pkgs,     
158                            dep_orphs  = sortLe le_mod (imp_orphs  imports),
159                            dep_finsts = sortLe le_mod (imp_finsts imports) }
160                 -- sort to get into canonical order
161
162              mod_guts = ModGuts {       
163                 mg_module       = mod,
164                 mg_boot         = isHsBoot hsc_src,
165                 mg_exports      = exports,
166                 mg_deps         = deps,
167                 mg_usages       = usages,
168                 mg_dir_imps     = [m | (m,_,_) <- moduleEnvElts dir_imp_mods],
169                 mg_rdr_env      = rdr_env,
170                 mg_fix_env      = fix_env,
171                 mg_deprecs      = deprecs,
172                 mg_types        = type_env,
173                 mg_insts        = insts,
174                 mg_fam_insts    = fam_insts,
175                 mg_fam_inst_env = fam_inst_env,
176                 mg_rules        = ds_rules,
177                 mg_binds        = ds_binds,
178                 mg_foreign      = ds_fords,
179                 mg_hpc_info     = ds_hpc_info,
180                 mg_dbg_sites    = dbgSites }
181         ; return (Just mod_guts)
182         }}}
183
184 mkAutoScc :: Module -> NameSet -> AutoScc
185 mkAutoScc mod exports
186   | not opt_SccProfilingOn      -- No profiling
187   = NoSccs              
188   | opt_AutoSccsOnAllToplevs    -- Add auto-scc on all top-level things
189   = AddSccs mod (\id -> True)
190   | opt_AutoSccsOnExportedToplevs       -- Only on exported things
191   = AddSccs mod (\id -> idName id `elemNameSet` exports)
192   | otherwise
193   = NoSccs
194
195
196 deSugarExpr :: HscEnv
197             -> Module -> GlobalRdrEnv -> TypeEnv 
198             -> LHsExpr Id
199             -> IO (Maybe CoreExpr)
200 -- Prints its own errors; returns Nothing if error occurred
201
202 deSugarExpr hsc_env this_mod rdr_env type_env tc_expr
203   = do  { let dflags = hsc_dflags hsc_env
204         ; showPass dflags "Desugar"
205
206         -- Do desugaring
207         ; mb_core_expr <- initDs hsc_env this_mod rdr_env type_env $
208                           dsLExpr tc_expr
209
210         ; case mb_core_expr of {
211             Nothing   -> return Nothing ;
212             Just expr -> do {
213
214                 -- Dump output
215           dumpIfSet_dyn dflags Opt_D_dump_ds "Desugared" (pprCoreExpr expr)
216
217         ; return (Just expr) } } }
218
219 --              addExportFlags
220 -- Set the no-discard flag if either 
221 --      a) the Id is exported
222 --      b) it's mentioned in the RHS of an orphan rule
223 --      c) it's in the keep-alive set
224 --
225 -- It means that the binding won't be discarded EVEN if the binding
226 -- ends up being trivial (v = w) -- the simplifier would usually just 
227 -- substitute w for v throughout, but we don't apply the substitution to
228 -- the rules (maybe we should?), so this substitution would make the rule
229 -- bogus.
230
231 -- You might wonder why exported Ids aren't already marked as such;
232 -- it's just because the type checker is rather busy already and
233 -- I didn't want to pass in yet another mapping.
234
235 addExportFlags target exports keep_alive prs rules
236   = [(add_export bndr, rhs) | (bndr,rhs) <- prs]
237   where
238     add_export bndr
239         | dont_discard bndr = setIdExported bndr
240         | otherwise         = bndr
241
242     orph_rhs_fvs = unionVarSets [ ruleRhsFreeVars rule
243                                 | rule <- rules, 
244                                   not (isLocalRule rule) ]
245         -- A non-local rule keeps alive the free vars of its right-hand side. 
246         -- (A "non-local" is one whose head function is not locally defined.)
247         -- Local rules are (later, after gentle simplification) 
248         -- attached to the Id, and that keeps the rhs free vars alive.
249
250     dont_discard bndr = is_exported name
251                      || name `elemNameSet` keep_alive
252                      || bndr `elemVarSet` orph_rhs_fvs 
253                      where
254                         name = idName bndr
255
256         -- In interactive mode, we don't want to discard any top-level
257         -- entities at all (eg. do not inline them away during
258         -- simplification), and retain them all in the TypeEnv so they are
259         -- available from the command line.
260         --
261         -- isExternalName separates the user-defined top-level names from those
262         -- introduced by the type checker.
263     is_exported :: Name -> Bool
264     is_exported | target == HscInterpreted = isExternalName
265                 | otherwise                = (`elemNameSet` exports)
266
267 ppr_ds_rules [] = empty
268 ppr_ds_rules rules
269   = text "" $$ text "-------------- DESUGARED RULES -----------------" $$
270     pprRules rules
271 \end{code}
272
273
274
275 %************************************************************************
276 %*                                                                      *
277 %*              Desugaring transformation rules
278 %*                                                                      *
279 %************************************************************************
280
281 \begin{code}
282 dsRule :: Module -> IdSet -> LRuleDecl Id -> DsM (Maybe CoreRule)
283 dsRule mod in_scope (L loc (HsRule name act vars lhs tv_lhs rhs fv_rhs))
284   = putSrcSpanDs loc $ 
285     do  { let bndrs     = [var | RuleBndr (L _ var) <- vars]
286         ; lhs'  <- dsLExpr lhs
287         ; rhs'  <- dsLExpr rhs
288
289         ; case decomposeRuleLhs bndrs lhs' of {
290                 Nothing -> do { warnDs msg; return Nothing } ;
291                 Just (bndrs', fn_id, args) -> do
292         
293         -- Substitute the dict bindings eagerly,
294         -- and take the body apart into a (f args) form
295         { let local_rule = isLocalId fn_id
296                 -- NB: isLocalId is False of implicit Ids.  This is good becuase
297                 -- we don't want to attach rules to the bindings of implicit Ids, 
298                 -- because they don't show up in the bindings until just before code gen
299               fn_name   = idName fn_id
300
301               rule = Rule { ru_name = name, ru_fn = fn_name, ru_act = act,
302                             ru_bndrs = bndrs', ru_args = args, ru_rhs = rhs', 
303                             ru_rough = roughTopNames args, 
304                             ru_local = local_rule }
305         ; return (Just rule)
306         } } }
307   where
308     msg = hang (ptext SLIT("RULE left-hand side too complicated to desugar; ignored"))
309              2 (ppr lhs)
310 \end{code}