[project @ 2003-03-03 12:43:31 by simonmar]
[ghc-hetmet.git] / ghc / compiler / codeGen / CodeGen.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[CodeGen]{@CodeGen@: main module of the code generator}
5
6 This module says how things get going at the top level.
7
8 @codeGen@ is the interface to the outside world.  The \tr{cgTop*}
9 functions drive the mangling of top-level bindings.
10
11 %************************************************************************
12 %*                                                                      *
13 \subsection[codeGen-outside-interface]{The code generator's offering to the world}
14 %*                                                                      *
15 %************************************************************************
16
17 \begin{code}
18 module CodeGen ( codeGen ) where
19
20 #include "HsVersions.h"
21
22 -- Kludge (??) so that CgExpr is reached via at least one non-SOURCE
23 -- import.  Before, that wasn't the case, and CM therefore didn't 
24 -- bother to compile it.
25 import CgExpr           ( {-NOTHING!-} )        -- DO NOT DELETE THIS IMPORT
26
27 import DriverState      ( v_Build_tag )
28 import StgSyn
29 import CgMonad
30 import AbsCSyn
31 import PrelNames        ( gHC_PRIM )
32 import CLabel           ( CLabel, mkSRTLabel, mkClosureLabel, 
33                           mkPlainModuleInitLabel, mkModuleInitLabel )
34 import PprAbsC          ( dumpRealC )
35 import AbsCUtils        ( mkAbstractCs, flattenAbsC )
36 import CgBindery        ( CgIdInfo, addBindC, addBindsC, getCAddrModeAndInfo )
37 import CgClosure        ( cgTopRhsClosure )
38 import CgCon            ( cgTopRhsCon )
39 import CgConTbls        ( genStaticConBits )
40 import ClosureInfo      ( mkClosureLFInfo )
41 import CmdLineOpts      ( DynFlags, DynFlag(..),
42                           opt_SccProfilingOn, opt_EnsureSplittableC )
43 import HscTypes         ( ModGuts(..), ModGuts, ForeignStubs(..), TypeEnv,
44                           typeEnvTyCons )
45 import CostCentre       ( CollectedCCs )
46 import Id               ( Id, idName, setIdName )
47 import Name             ( nameSrcLoc, nameOccName, nameUnique, isInternalName, mkExternalName )
48 import OccName          ( mkLocalOcc )
49 import PrimRep          ( PrimRep(..) )
50 import TyCon            ( isDataTyCon )
51 import Module           ( Module )
52 import BasicTypes       ( TopLevelFlag(..) )
53 import UniqSupply       ( mkSplitUniqSupply )
54 import ErrUtils         ( dumpIfSet_dyn, showPass )
55 import Panic            ( assertPanic )
56
57 #ifdef DEBUG
58 import Outputable
59 #endif
60
61 import DATA_IOREF       ( readIORef )
62 \end{code}
63
64 \begin{code}
65 codeGen :: DynFlags
66         -> Module
67         -> TypeEnv
68         -> ForeignStubs
69         -> [Module]             -- directly-imported modules
70         -> CollectedCCs         -- (Local/global) cost-centres needing declaring/registering.
71         -> [(StgBinding,[Id])]  -- Bindings to convert, with SRTs
72         -> IO AbstractC         -- Output
73
74 codeGen dflags this_mod type_env foreign_stubs imported_mods 
75         cost_centre_info stg_binds
76   = do  
77         showPass dflags "CodeGen"
78         fl_uniqs <- mkSplitUniqSupply 'f'
79         way <- readIORef v_Build_tag
80
81         let
82             tycons         = typeEnvTyCons type_env
83             data_tycons    = filter isDataTyCon tycons
84
85         mapM_ (\x -> seq x (return ())) data_tycons
86
87         let
88
89             cinfo          = MkCompInfo this_mod
90
91             datatype_stuff = genStaticConBits cinfo data_tycons
92             code_stuff     = initC cinfo (mapCs cgTopBinding stg_binds)
93             init_stuff     = mkModuleInit way cost_centre_info this_mod
94                                 foreign_stubs imported_mods
95
96             abstractC = mkAbstractCs [ maybeSplitCode,
97                                        init_stuff, 
98                                        code_stuff,
99                                        datatype_stuff]
100                 -- Put datatype_stuff after code_stuff, because the
101                 -- datatype closure table (for enumeration types) to
102                 -- (say) PrelBase_True_closure, which is defined in
103                 -- code_stuff
104
105         dumpIfSet_dyn dflags Opt_D_dump_absC "Abstract C" (dumpRealC abstractC)
106
107         return $! flattenAbsC fl_uniqs abstractC
108 \end{code}
109
110 %************************************************************************
111 %*                                                                      *
112 \subsection[codegen-init]{Module initialisation code}
113 %*                                                                      *
114 %************************************************************************
115
116 \begin{code}
117 mkModuleInit 
118         :: String               -- the "way"
119         -> CollectedCCs         -- cost centre info
120         -> Module
121         -> ForeignStubs
122         -> [Module]
123         -> AbstractC
124 mkModuleInit way cost_centre_info this_mod foreign_stubs imported_mods
125   = let
126         (cc_decls, cc_regs) = mkCostCentreStuff cost_centre_info
127
128         register_foreign_exports 
129                 = case foreign_stubs of
130                         NoStubs                     -> []
131                         ForeignStubs _ _ _ fe_bndrs -> map mk_export_register fe_bndrs
132
133         mk_export_register bndr
134           = CMacroStmt REGISTER_FOREIGN_EXPORT [lbl]
135           where
136             lbl = CLbl (mkClosureLabel (idName bndr)) PtrRep
137                 -- we don't want/need to init GHC.Prim, so filter it out
138
139         mk_import_register mod
140             | mod == gHC_PRIM = AbsCNop
141             | otherwise       = CMacroStmt REGISTER_IMPORT [
142                                    CLbl (mkModuleInitLabel mod way) AddrRep
143                                 ]
144
145         register_mod_imports = map mk_import_register imported_mods
146     in
147     mkAbstractCs [
148         cc_decls,
149         CModuleInitBlock (mkPlainModuleInitLabel this_mod)
150                          (mkModuleInitLabel this_mod way)
151                          (mkAbstractCs (register_foreign_exports ++
152                                         cc_regs :
153                                         register_mod_imports))
154     ]
155 \end{code}
156
157 Cost-centre profiling: Besides the usual stuff, we must produce
158 declarations for the cost-centres defined in this module;
159
160 (The local cost-centres involved in this are passed into the
161 code-generator.)
162
163 \begin{code}
164 mkCostCentreStuff (local_CCs, extern_CCs, singleton_CCSs)
165   | not opt_SccProfilingOn = (AbsCNop, AbsCNop)
166   | otherwise = 
167         ( mkAbstractCs (
168                 map (CCostCentreDecl True)   local_CCs ++
169                 map (CCostCentreDecl False)  extern_CCs ++
170                 map CCostCentreStackDecl     singleton_CCSs),
171           mkAbstractCs (mkCcRegister local_CCs singleton_CCSs)
172         )
173   where
174     mkCcRegister ccs cc_stacks
175       = let
176             register_ccs       = mkAbstractCs (map mk_register ccs)
177             register_cc_stacks = mkAbstractCs (map mk_register_ccs cc_stacks)
178         in
179         [ register_ccs, register_cc_stacks ]
180       where
181         mk_register cc
182           = CCallProfCCMacro FSLIT("REGISTER_CC") [mkCCostCentre cc]
183
184         mk_register_ccs ccs
185           = CCallProfCCMacro FSLIT("REGISTER_CCS") [mkCCostCentreStack ccs]
186 \end{code}
187
188 %************************************************************************
189 %*                                                                      *
190 \subsection[codegen-top-bindings]{Converting top-level STG bindings}
191 %*                                                                      *
192 %************************************************************************
193
194 @cgTopBinding@ is only used for top-level bindings, since they need
195 to be allocated statically (not in the heap) and need to be labelled.
196 No unboxed bindings can happen at top level.
197
198 In the code below, the static bindings are accumulated in the
199 @MkCgState@, and transferred into the ``statics'' slot by @forkStatics@.
200 This is so that we can write the top level processing in a compositional
201 style, with the increasing static environment being plumbed as a state
202 variable.
203
204 \begin{code}
205 cgTopBinding :: (StgBinding,[Id]) -> Code
206 cgTopBinding (StgNonRec srt_info id rhs, srt)
207   = absC maybeSplitCode         `thenC`
208     maybeExternaliseId id               `thenFC` \ id' ->
209     let
210         srt_label = mkSRTLabel (idName id')
211     in
212     mkSRT srt_label srt []      `thenC`
213     setSRTLabel srt_label (
214     cgTopRhs id' rhs srt_info   `thenFC` \ (id, info) ->
215     addBindC id info    -- Add the un-externalised Id to the envt, so we
216                         -- find it when we look up occurrences
217     )
218
219 cgTopBinding (StgRec srt_info pairs, srt)
220   = absC maybeSplitCode                 `thenC`
221     let
222         (bndrs, rhss) = unzip pairs
223     in
224     mapFCs maybeExternaliseId bndrs     `thenFC` \ bndrs'@(id:_) ->
225     let
226         srt_label = mkSRTLabel (idName id)
227         pairs'    = zip bndrs' rhss
228     in
229     mkSRT srt_label srt bndrs'          `thenC`
230     setSRTLabel srt_label (
231        fixC (\ new_binds -> 
232                 addBindsC new_binds             `thenC`
233                 mapFCs ( \ (b,e) -> cgTopRhs b e srt_info ) pairs'
234        )  `thenFC` \ new_binds -> nopC
235     )
236
237 mkSRT :: CLabel -> [Id] -> [Id] -> Code
238 mkSRT lbl []  these = nopC
239 mkSRT lbl ids these
240   = mapFCs remap ids `thenFC` \ ids ->
241     absC (CSRT lbl (map (mkClosureLabel . idName) ids))
242   where
243         -- sigh, better map all the ids against the environment in case they've
244         -- been externalised (see maybeExternaliseId below).
245     remap id = case filter (==id) these of
246                 [] ->  getCAddrModeAndInfo id 
247                                 `thenFC` \ (id, _, _) -> returnFC id
248                 (id':_) -> returnFC id'
249
250 -- Urgh!  I tried moving the forkStatics call from the rhss of cgTopRhs
251 -- to enclose the listFCs in cgTopBinding, but that tickled the
252 -- statics "error" call in initC.  I DON'T UNDERSTAND WHY!
253
254 cgTopRhs :: Id -> StgRhs -> SRT -> FCode (Id, CgIdInfo)
255         -- The Id is passed along for setting up a binding...
256         -- It's already been externalised if necessary
257
258 cgTopRhs bndr (StgRhsCon cc con args) srt
259   = forkStatics (cgTopRhsCon bndr con args srt)
260
261 cgTopRhs bndr (StgRhsClosure cc bi fvs upd_flag args body) srt
262   = ASSERT(null fvs)    -- There should be no free variables
263     let 
264         lf_info = mkClosureLFInfo bndr TopLevel [{-no fvs-}] upd_flag args
265     in
266     forkStatics (cgTopRhsClosure bndr cc bi srt args body lf_info)
267 \end{code}
268
269
270 %************************************************************************
271 %*                                                                      *
272 \subsection{Stuff to support splitting}
273 %*                                                                      *
274 %************************************************************************
275
276 If we're splitting the object, we need to externalise all the top-level names
277 (and then make sure we only use the externalised one in any C label we use
278 which refers to this name).
279
280 \begin{code}
281 maybeExternaliseId :: Id -> FCode Id
282 maybeExternaliseId id
283   | opt_EnsureSplittableC,      -- Externalise the name for -split-objs
284     isInternalName name
285   = moduleName                           `thenFC` \ mod ->
286     returnFC (setIdName id (mkExternalName uniq mod new_occ (nameSrcLoc name)))
287   | otherwise           
288   = returnFC id
289   where
290     name       = idName id
291     uniq       = nameUnique name
292     new_occ    = mkLocalOcc uniq (nameOccName name)
293         -- We want to conjure up a name that can't clash with any
294         -- existing name.  So we generate
295         --      Mod_$L243foo
296         -- where 243 is the unique.
297
298 maybeSplitCode
299   | opt_EnsureSplittableC = CSplitMarker 
300   | otherwise             = AbsCNop
301 \end{code}