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