Add PrimCall to the STG layer and update Core -> STG translation
[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
35 import StgSyn
36 import PrelNames
37 import DynFlags
38 import StaticFlags
39
40 import HscTypes
41 import CostCentre
42 import Id
43 import Name
44 import OccName
45 import TyCon
46 import Module
47 import ErrUtils
48 import Panic
49 \end{code}
50
51 \begin{code}
52 codeGen :: DynFlags
53         -> Module
54         -> [TyCon]
55         -> [Module]             -- directly-imported modules
56         -> CollectedCCs         -- (Local/global) cost-centres needing declaring/registering.
57         -> [(StgBinding,[(Id,[Id])])]   -- Bindings to convert, with SRTs
58         -> HpcInfo
59         -> IO [Cmm]             -- Output
60
61                 -- N.B. returning '[Cmm]' and not 'Cmm' here makes it
62                 -- possible for object splitting to split up the
63                 -- pieces later.
64
65 codeGen dflags this_mod data_tycons imported_mods 
66         cost_centre_info stg_binds hpc_info
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 way cost_centre_info 
79                                              this_mod main_mod
80                                              imported_mods hpc_info)
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         :: String               -- the "way"
139         -> CollectedCCs         -- cost centre info
140         -> Module
141         -> Module               -- name of the Main module
142         -> [Module]
143         -> HpcInfo
144         -> Code
145 mkModuleInit way cost_centre_info this_mod main_mod imported_mods hpc_info
146   = do  { -- Allocate the static boolean that records if this
147           -- module has been registered already
148           emitData Data [CmmDataLabel moduleRegdLabel, 
149                          CmmStaticLit zeroCLit]
150
151         ; whenC (opt_Hpc) $
152               hpcTable this_mod hpc_info
153
154           -- we emit a recursive descent module search for all modules
155           -- and *choose* to chase it in :Main, below.
156           -- In this way, Hpc enabled modules can interact seamlessly with
157           -- not Hpc enabled moduled, provided Main is compiled with Hpc.
158
159         ; emitSimpleProc real_init_lbl $ do
160                        { ret_blk <- forkLabelledCode ret_code
161
162                         ; init_blk <- forkLabelledCode $ do
163                                         { mod_init_code; stmtC (CmmBranch ret_blk) }
164                                     
165                         ; stmtC (CmmCondBranch (cmmNeWord (CmmLit zeroCLit) mod_reg_val)
166                                     ret_blk)
167                         ; stmtC (CmmBranch init_blk)        
168                         }
169
170             -- Make the "plain" procedure jump to the "real" init procedure
171         ; emitSimpleProc plain_init_lbl jump_to_init
172
173         -- When compiling the module in which the 'main' function lives,
174         -- (that is, this_mod == main_mod)
175         -- we inject an extra stg_init procedure for stg_init_ZCMain, for the 
176         -- RTS to invoke.  We must consult the -main-is flag in case the
177         -- user specified a different function to Main.main
178  
179         -- Notice that the recursive descent is optional, depending on what options
180         -- are enabled.
181
182         ; whenC (this_mod == main_mod)
183                 (emitSimpleProc plain_main_init_lbl rec_descent_init)
184     }
185   where
186     plain_init_lbl = mkPlainModuleInitLabel this_mod
187     real_init_lbl  = mkModuleInitLabel this_mod way
188     plain_main_init_lbl = mkPlainModuleInitLabel rOOT_MAIN
189
190     jump_to_init = stmtC (CmmJump (mkLblExpr real_init_lbl) [])
191
192     mod_reg_val = CmmLoad (mkLblExpr moduleRegdLabel) bWord
193
194     -- Main refers to GHC.TopHandler.runIO, so make sure we call the
195     -- init function for GHC.TopHandler.
196     extra_imported_mods
197         | this_mod == main_mod = [gHC_TOP_HANDLER]
198         | otherwise            = []
199
200     mod_init_code = do
201         {       -- Set mod_reg to 1 to record that we've been here
202           stmtC (CmmStore (mkLblExpr moduleRegdLabel) (CmmLit (mkIntCLit 1)))
203
204         ; whenC (opt_SccProfilingOn) $ do 
205             initCostCentres cost_centre_info
206
207         ; whenC (opt_Hpc) $
208             initHpc this_mod hpc_info
209          
210         ; mapCs (registerModuleImport way)
211                 (imported_mods++extra_imported_mods)
212
213         } 
214
215                     -- The return-code pops the work stack by 
216                     -- incrementing Sp, and then jumpd to the popped item
217     ret_code = stmtsC [ CmmAssign spReg (cmmRegOffW spReg 1)
218                       , CmmJump (CmmLoad (cmmRegOffW spReg (-1)) bWord) [] ]
219
220
221     rec_descent_init = if opt_SccProfilingOn || isHpcUsed hpc_info
222                        then jump_to_init
223                        else ret_code
224
225 -----------------------
226 registerModuleImport :: String -> Module -> Code
227 registerModuleImport way mod
228   | mod == gHC_PRIM
229   = nopC 
230   | otherwise   -- Push the init procedure onto the work stack
231   = stmtsC [ CmmAssign spReg (cmmRegOffW spReg (-1))
232            , CmmStore (CmmReg spReg) (mkLblExpr (mkModuleInitLabel mod way)) ]
233 \end{code}
234
235
236
237 Cost-centre profiling: Besides the usual stuff, we must produce
238 declarations for the cost-centres defined in this module;
239
240 (The local cost-centres involved in this are passed into the
241 code-generator.)
242
243 \begin{code}
244 initCostCentres :: CollectedCCs -> Code
245 -- Emit the declarations, and return code to register them
246 initCostCentres (local_CCs, ___extern_CCs, singleton_CCSs)
247   | not opt_SccProfilingOn = nopC
248   | otherwise
249   = do  { mapM_ emitCostCentreDecl       local_CCs
250         ; mapM_ emitCostCentreStackDecl  singleton_CCSs
251         ; mapM_ emitRegisterCC           local_CCs
252         ; mapM_ emitRegisterCCS          singleton_CCSs
253         }
254 \end{code}
255
256 %************************************************************************
257 %*                                                                      *
258 \subsection[codegen-top-bindings]{Converting top-level STG bindings}
259 %*                                                                      *
260 %************************************************************************
261
262 @cgTopBinding@ is only used for top-level bindings, since they need
263 to be allocated statically (not in the heap) and need to be labelled.
264 No unboxed bindings can happen at top level.
265
266 In the code below, the static bindings are accumulated in the
267 @MkCgState@, and transferred into the ``statics'' slot by @forkStatics@.
268 This is so that we can write the top level processing in a compositional
269 style, with the increasing static environment being plumbed as a state
270 variable.
271
272 \begin{code}
273 cgTopBinding :: DynFlags -> (StgBinding,[(Id,[Id])]) -> Code
274 cgTopBinding dflags (StgNonRec id rhs, srts)
275   = do  { id' <- maybeExternaliseId dflags id
276         ; mapM_ (mkSRT [id']) srts
277         ; (id,info) <- cgTopRhs id' rhs
278         ; addBindC id info      -- Add the *un-externalised* Id to the envt,
279                                 -- so we find it when we look up occurrences
280         }
281
282 cgTopBinding dflags (StgRec pairs, srts)
283   = do  { let (bndrs, rhss) = unzip pairs
284         ; bndrs' <- mapFCs (maybeExternaliseId dflags) bndrs
285         ; let pairs' = zip bndrs' rhss
286         ; mapM_ (mkSRT bndrs')  srts
287         ; _new_binds <- fixC (\ new_binds -> do 
288                 { addBindsC new_binds
289                 ; mapFCs ( \ (b,e) -> cgTopRhs b e ) pairs' })
290         ; nopC }
291
292 mkSRT :: [Id] -> (Id,[Id]) -> Code
293 mkSRT _ (_,[])  = nopC
294 mkSRT these (id,ids)
295   = do  { ids <- mapFCs remap ids
296         ; id  <- remap id
297         ; emitRODataLits "CodeGen.mkSRT" (mkSRTLabel (idName id) (idCafInfo id)) 
298                (map (\id -> CmmLabel $ mkClosureLabel (idName id) (idCafInfo id)) ids)
299         }
300   where
301         -- Sigh, better map all the ids against the environment in 
302         -- case they've been externalised (see maybeExternaliseId below).
303     remap id = case filter (==id) these of
304                 (id':_) -> returnFC id'
305                 [] -> do { info <- getCgIdInfo id; return (cgIdInfoId info) }
306
307 -- Urgh!  I tried moving the forkStatics call from the rhss of cgTopRhs
308 -- to enclose the listFCs in cgTopBinding, but that tickled the
309 -- statics "error" call in initC.  I DON'T UNDERSTAND WHY!
310
311 cgTopRhs :: Id -> StgRhs -> FCode (Id, CgIdInfo)
312         -- The Id is passed along for setting up a binding...
313         -- It's already been externalised if necessary
314
315 cgTopRhs bndr (StgRhsCon _cc con args)
316   = forkStatics (cgTopRhsCon bndr con args)
317
318 cgTopRhs bndr (StgRhsClosure cc bi fvs upd_flag srt args body)
319   = ASSERT(null fvs)    -- There should be no free variables
320     setSRTLabel (mkSRTLabel (idName bndr) (idCafInfo bndr)) $
321     setSRT srt $
322     forkStatics (cgTopRhsClosure bndr cc bi upd_flag args body)
323 \end{code}
324
325
326 %************************************************************************
327 %*                                                                      *
328 \subsection{Stuff to support splitting}
329 %*                                                                      *
330 %************************************************************************
331
332 If we're splitting the object, we need to externalise all the top-level names
333 (and then make sure we only use the externalised one in any C label we use
334 which refers to this name).
335
336 \begin{code}
337 maybeExternaliseId :: DynFlags -> Id -> FCode Id
338 maybeExternaliseId dflags id
339   | dopt Opt_SplitObjs dflags,  -- Externalise the name for -split-objs
340     isInternalName name = do { mod <- getModuleName
341                              ; returnFC (setIdName id (externalise mod)) }
342   | otherwise           = returnFC id
343   where
344     externalise mod = mkExternalName uniq mod new_occ loc
345     name    = idName id
346     uniq    = nameUnique name
347     new_occ = mkLocalOcc uniq (nameOccName name)
348     loc     = nameSrcSpan name
349         -- We want to conjure up a name that can't clash with any
350         -- existing name.  So we generate
351         --      Mod_$L243foo
352         -- where 243 is the unique.
353 \end{code}