[project @ 1999-03-02 14:34:33 by sof]
[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 import StgSyn
23 import CgMonad
24 import AbsCSyn
25 import CLabel           ( CLabel, mkSRTLabel, mkClosureLabel )
26
27 import AbsCUtils        ( mkAbstractCs, mkAbsCStmts )
28 import CgBindery        ( CgIdInfo )
29 import CgClosure        ( cgTopRhsClosure )
30 import CgCon            ( cgTopRhsCon )
31 import CgConTbls        ( genStaticConBits )
32 import ClosureInfo      ( mkClosureLFInfo )
33 import CmdLineOpts      ( opt_SccProfilingOn, opt_EnsureSplittableC, 
34                                               opt_SccGroup
35                         )
36 import CostCentre       ( CostCentre, CostCentreStack )
37 import FiniteMap        ( FiniteMap )
38 import Id               ( Id, idName )
39 import Module           ( Module, moduleString )
40 import PrimRep          ( getPrimRepSize, PrimRep(..) )
41 import Type             ( Type )
42 import TyCon            ( TyCon )
43 import BasicTypes       ( TopLevelFlag(..) )
44 import Util
45 import Panic            ( assertPanic )
46 \end{code}
47
48 \begin{code}
49 codeGen :: Module               -- module name
50         -> ([CostCentre],       -- local cost-centres needing declaring/registering
51             [CostCentre],       -- "extern" cost-centres needing declaring
52             [CostCentreStack])  -- pre-defined "singleton" cost centre stacks
53         -> [Module]             -- import names
54         -> [TyCon]              -- tycons with data constructors to convert
55         -> FiniteMap TyCon [(Bool, [Maybe Type])]
56                                 -- tycon specialisation info
57         -> [(StgBinding,[Id])]  -- bindings to convert, with SRTs
58         -> AbstractC            -- output
59
60 codeGen mod_name (local_CCs, extern_CCs, singleton_CCSs) 
61         import_names gen_tycons tycon_specs stg_pgm
62   = let
63         maybe_split       = if opt_EnsureSplittableC 
64                                 then CSplitMarker 
65                                 else AbsCNop
66         cinfo             = MkCompInfo mod_name
67     in
68     let 
69         module_code = mkAbstractCs [
70             genStaticConBits cinfo gen_tycons tycon_specs,
71             initC cinfo (cgTopBindings maybe_split stg_pgm) ]
72
73          -- Cost-centre profiling:
74          -- Besides the usual stuff, we must produce:
75          --
76          -- * Declarations for the cost-centres defined in this module;
77          -- * Code to participate in "registering" all the cost-centres
78          --   in the program (done at startup time when the pgm is run).
79          --
80          -- (The local cost-centres involved in this are passed
81          -- into the code-generator, as are the imported-modules' names.)
82          --
83          --
84         cost_centre_stuff 
85                 | not opt_SccProfilingOn = AbsCNop
86                 | otherwise = mkAbstractCs (
87                     map (CCostCentreDecl True)   local_CCs ++
88                     map (CCostCentreDecl False)  extern_CCs ++
89                     map CCostCentreStackDecl     singleton_CCSs ++
90                     mkCcRegister local_CCs singleton_CCSs import_names
91                    )
92    in
93    mkAbstractCs [ cost_centre_stuff, module_code ]
94
95   where
96     mkCcRegister ccs cc_stacks import_names
97       = let
98             register_ccs     = mkAbstractCs (map mk_register ccs)
99             register_imports
100               = foldr (mkAbsCStmts . mk_import_register) AbsCNop import_names
101             register_cc_stacks = mkAbstractCs (map mk_register_ccs cc_stacks)
102         in
103         [
104             CCallProfCCMacro SLIT("START_REGISTER_CCS") 
105                [ CLitLit (_PK_ ("_reg" ++ moduleString mod_name)) AddrRep],
106             register_ccs,
107             register_cc_stacks,
108             register_imports,
109             CCallProfCCMacro SLIT("END_REGISTER_CCS") []
110         ]
111       where
112         mk_register cc
113           = CCallProfCCMacro SLIT("REGISTER_CC") [mkCCostCentre cc]
114
115         mk_register_ccs ccs
116           = CCallProfCCMacro SLIT("REGISTER_CCS") [mkCCostCentreStack ccs]
117
118         mk_import_register import_name
119           = CCallProfCCMacro SLIT("REGISTER_IMPORT") 
120               [CLitLit (_PK_ ("_reg" ++ moduleString import_name)) AddrRep]
121 \end{code}
122
123 %************************************************************************
124 %*                                                                      *
125 \subsection[codegen-top-bindings]{Converting top-level STG bindings}
126 %*                                                                      *
127 %************************************************************************
128
129 @cgTopBindings@ is only used for top-level bindings, since they need
130 to be allocated statically (not in the heap) and need to be labelled.
131 No unboxed bindings can happen at top level.
132
133 In the code below, the static bindings are accumulated in the
134 @MkCgState@, and transferred into the ``statics'' slot by @forkStatics@.
135 This is so that we can write the top level processing in a compositional
136 style, with the increasing static environment being plumbed as a state
137 variable.
138
139 \begin{code}
140 cgTopBindings :: AbstractC -> [(StgBinding,[Id])] -> Code
141
142 cgTopBindings split bindings = mapCs (cgTopBinding split) bindings
143
144 cgTopBinding :: AbstractC -> (StgBinding,[Id]) -> Code
145
146 cgTopBinding split ((StgNonRec name rhs), srt)
147   = absC split                  `thenC`
148     absC (mkSRT srt_label srt)  `thenC`
149     setSRTLabel srt_label (
150     cgTopRhs name rhs           `thenFC` \ (name, info) ->
151     addBindC name info
152     )
153   where
154     srt_label = mkSRTLabel (idName name)
155
156 cgTopBinding split ((StgRec pairs@((name,rhs):_)), srt)
157   = absC split                  `thenC`
158     absC (mkSRT srt_label srt)  `thenC`
159     setSRTLabel srt_label (
160     fixC (\ new_binds -> addBindsC new_binds    `thenC`
161                          mapFCs ( \ (b,e) -> cgTopRhs b e ) pairs
162     )                     `thenFC` \ new_binds ->
163     addBindsC new_binds
164     )
165   where
166     srt_label = mkSRTLabel (idName name)
167
168 mkSRT :: CLabel -> [Id] -> AbstractC
169 mkSRT lbl []  = AbsCNop
170 mkSRT lbl ids = CSRT lbl (map (mkClosureLabel . idName) ids)
171
172 -- Urgh!  I tried moving the forkStatics call from the rhss of cgTopRhs
173 -- to enclose the listFCs in cgTopBinding, but that tickled the
174 -- statics "error" call in initC.  I DON'T UNDERSTAND WHY!
175
176 cgTopRhs :: Id -> StgRhs -> FCode (Id, CgIdInfo)
177         -- the Id is passed along for setting up a binding...
178
179 cgTopRhs bndr (StgRhsCon cc con args)
180   = forkStatics (cgTopRhsCon bndr con args (all zero_size args))
181   where
182     zero_size atom = getPrimRepSize (getArgPrimRep atom) == 0
183
184 cgTopRhs bndr (StgRhsClosure cc bi srt fvs upd_flag args body)
185   = ASSERT(null fvs) -- There should be no free variables
186     forkStatics (cgTopRhsClosure bndr cc bi srt args body lf_info)
187   where
188     lf_info = mkClosureLFInfo bndr TopLevel [{-no fvs-}] upd_flag args
189 \end{code}