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