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