[project @ 2000-11-21 15:41:10 by sewardj]
[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 )
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 )
43 import Module           ( Module )
44 import PrimRep          ( PrimRep(..) )
45 import TyCon            ( TyCon, isDataTyCon )
46 import BasicTypes       ( TopLevelFlag(..) )
47 import UniqSupply       ( mkSplitUniqSupply )
48 import ErrUtils         ( dumpIfSet_dyn, showPass )
49 import Panic            ( assertPanic )
50 \end{code}
51
52 \begin{code}
53
54
55 codeGen :: DynFlags
56         -> Module               -- Module name
57         -> [Module]             -- Import names
58         -> ([CostCentre],       -- Local cost-centres needing declaring/registering
59             [CostCentre],       -- "extern" cost-centres needing declaring
60             [CostCentreStack])  -- Pre-defined "singleton" cost centre stacks
61         -> [Id]                 -- foreign-exported binders
62         -> [TyCon]              -- Local tycons, including ones from classes
63         -> [(StgBinding,[Id])]  -- Bindings to convert, with SRTs
64         -> IO AbstractC         -- Output
65
66 codeGen dflags mod_name imported_modules cost_centre_info fe_binders
67         tycons stg_binds
68   = do  { showPass dflags "CodeGen"
69
70         ; fl_uniqs <- mkSplitUniqSupply 'f'
71         ; let
72             datatype_stuff = genStaticConBits cinfo data_tycons
73             code_stuff     = initC cinfo (cgTopBindings maybe_split stg_binds)
74             init_stuff     = mkModuleInit fe_binders mod_name imported_modules 
75                                           cost_centre_info
76
77             abstractC = mkAbstractCs [ maybe_split,
78                                        init_stuff, 
79                                        code_stuff,
80                                        datatype_stuff]
81                 -- Put datatype_stuff after code_stuff, because the
82                 -- datatype closure table (for enumeration types)
83                 -- to (say) PrelBase_True_closure, which is defined in code_stuff
84
85             flat_abstractC = flattenAbsC fl_uniqs abstractC
86
87         ; dumpIfSet_dyn dflags Opt_D_dump_absC "Abstract C" (dumpRealC abstractC)
88         ; return flat_abstractC
89         }
90   where
91     data_tycons = filter isDataTyCon tycons
92
93     maybe_split = if opt_EnsureSplittableC 
94                   then CSplitMarker 
95                   else AbsCNop
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 @cgTopBindings@ 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 cgTopBindings :: AbstractC -> [(StgBinding,[Id])] -> Code
189
190 cgTopBindings split bindings = mapCs (cgTopBinding split) bindings
191
192 cgTopBinding :: AbstractC -> (StgBinding,[Id]) -> Code
193
194 cgTopBinding split ((StgNonRec name rhs), srt)
195   = absC split                  `thenC`
196     absC (mkSRT srt_label srt)  `thenC`
197     setSRTLabel srt_label (
198     cgTopRhs name rhs           `thenFC` \ (name, info) ->
199     addBindC name info
200     )
201   where
202     srt_label = mkSRTLabel (idName name)
203
204 cgTopBinding split ((StgRec pairs@((name,rhs):_)), srt)
205   = absC split                  `thenC`
206     absC (mkSRT srt_label srt)  `thenC`
207     setSRTLabel srt_label (
208     fixC (\ new_binds -> addBindsC new_binds    `thenC`
209                          mapFCs ( \ (b,e) -> cgTopRhs b e ) pairs
210     )                     `thenFC` \ new_binds ->
211     addBindsC new_binds
212     )
213   where
214     srt_label = mkSRTLabel (idName name)
215
216 mkSRT :: CLabel -> [Id] -> AbstractC
217 mkSRT lbl []  = AbsCNop
218 mkSRT lbl ids = CSRT lbl (map (mkClosureLabel . idName) ids)
219
220 -- Urgh!  I tried moving the forkStatics call from the rhss of cgTopRhs
221 -- to enclose the listFCs in cgTopBinding, but that tickled the
222 -- statics "error" call in initC.  I DON'T UNDERSTAND WHY!
223
224 cgTopRhs :: Id -> StgRhs -> FCode (Id, CgIdInfo)
225         -- the Id is passed along for setting up a binding...
226
227 cgTopRhs bndr (StgRhsCon cc con args)
228   = forkStatics (cgTopRhsCon bndr con args)
229
230 cgTopRhs bndr (StgRhsClosure cc bi srt fvs upd_flag args body)
231   = ASSERT(null fvs) -- There should be no free variables
232     getSRTLabel `thenFC` \srt_label ->
233     let lf_info = 
234           mkClosureLFInfo bndr TopLevel [{-no fvs-}] upd_flag args srt_label srt
235     in
236     forkStatics (cgTopRhsClosure bndr cc bi args body lf_info)
237 \end{code}