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