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