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