eaaae2c165c039306cca31c3385207f8d1e548f8
[ghc-hetmet.git] / compiler / codeGen / CodeGen.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5
6 The Code Generator
7
8 This module says how things get going at the top level.
9
10 @codeGen@ is the interface to the outside world.  The \tr{cgTop*}
11 functions drive the mangling of top-level bindings.
12
13 \begin{code}
14 module CodeGen ( codeGen ) where
15
16 #include "HsVersions.h"
17
18 -- Kludge (??) so that CgExpr is reached via at least one non-SOURCE
19 -- import.  Before, that wasn't the case, and CM therefore didn't 
20 -- bother to compile it.
21 import CgExpr           ( {-NOTHING!-} )        -- DO NOT DELETE THIS IMPORT
22 import CgProf
23 import CgMonad
24 import CgBindery
25 import CgClosure
26 import CgCon
27 import CgUtils
28 import CgHpc
29
30 import CLabel
31 import Cmm
32 import CmmUtils
33 import PprCmm
34 import MachOp
35
36 import StgSyn
37 import PrelNames
38 import DynFlags
39 import StaticFlags
40
41 import PackageConfig
42 import HscTypes
43 import CostCentre
44 import Id
45 import Name
46 import OccName
47 import TyCon
48 import Module
49 import ErrUtils
50
51 #ifdef DEBUG
52 import Panic
53 #endif
54 \end{code}
55
56 \begin{code}
57 codeGen :: DynFlags
58         -> Module
59         -> [TyCon]
60         -> [Module]             -- directly-imported modules
61         -> CollectedCCs         -- (Local/global) cost-centres needing declaring/registering.
62         -> [(StgBinding,[(Id,[Id])])]   -- Bindings to convert, with SRTs
63         -> HpcInfo
64         -> IO [Cmm]             -- Output
65
66 codeGen dflags this_mod data_tycons imported_mods 
67         cost_centre_info stg_binds hpc_info
68   = do  
69   { showPass dflags "CodeGen"
70   ; let way = buildTag dflags
71         main_mod = mainModIs dflags
72
73 -- Why?
74 --   ; mapM_ (\x -> seq x (return ())) data_tycons
75
76   ; code_stuff <- initC dflags this_mod $ do 
77                 { cmm_binds  <- mapM (getCmm . cgTopBinding dflags) stg_binds
78                 ; cmm_tycons <- mapM cgTyCon data_tycons
79                 ; cmm_init   <- getCmm (mkModuleInit way cost_centre_info 
80                                              this_mod main_mod
81                                              imported_mods hpc_info)
82                 ; return (cmm_binds ++ concat cmm_tycons ++ [cmm_init])
83                 }
84                 -- Put datatype_stuff after code_stuff, because the
85                 -- datatype closure table (for enumeration types) to
86                 -- (say) PrelBase_True_closure, which is defined in
87                 -- code_stuff
88
89   ; dumpIfSet_dyn dflags Opt_D_dump_cmm "Cmm" (pprCmms code_stuff)
90
91   ; return code_stuff }
92 \end{code}
93
94 %************************************************************************
95 %*                                                                      *
96 \subsection[codegen-init]{Module initialisation code}
97 %*                                                                      *
98 %************************************************************************
99
100 /* -----------------------------------------------------------------------------
101    Module initialisation
102
103    The module initialisation code looks like this, roughly:
104
105         FN(__stginit_Foo) {
106           JMP_(__stginit_Foo_1_p)
107         }
108
109         FN(__stginit_Foo_1_p) {
110         ...
111         }
112
113    We have one version of the init code with a module version and the
114    'way' attached to it.  The version number helps to catch cases
115    where modules are not compiled in dependency order before being
116    linked: if a module has been compiled since any modules which depend on
117    it, then the latter modules will refer to a different version in their
118    init blocks and a link error will ensue.
119
120    The 'way' suffix helps to catch cases where modules compiled in different
121    ways are linked together (eg. profiled and non-profiled).
122
123    We provide a plain, unadorned, version of the module init code
124    which just jumps to the version with the label and way attached.  The
125    reason for this is that when using foreign exports, the caller of
126    startupHaskell() must supply the name of the init function for the "top"
127    module in the program, and we don't want to require that this name
128    has the version and way info appended to it.
129    --------------------------------------------------------------------------  */
130
131 We initialise the module tree by keeping a work-stack, 
132         * pointed to by Sp
133         * that grows downward
134         * Sp points to the last occupied slot
135
136
137 \begin{code}
138 mkModuleInit 
139         :: String               -- the "way"
140         -> CollectedCCs         -- cost centre info
141         -> Module
142         -> Module               -- name of the Main module
143         -> [Module]
144         -> HpcInfo
145         -> Code
146 mkModuleInit way cost_centre_info this_mod main_mod imported_mods hpc_info
147   = do  { -- Allocate the static boolean that records if this
148           -- module has been registered already
149           emitData Data [CmmDataLabel moduleRegdLabel, 
150                          CmmStaticLit zeroCLit]
151
152         ; whenC (opt_Hpc) $
153               hpcTable this_mod hpc_info
154
155           -- we emit a recursive descent module search for all modules
156           -- and *choose* to chase it in :Main, below.
157           -- In this way, Hpc enabled modules can interact seamlessly with
158           -- not Hpc enabled moduled, provided Main is compiled with Hpc.
159
160         ; emitSimpleProc real_init_lbl $ do
161                        { ret_blk <- forkLabelledCode ret_code
162
163                         ; init_blk <- forkLabelledCode $ do
164                                         { mod_init_code; stmtC (CmmBranch ret_blk) }
165                                     
166                         ; stmtC (CmmCondBranch (cmmNeWord (CmmLit zeroCLit) mod_reg_val)
167                                     ret_blk)
168                         ; stmtC (CmmBranch init_blk)        
169                         }
170
171             -- Make the "plain" procedure jump to the "real" init procedure
172         ; emitSimpleProc plain_init_lbl jump_to_init
173
174         -- When compiling the module in which the 'main' function lives,
175         -- (that is, this_mod == main_mod)
176         -- we inject an extra stg_init procedure for stg_init_ZCMain, for the 
177         -- RTS to invoke.  We must consult the -main-is flag in case the
178         -- user specified a different function to Main.main
179  
180         -- Notice that the recursive descent is optional, depending on what options
181         -- are enabled.
182
183         ; whenC (this_mod == main_mod)
184                 (emitSimpleProc plain_main_init_lbl rec_descent_init)
185     }
186   where
187     plain_init_lbl = mkPlainModuleInitLabel this_mod
188     real_init_lbl  = mkModuleInitLabel this_mod way
189     plain_main_init_lbl = mkPlainModuleInitLabel rOOT_MAIN
190
191     jump_to_init = stmtC (CmmJump (mkLblExpr real_init_lbl) [])
192
193     mod_reg_val = CmmLoad (mkLblExpr moduleRegdLabel) wordRep
194
195     -- Main refers to GHC.TopHandler.runIO, so make sure we call the
196     -- init function for GHC.TopHandler.
197     extra_imported_mods
198         | this_mod == main_mod = [gHC_TOP_HANDLER]
199         | otherwise            = []
200
201     mod_init_code = do
202         {       -- Set mod_reg to 1 to record that we've been here
203           stmtC (CmmStore (mkLblExpr moduleRegdLabel) (CmmLit (mkIntCLit 1)))
204
205         ; whenC (opt_SccProfilingOn) $ do 
206             initCostCentres cost_centre_info
207
208         ; whenC (opt_Hpc) $
209             initHpc this_mod hpc_info
210          
211         ; mapCs (registerModuleImport way)
212                 (imported_mods++extra_imported_mods)
213
214         } 
215
216                     -- The return-code pops the work stack by 
217                     -- incrementing Sp, and then jumpd to the popped item
218     ret_code = stmtsC [ CmmAssign spReg (cmmRegOffW spReg 1)
219                       , CmmJump (CmmLoad (cmmRegOffW spReg (-1)) wordRep) [] ]
220
221
222     rec_descent_init = if opt_SccProfilingOn || isHpcUsed hpc_info
223                        then jump_to_init
224                        else ret_code
225
226 -----------------------
227 registerModuleImport :: String -> Module -> Code
228 registerModuleImport way mod
229   | mod == gHC_PRIM
230   = nopC 
231   | otherwise   -- Push the init procedure onto the work stack
232   = stmtsC [ CmmAssign spReg (cmmRegOffW spReg (-1))
233            , CmmStore (CmmReg spReg) (mkLblExpr (mkModuleInitLabel mod way)) ]
234 \end{code}
235
236
237
238 Cost-centre profiling: Besides the usual stuff, we must produce
239 declarations for the cost-centres defined in this module;
240
241 (The local cost-centres involved in this are passed into the
242 code-generator.)
243
244 \begin{code}
245 initCostCentres :: CollectedCCs -> Code
246 -- Emit the declarations, and return code to register them
247 initCostCentres (local_CCs, ___extern_CCs, singleton_CCSs)
248   | not opt_SccProfilingOn = nopC
249   | otherwise
250   = do  { mapM_ emitCostCentreDecl       local_CCs
251         ; mapM_ emitCostCentreStackDecl  singleton_CCSs
252         ; mapM_ emitRegisterCC           local_CCs
253         ; mapM_ emitRegisterCCS          singleton_CCSs
254         }
255 \end{code}
256
257 %************************************************************************
258 %*                                                                      *
259 \subsection[codegen-top-bindings]{Converting top-level STG bindings}
260 %*                                                                      *
261 %************************************************************************
262
263 @cgTopBinding@ is only used for top-level bindings, since they need
264 to be allocated statically (not in the heap) and need to be labelled.
265 No unboxed bindings can happen at top level.
266
267 In the code below, the static bindings are accumulated in the
268 @MkCgState@, and transferred into the ``statics'' slot by @forkStatics@.
269 This is so that we can write the top level processing in a compositional
270 style, with the increasing static environment being plumbed as a state
271 variable.
272
273 \begin{code}
274 cgTopBinding :: DynFlags -> (StgBinding,[(Id,[Id])]) -> Code
275 cgTopBinding dflags (StgNonRec id rhs, srts)
276   = do  { id' <- maybeExternaliseId dflags id
277         ; mapM_ (mkSRT [id']) srts
278         ; (id,info) <- cgTopRhs id' rhs
279         ; addBindC id info      -- Add the *un-externalised* Id to the envt,
280                                 -- so we find it when we look up occurrences
281         }
282
283 cgTopBinding dflags (StgRec pairs, srts)
284   = do  { let (bndrs, rhss) = unzip pairs
285         ; bndrs' <- mapFCs (maybeExternaliseId dflags) bndrs
286         ; let pairs' = zip bndrs' rhss
287         ; mapM_ (mkSRT bndrs')  srts
288         ; _new_binds <- fixC (\ new_binds -> do 
289                 { addBindsC new_binds
290                 ; mapFCs ( \ (b,e) -> cgTopRhs b e ) pairs' })
291         ; nopC }
292
293 mkSRT :: [Id] -> (Id,[Id]) -> Code
294 mkSRT these (id,[])  = nopC
295 mkSRT these (id,ids)
296   = do  { ids <- mapFCs remap ids
297         ; id  <- remap id
298         ; emitRODataLits (mkSRTLabel (idName id)) 
299                        (map (CmmLabel . mkClosureLabel . idName) ids)
300         }
301   where
302         -- Sigh, better map all the ids against the environment in 
303         -- case they've been externalised (see maybeExternaliseId below).
304     remap id = case filter (==id) these of
305                 (id':_) -> returnFC id'
306                 [] -> do { info <- getCgIdInfo id; return (cgIdInfoId info) }
307
308 -- Urgh!  I tried moving the forkStatics call from the rhss of cgTopRhs
309 -- to enclose the listFCs in cgTopBinding, but that tickled the
310 -- statics "error" call in initC.  I DON'T UNDERSTAND WHY!
311
312 cgTopRhs :: Id -> StgRhs -> FCode (Id, CgIdInfo)
313         -- The Id is passed along for setting up a binding...
314         -- It's already been externalised if necessary
315
316 cgTopRhs bndr (StgRhsCon cc con args)
317   = forkStatics (cgTopRhsCon bndr con args)
318
319 cgTopRhs bndr (StgRhsClosure cc bi fvs upd_flag srt args body)
320   = ASSERT(null fvs)    -- There should be no free variables
321     setSRTLabel (mkSRTLabel (idName bndr)) $
322     setSRT srt $
323     forkStatics (cgTopRhsClosure bndr cc bi upd_flag args body)
324 \end{code}
325
326
327 %************************************************************************
328 %*                                                                      *
329 \subsection{Stuff to support splitting}
330 %*                                                                      *
331 %************************************************************************
332
333 If we're splitting the object, we need to externalise all the top-level names
334 (and then make sure we only use the externalised one in any C label we use
335 which refers to this name).
336
337 \begin{code}
338 maybeExternaliseId :: DynFlags -> Id -> FCode Id
339 maybeExternaliseId dflags id
340   | dopt Opt_SplitObjs dflags,  -- Externalise the name for -split-objs
341     isInternalName name = do { mod <- getModuleName
342                              ; returnFC (setIdName id (externalise mod)) }
343   | otherwise           = returnFC id
344   where
345     externalise mod = mkExternalName uniq mod new_occ loc
346     name    = idName id
347     uniq    = nameUnique name
348     new_occ = mkLocalOcc uniq (nameOccName name)
349     loc     = nameSrcSpan name
350         -- We want to conjure up a name that can't clash with any
351         -- existing name.  So we generate
352         --      Mod_$L243foo
353         -- where 243 is the unique.
354 \end{code}