[project @ 2000-10-26 07:19:52 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / HscMain.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-2000
3 %
4 \section[GHC_Main]{Main driver for Glasgow Haskell compiler}
5
6 \begin{code}
7 module HscMain ( hscMain ) where
8
9 #include "HsVersions.h"
10
11 import Monad            ( when )
12 import IO               ( hPutStr, hClose, stderr, openFile, IOMode(..) )
13 import HsSyn
14
15 import RdrHsSyn         ( RdrNameHsModule )
16 import FastString       ( unpackFS )
17 import StringBuffer     ( hGetStringBuffer )
18 import Parser           ( parse )
19 import Lex              ( PState(..), ParseResult(..) )
20 import SrcLoc           ( mkSrcLoc )
21
22 import Rename           ( renameModule, checkOldIface )
23
24 import PrelInfo         ( wiredInThings )
25 import PrelRules        ( builtinRules )
26 import MkIface          ( completeIface, mkModDetailsFromIface )
27 import TcModule         ( TcResults(..), typecheckModule )
28 import Desugar          ( deSugar )
29 import SimplCore        ( core2core )
30 import OccurAnal        ( occurAnalyseBinds )
31 import CoreUtils        ( coreBindsSize )
32 import CoreTidy         ( tidyCorePgm )
33 import CoreToStg        ( topCoreBindsToStg )
34 import StgSyn           ( collectFinalStgBinders )
35 import SimplStg         ( stg2stg )
36 import CodeGen          ( codeGen )
37 import CodeOutput       ( codeOutput )
38
39 import Module           ( ModuleName, moduleNameUserString, 
40                           moduleUserString, moduleName )
41 import CmdLineOpts
42 import ErrUtils         ( ghcExit, doIfSet, dumpIfSet )
43 import UniqSupply       ( mkSplitUniqSupply )
44
45 import Bag              ( emptyBag )
46 import Outputable
47 import Char             ( isSpace )
48 import StgInterp        ( stgToInterpSyn )
49 import HscStats         ( ppSourceStats )
50 import HscTypes         ( ModDetails, ModIface, PersistentCompilerState(..),
51                           PersistentRenamerState(..), WhatsImported(..),
52                           HomeSymbolTable, PackageSymbolTable, ImportVersion, 
53                           GenAvailInfo(..), RdrAvailInfo, OrigNameEnv(..),
54                           PackageRuleBase )
55 import RnMonad          ( ExportItem, ParsedIface(..) )
56 import CmSummarise      ( ModSummary )
57 import InterpSyn        ( UnlinkedIBind )
58 import StgInterp        ( ItblEnv )
59 import FiniteMap        ( FiniteMap, plusFM, emptyFM, addToFM )
60 import OccName          ( OccName, pprOccName )
61 import Name             ( Name, nameModule )
62 \end{code}
63
64
65 %************************************************************************
66 %*                                                                      *
67 \subsection{The main compiler pipeline}
68 %*                                                                      *
69 %************************************************************************
70
71 \begin{code}
72 data HscResult
73    = HscOK   ModDetails              -- new details (HomeSymbolTable additions)
74              (Maybe ModIface)        -- new iface (if any compilation was done)
75              (Maybe String)          -- generated stub_h filename (in /tmp)
76              (Maybe String)          -- generated stub_c filename (in /tmp)
77              (Maybe ([UnlinkedIBind],ItblEnv)) -- interpreted code, if any
78              PersistentCompilerState -- updated PCS
79
80    | HscFail PersistentCompilerState -- updated PCS
81         -- no errors or warnings; the individual passes
82         -- (parse/rename/typecheck) print messages themselves
83
84 hscMain
85   :: DynFlags   
86   -> ModSummary       -- summary, including source filename
87   -> Maybe ModIface   -- old interface, if available
88   -> String           -- file in which to put the output (.s, .hc, .java etc.)
89   -> HomeSymbolTable            -- for home module ModDetails
90   -> PersistentCompilerState    -- IN: persistent compiler state
91   -> IO HscResult
92
93 hscMain dflags core_cmds stg_cmds summary maybe_old_iface
94         output_filename mod_details pcs
95  = do {
96       -- ????? source_unchanged :: Bool -- extracted from summary?
97
98       (ch_pcs, check_errs, (recomp_reqd, maybe_checked_iface))
99          <- checkOldIface dflags finder hit hst pcs mod source_unchanged
100                           maybe_old_iface;
101       if check_errs then
102          return (HscFail ch_pcs)
103       else do {
104
105       let no_old_iface = not (isJust maybe_checked_iface)
106           what_next | recomp_reqd || no_old_iface = hscRecomp 
107                     | otherwise                   = hscNoRecomp
108       ;
109       return (what_next dflags finder core_cmds stg_cmds summary hit hst 
110                         pcs2 maybe_checked_iface)
111       }}
112
113
114 hscNoRecomp dflags finder core_cmds stg_cmds summary hit hst pcs maybe_old_iface
115  = do {
116       -- we definitely expect to have the old interface available
117       let old_iface = case maybe_old_iface of 
118                          Just old_if -> old_if
119                          Nothing -> panic "hscNoRecomp:old_iface"
120       ;
121       -- CLOSURE
122       (pcs_cl, closure_errs, cl_hs_decls) 
123          <- closeIfaceDecls dflags finder hit hst pcs old_iface ;
124       if closure_errs then 
125          return (HscFail cl_pcs) 
126       else do {
127
128       -- TYPECHECK
129       maybe_tc_result
130          <- typecheckModule dflags mod pcs_cl hst hit pit cl_hs_decls;
131       case maybe_tc_result of {
132          Nothing -> return (HscFail cl_pcs);
133          Just tc_result -> do {
134
135       let pcs_tc        = tc_pcs tc_result
136           env_tc        = tc_env tc_result
137           binds_tc      = tc_binds tc_result
138           local_insts   = tc_insts tc_result
139           local_rules   = tc_rules tc_result
140       ;
141       -- create a new details from the closed, typechecked, old iface
142       let new_details = mkModDetailsFromIface env_tc local_insts local_rules
143       ;
144       return (HscOK final_details
145                     Nothing -- tells CM to use old iface and linkables
146                     Nothing Nothing -- foreign export stuff
147                     Nothing -- ibinds
148                     pcs_tc)
149       }}}}
150
151
152 hscRecomp dflags finder core_cmds stg_cmds summary hit hst pcs maybe_old_iface
153  = do {
154       -- what target are we shooting for?
155       let toInterp = dopt_HscLang dflags == HscInterpreted
156       ;
157       -- PARSE
158       maybe_parsed <- myParseModule dflags summary;
159       case maybe_parsed of {
160          Nothing -> return (HscFail pcs);
161          Just rdr_module -> do {
162
163       -- RENAME
164       (pcs_rn, maybe_rn_result) 
165          <- renameModule dflags finder hit hst pcs mod rdr_module;
166       case maybe_rn_result of {
167          Nothing -> return (HscFail pcs_rn);
168          Just (new_iface, rn_hs_decls) -> do {
169
170       -- TYPECHECK
171       maybe_tc_result
172          <- typecheckModule dflags mod pcs_rn hst hit pit rn_hs_decls;
173       case maybe_tc_result of {
174          Nothing -> return (HscFail pcs_rn);
175          Just tc_result -> do {
176
177       let pcs_tc        = tc_pcs tc_result
178           env_tc        = tc_env tc_result
179           binds_tc      = tc_binds tc_result
180           local_insts   = tc_insts tc_result
181       ;
182       -- DESUGAR, SIMPLIFY, TIDY-CORE
183       -- We grab the the unfoldings at this point.
184       (tidy_binds, orphan_rules, foreign_stuff)
185          <- dsThenSimplThenTidy dflags mod tc_result ds_uniqs
186       ;
187       -- CONVERT TO STG
188       (stg_binds, cost_centre_info, top_level_ids) 
189          <- myCoreToStg finder c2s_uniqs st_uniqs this_mod tidy_binds
190       ;
191       -- cook up a new ModDetails now we (finally) have all the bits
192       let new_details = mkModDetails tc_env local_insts tidy_binds 
193                                      top_level_ids orphan_rules
194       ;
195       -- and possibly create a new ModIface
196       let maybe_final_iface = completeIface maybe_old_iface new_iface new_details 
197       ;
198
199       -- Write the interface file
200       writeIface finder maybe_final_iface
201       ;
202
203       -- do the rest of code generation/emission
204       (maybe_ibinds, maybe_stub_h_filename, maybe_stub_c_filename) 
205          <- restOfCodeGeneration toInterp
206                                  this_mod imported_modules cost_centre_info 
207                                  fe_binders tc_env stg_binds
208       ;
209       -- and the answer is ...
210       return (HscOK new_details maybe_final_iface 
211                     maybe_stub_h_filename maybe_stub_c_filename
212                     maybe_ibinds pcs_tc)
213       }}}}}}}
214
215
216 myParseModule dflags summary
217  = do --------------------------  Reader  ----------------
218       show_pass "Parser"
219       -- _scc_     "Parser"
220
221       let src_filename -- name of the preprocessed source file
222             = case ms_ppsource summary of
223                  Just (filename, fingerprint) -> filename
224                  Nothing -> pprPanic 
225                                "myParseModule:summary is not of a source module"
226                                (ppr summary)
227
228       buf <- hGetStringBuffer True{-expand tabs-} src_filename
229
230       let glaexts | dopt Opt_GlasgowExts dflags = 1#
231                   | otherwise                 = 0#
232
233       case parse buf PState{ bol = 0#, atbol = 1#,
234                              context = [], glasgow_exts = glaexts,
235                              loc = mkSrcLoc src_filename 1 } of {
236
237         PFailed err -> do { hPutStrLn stderr (showSDoc err);
238                             return Nothing };
239         POk _ rdr_module@(HsModule mod_name _ _ _ _ _ _) ->
240
241       dumpIfSet_dyn dflags Opt_D_dump_parsed "Parser" (ppr rdr_module)
242       dumpIfSet_dyn dflags Opt_D_source_stats "Source Statistics"
243                            (ppSourceStats False rdr_module)
244
245       return (Just rdr_module)
246       }
247
248
249 restOfCodeGeneration toInterp this_mod imported_modules cost_centre_info 
250                      foreign_stuff tc_env stg_binds
251  | toInterp
252  = return (Nothing, Nothing, 
253            Just (stgToInterpSyn stg_binds local_tycons local_classes))
254  | otherwise
255  = do --------------------------  Code generation -------------------------------
256       show_pass "CodeGen"
257       -- _scc_     "CodeGen"
258       abstractC <- codeGen this_mod imported_modules
259                            cost_centre_info fe_binders
260                            local_tycons local_classes stg_binds
261
262       --------------------------  Code output -------------------------------
263       show_pass "CodeOutput"
264       -- _scc_     "CodeOutput"
265       let (fe_binders, h_code, c_code) = foreign_stuff
266       (maybe_stub_h_name, maybe_stub_c_name)
267          <- codeOutput this_mod local_tycons local_classes
268                        occ_anal_tidy_binds stg_binds2
269                        c_code h_code abstractC ncg_uniqs
270
271       return (maybe_stub_h_name, maybe_stub_c_name, Nothing)
272  where
273     local_tycons  = tcEnvTyCons tc_env
274     local_classes = tcEnvClasses tc_env
275
276
277 dsThenSimplThenTidy dflags mod tc_result
278 -- make up ds_uniqs here
279  = do --------------------------  Desugaring ----------------
280       -- _scc_     "DeSugar"
281       (desugared, rules, h_code, c_code, fe_binders) 
282          <- deSugar this_mod ds_uniqs tc_result
283
284       --------------------------  Main Core-language transformations ----------------
285       -- _scc_     "Core2Core"
286       (simplified, orphan_rules)  <- core2core core_cmds desugared rules
287
288       -- Do the final tidy-up
289       (tidy_binds, tidy_orphan_rules) 
290          <- tidyCorePgm this_mod simplified orphan_rules
291       
292       return (tidy_binds, tidy_orphan_rules, (fe_binders,h_code,c_code))
293
294
295 myCoreToStg c2s_uniqs st_uniqs this_mod tidy_binds
296  = do let occ_anal_tidy_binds = occurAnalyseBinds tidy_binds
297
298       () <- coreBindsSize occ_anal_tidy_binds `seq` return ()
299       -- TEMP: the above call zaps some space usage allocated by the
300       -- simplifier, which for reasons I don't understand, persists
301       -- thoroughout code generation
302
303       show_pass "Core2Stg"
304       -- _scc_     "Core2Stg"
305       let stg_binds   = topCoreBindsToStg c2s_uniqs occ_anal_tidy_binds
306
307       show_pass "Stg2Stg"
308       -- _scc_     "Stg2Stg"
309       (stg_binds2, cost_centre_info) <- stg2stg stg_cmds this_mod st_uniqs stg_binds
310       let final_ids = collectFinalStgBinders (map fst stg_binds2)
311
312       return (stg_binds2, cost_centre_info, final_ids)
313 \end{code}
314
315
316 %************************************************************************
317 %*                                                                      *
318 \subsection{Initial persistent state}
319 %*                                                                      *
320 %************************************************************************
321
322 \begin{code}
323 initPersistentCompilerState :: IO PersistentCompilerState
324 initPersistentCompilerState 
325   = do prs <- initPersistentRenamerState
326        return (
327         PCS { pcs_PST   = initPackageDetails,
328               pcs_insts = emptyInstEnv,
329               pcs_rules = emptyRuleEnv,
330               pcs_PRS   = prs
331             }
332         )
333
334 initPackageDetails :: PackageSymbolTable
335 initPackageDetails = extendTypeEnv emptyModuleEnv wiredInThings
336
337 initPersistentRenamerState :: IO PersistentRenamerState
338   = do ns <- mkSplitUniqSupply 'r'
339        return (
340         PRS { prsOrig  = Orig { origNames  = initOrigNames,
341                                 origIParam = emptyFM },
342               prsDecls = emptyNameEnv,
343               prsInsts = emptyBag,
344               prsRules = emptyBag,
345               prsNS    = ns
346             }
347         )
348
349 initOrigNames :: FiniteMap (ModuleName,OccName) Name
350 initOrigNames = grab knownKeyNames `plusFM` grab (map getName wiredInThings)
351               where
352                 grab names   = foldl add emptyFM names
353                 add env name = addToFM env (moduleName (nameModule name), nameOccName name) name
354
355
356 initRules :: PackageRuleBase
357 initRules = foldl add emptyVarEnv builtinRules
358           where
359             add env (name,rule) = extendNameEnv_C add1 env name [rule]
360             add1 rules _        = rule : rules
361 \end{code}