Deal more correctly with orphan instances
[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   = do  { showPass dflags "Desugar"
82
83         -- Desugar the program
84         ; let export_set = availsToNameSet exports
85         ; let auto_scc = mkAutoScc mod export_set
86         ; let noDbgSites = []
87         ; mb_res <- case ghcMode dflags of
88                      JustTypecheck -> return (Just ([], [], NoStubs, noHpcInfo, noDbgSites))
89                      _        -> do (binds_cvr,ds_hpc_info) 
90                                               <- if opt_Hpc
91                                                  then addCoverageTicksToBinds dflags mod mod_loc binds
92                                                  else return (binds, noHpcInfo)
93                                     initDs hsc_env mod rdr_env type_env $ do
94                                         { core_prs <- dsTopLHsBinds auto_scc binds_cvr
95                                         ; (ds_fords, foreign_prs) <- dsForeigns fords
96                                         ; let all_prs = foreign_prs ++ core_prs
97                                               local_bndrs = mkVarSet (map fst all_prs)
98                                         ; ds_rules <- mappM (dsRule mod local_bndrs) rules
99                                         ; return (all_prs, catMaybes ds_rules, ds_fords, ds_hpc_info)
100                                         ; dbgSites_var <- getBkptSitesDs
101                                         ; dbgSites <- ioToIOEnv$ readIORef dbgSites_var
102                                         ; return (all_prs, catMaybes ds_rules, ds_fords, ds_hpc_info, dbgSites)
103                                         }
104         ; case mb_res of {
105            Nothing -> return Nothing ;
106            Just (all_prs, ds_rules, ds_fords,ds_hpc_info, dbgSites) -> do
107
108         {       -- Add export flags to bindings
109           keep_alive <- readIORef keep_var
110         ; let final_prs = addExportFlags ghci_mode export_set
111                                  keep_alive all_prs ds_rules
112               ds_binds  = [Rec final_prs]
113         -- Notice that we put the whole lot in a big Rec, even the foreign binds
114         -- When compiling PrelFloat, which defines data Float = F# Float#
115         -- we want F# to be in scope in the foreign marshalling code!
116         -- You might think it doesn't matter, but the simplifier brings all top-level
117         -- things into the in-scope set before simplifying; so we get no unfolding for F#!
118
119         -- Lint result if necessary
120         ; endPass dflags "Desugar" Opt_D_dump_ds ds_binds
121
122         -- Dump output
123         ; doIfSet (dopt Opt_D_dump_ds dflags) 
124                   (printDump (ppr_ds_rules ds_rules))
125
126         ; dfun_uses <- readIORef dfun_uses_var          -- What dfuns are used
127         ; th_used   <- readIORef th_var                 -- Whether TH is used
128         ; let used_names = allUses dus `unionNameSets` dfun_uses
129               pkgs | th_used   = insertList thPackageId (imp_dep_pkgs imports)
130                    | otherwise = imp_dep_pkgs imports
131
132               dep_mods = eltsUFM (delFromUFM (imp_dep_mods imports) (moduleName mod))
133                 -- M.hi-boot can be in the imp_dep_mods, but we must remove
134                 -- it before recording the modules on which this one depends!
135                 -- (We want to retain M.hi-boot in imp_dep_mods so that 
136                 --  loadHiBootInterface can see if M's direct imports depend 
137                 --  on M.hi-boot, and hence that we should do the hi-boot consistency 
138                 --  check.)
139
140               dir_imp_mods = imp_mods imports
141
142         ; usages <- mkUsageInfo hsc_env dir_imp_mods dep_mods used_names
143
144         ; let 
145                 -- Modules don't compare lexicographically usually, 
146                 -- but we want them to do so here.
147              le_mod :: Module -> Module -> Bool  
148              le_mod m1 m2 = moduleNameFS (moduleName m1) 
149                                 <= moduleNameFS (moduleName m2)
150              le_dep_mod :: (ModuleName, IsBootInterface) -> (ModuleName, IsBootInterface) -> Bool        
151              le_dep_mod (m1,_) (m2,_) = moduleNameFS m1 <= moduleNameFS m2
152
153              deps = Deps { dep_mods   = sortLe le_dep_mod dep_mods,
154                            dep_pkgs   = sortLe (<=)   pkgs,     
155                            dep_orphs  = sortLe le_mod (imp_orphs  imports),
156                            dep_finsts = sortLe le_mod (imp_finsts imports) }
157                 -- sort to get into canonical order
158
159              mod_guts = ModGuts {       
160                 mg_module       = mod,
161                 mg_boot         = isHsBoot hsc_src,
162                 mg_exports      = exports,
163                 mg_deps         = deps,
164                 mg_usages       = usages,
165                 mg_dir_imps     = [m | (m,_,_) <- moduleEnvElts dir_imp_mods],
166                 mg_rdr_env      = rdr_env,
167                 mg_fix_env      = fix_env,
168                 mg_deprecs      = deprecs,
169                 mg_types        = type_env,
170                 mg_insts        = insts,
171                 mg_fam_insts    = fam_insts,
172                 mg_fam_inst_env = fam_inst_env,
173                 mg_rules        = ds_rules,
174                 mg_binds        = ds_binds,
175                 mg_foreign      = ds_fords,
176                 mg_hpc_info     = ds_hpc_info,
177                 mg_dbg_sites    = dbgSites }
178         ; return (Just mod_guts)
179         }}}
180
181   where
182     dflags    = hsc_dflags hsc_env
183     ghci_mode = ghcMode (hsc_dflags hsc_env)
184
185 mkAutoScc :: Module -> NameSet -> AutoScc
186 mkAutoScc mod exports
187   | not opt_SccProfilingOn      -- No profiling
188   = NoSccs              
189   | opt_AutoSccsOnAllToplevs    -- Add auto-scc on all top-level things
190   = AddSccs mod (\id -> True)
191   | opt_AutoSccsOnExportedToplevs       -- Only on exported things
192   = AddSccs mod (\id -> idName id `elemNameSet` exports)
193   | otherwise
194   = NoSccs
195
196
197 deSugarExpr :: HscEnv
198             -> Module -> GlobalRdrEnv -> TypeEnv 
199             -> LHsExpr Id
200             -> IO (Maybe CoreExpr)
201 -- Prints its own errors; returns Nothing if error occurred
202
203 deSugarExpr hsc_env this_mod rdr_env type_env tc_expr
204   = do  { let dflags = hsc_dflags hsc_env
205         ; showPass dflags "Desugar"
206
207         -- Do desugaring
208         ; mb_core_expr <- initDs hsc_env this_mod rdr_env type_env $
209                           dsLExpr tc_expr
210
211         ; case mb_core_expr of {
212             Nothing   -> return Nothing ;
213             Just expr -> do {
214
215                 -- Dump output
216           dumpIfSet_dyn dflags Opt_D_dump_ds "Desugared" (pprCoreExpr expr)
217
218         ; return (Just expr) } } }
219
220 --              addExportFlags
221 -- Set the no-discard flag if either 
222 --      a) the Id is exported
223 --      b) it's mentioned in the RHS of an orphan rule
224 --      c) it's in the keep-alive set
225 --
226 -- It means that the binding won't be discarded EVEN if the binding
227 -- ends up being trivial (v = w) -- the simplifier would usually just 
228 -- substitute w for v throughout, but we don't apply the substitution to
229 -- the rules (maybe we should?), so this substitution would make the rule
230 -- bogus.
231
232 -- You might wonder why exported Ids aren't already marked as such;
233 -- it's just because the type checker is rather busy already and
234 -- I didn't want to pass in yet another mapping.
235
236 addExportFlags ghci_mode exports keep_alive prs rules
237   = [(add_export bndr, rhs) | (bndr,rhs) <- prs]
238   where
239     add_export bndr
240         | dont_discard bndr = setIdExported bndr
241         | otherwise         = bndr
242
243     orph_rhs_fvs = unionVarSets [ ruleRhsFreeVars rule
244                                 | rule <- rules, 
245                                   not (isLocalRule rule) ]
246         -- A non-local rule keeps alive the free vars of its right-hand side. 
247         -- (A "non-local" is one whose head function is not locally defined.)
248         -- Local rules are (later, after gentle simplification) 
249         -- attached to the Id, and that keeps the rhs free vars alive.
250
251     dont_discard bndr = is_exported name
252                      || name `elemNameSet` keep_alive
253                      || bndr `elemVarSet` orph_rhs_fvs 
254                      where
255                         name = idName bndr
256
257         -- In interactive mode, we don't want to discard any top-level
258         -- entities at all (eg. do not inline them away during
259         -- simplification), and retain them all in the TypeEnv so they are
260         -- available from the command line.
261         --
262         -- isExternalName separates the user-defined top-level names from those
263         -- introduced by the type checker.
264     is_exported :: Name -> Bool
265     is_exported | ghci_mode == Interactive = isExternalName
266                 | otherwise                = (`elemNameSet` exports)
267
268 ppr_ds_rules [] = empty
269 ppr_ds_rules rules
270   = text "" $$ text "-------------- DESUGARED RULES -----------------" $$
271     pprRules rules
272 \end{code}
273
274
275
276 %************************************************************************
277 %*                                                                      *
278 %*              Desugaring transformation rules
279 %*                                                                      *
280 %************************************************************************
281
282 \begin{code}
283 dsRule :: Module -> IdSet -> LRuleDecl Id -> DsM (Maybe CoreRule)
284 dsRule mod in_scope (L loc (HsRule name act vars lhs tv_lhs rhs fv_rhs))
285   = putSrcSpanDs loc $ 
286     do  { let bndrs     = [var | RuleBndr (L _ var) <- vars]
287         ; lhs'  <- dsLExpr lhs
288         ; rhs'  <- dsLExpr rhs
289
290         ; case decomposeRuleLhs bndrs lhs' of {
291                 Nothing -> do { warnDs msg; return Nothing } ;
292                 Just (bndrs', fn_id, args) -> do
293         
294         -- Substitute the dict bindings eagerly,
295         -- and take the body apart into a (f args) form
296         { let local_rule = nameIsLocalOrFrom mod fn_name
297                 -- NB we can't use isLocalId in the orphan test, 
298                 -- because isLocalId isn't true of class methods
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}