795f2ec8b3a783e78a31f7c11d1e1f1c9c742d2a
[ghc-hetmet.git] / ghc / compiler / codeGen / CodeGen.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1995
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 #include "HsVersions.h"
19
20 module CodeGen (
21         codeGen,
22
23         -- and to make the interface self-sufficient...
24         UniqFM, AbstractC, StgBinding, Id, FiniteMap
25     ) where
26
27
28 import StgSyn
29 import CgMonad
30 import AbsCSyn
31
32 import CLabelInfo       ( modnameToC )
33 import CgClosure        ( cgTopRhsClosure )
34 import CgCon            ( cgTopRhsCon )
35 import CgConTbls        ( genStaticConBits, TCE(..), UniqFM )
36 import ClosureInfo      ( LambdaFormInfo, mkClosureLFInfo )
37 import CmdLineOpts
38 import FiniteMap        ( FiniteMap )
39 import Maybes           ( Maybe(..) )
40 import Pretty           -- debugging only
41 import PrimKind         ( getKindSize )
42 import Util
43 \end{code}
44
45 \begin{code}
46 codeGen :: FAST_STRING          -- module name
47         -> ([CostCentre],       -- local cost-centres needing declaring/registering
48             [CostCentre])       -- "extern" cost-centres needing declaring
49         -> [FAST_STRING]        -- import names
50         -> (GlobalSwitch -> SwitchResult)
51                                 -- global switch lookup function
52         -> [TyCon]              -- tycons with data constructors to convert
53         -> FiniteMap TyCon [[Maybe UniType]]
54                                 -- tycon specialisation info
55         -> PlainStgProgram      -- bindings to convert
56         -> AbstractC            -- output
57
58 codeGen mod_name (local_CCs, extern_CCs) import_names sw_lookup_fn gen_tycons tycon_specs stg_pgm
59   = let
60         switch_is_on      = switchIsOn   sw_lookup_fn
61         int_switch_set    = intSwitchSet sw_lookup_fn
62         doing_profiling   = switch_is_on SccProfilingOn
63         compiling_prelude = switch_is_on CompilingPrelude
64         splitting         = switch_is_on (EnsureSplittableC (panic "codeGen:esc"))
65
66         cinfo = MkCompInfo switch_is_on int_switch_set mod_name
67     in
68
69 {- OLD:
70     pprTrace "codeGen:" (ppCat [
71     (case (switch_is_on StgDoLetNoEscapes) of
72         False -> ppStr "False?"
73         True  -> ppStr "True?"
74     ),
75     (case (int_switch_set ReturnInRegsThreshold) of
76         Nothing -> ppStr "Nothing!"
77         Just  n -> ppCat [ppStr "Just", ppInt n]
78     ),
79     (case (int_switch_set UnfoldingUseThreshold) of
80         Nothing -> ppStr "Nothing!"
81         Just  n -> ppCat [ppStr "Just", ppInt n]
82     ),
83     (case (int_switch_set UnfoldingCreationThreshold) of
84         Nothing -> ppStr "Nothing!"
85         Just  n -> ppCat [ppStr "Just", ppInt n]
86     )
87     ]) $
88 -}
89     if not doing_profiling then
90         mkAbstractCs [
91             genStaticConBits cinfo gen_tycons tycon_specs,
92             initC cinfo (cgTopBindings splitting stg_pgm) ]
93
94     else -- yes, cost-centre profiling:
95          -- Besides the usual stuff, we must produce:
96          --
97          -- * Declarations for the cost-centres defined in this module;
98          -- * Code to participate in "registering" all the cost-centres
99          --   in the program (done at startup time when the pgm is run).
100          --
101          -- (The local cost-centres involved in this are passed
102          -- into the code-generator, as are the imported-modules' names.)
103          --
104          -- Note: we don't register/etc if compiling Prelude bits.
105
106         mkAbstractCs [
107                 if compiling_prelude
108                 then AbsCNop
109                 else mkAbstractCs [mkAbstractCs (map (CCostCentreDecl True)  local_CCs),
110                                    mkAbstractCs (map (CCostCentreDecl False) extern_CCs),
111                                    mkCcRegister local_CCs import_names],
112
113                 genStaticConBits cinfo gen_tycons tycon_specs,
114                 initC cinfo (cgTopBindings splitting stg_pgm) ]
115   where
116     -----------------
117     grp_name  = case (stringSwitchSet sw_lookup_fn SccGroup) of
118                   Just xx -> _PK_ xx
119                   Nothing -> mod_name   -- default: module name
120
121     -----------------
122     mkCcRegister ccs import_names
123       = let 
124             register_ccs     = mkAbstractCs (map mk_register ccs)
125             register_imports = mkAbstractCs (map mk_import_register import_names)
126         in
127         mkAbstractCs [
128             CCallProfCCMacro SLIT("START_REGISTER_CCS") [CLitLit (modnameToC (SLIT("_reg") _APPEND_ mod_name)) AddrKind],
129             register_ccs,
130             register_imports,
131             CCallProfCCMacro SLIT("END_REGISTER_CCS") []
132         ]
133       where
134         mk_register cc
135           = CCallProfCCMacro SLIT("REGISTER_CC") [mkCCostCentre cc]
136
137         mk_import_register import_name
138           = CCallProfCCMacro SLIT("REGISTER_IMPORT") [CLitLit (modnameToC (SLIT("_reg") _APPEND_ import_name)) AddrKind]
139 \end{code}
140
141 %************************************************************************
142 %*                                                                      *
143 \subsection[codegen-top-bindings]{Converting top-level STG bindings}
144 %*                                                                      *
145 %************************************************************************
146
147 @cgTopBindings@ is only used for top-level bindings, since they need
148 to be allocated statically (not in the heap) and need to be labelled.
149 No unboxed bindings can happen at top level.
150
151 In the code below, the static bindings are accumulated in the
152 @MkCgState@, and transferred into the ``statics'' slot by @forkStatics@.
153 This is so that we can write the top level processing in a compositional
154 style, with the increasing static environment being plumbed as a state
155 variable.
156
157 \begin{code}
158 cgTopBindings :: Bool -> PlainStgProgram -> Code
159
160 cgTopBindings splitting bindings = mapCs (cgTopBinding splitting) bindings
161   
162 cgTopBinding :: Bool -> PlainStgBinding -> Code
163
164 cgTopBinding splitting (StgNonRec name rhs) 
165   = absC maybe_split    `thenC`
166     cgTopRhs name rhs   `thenFC` \ (name, info) ->
167     addBindC name info
168   where
169     maybe_split = if splitting then CSplitMarker else AbsCNop
170
171 cgTopBinding splitting (StgRec pairs) 
172   = absC maybe_split    `thenC`
173     fixC (\ new_binds -> addBindsC new_binds    `thenC`
174                          mapFCs ( \ (b,e) -> cgTopRhs b e ) pairs
175     )                   `thenFC` \ new_binds ->
176     addBindsC new_binds
177   where
178     maybe_split = if splitting then CSplitMarker else AbsCNop
179
180 -- Urgh!  I tried moving the forkStatics call from the rhss of cgTopRhs
181 -- to enclose the listFCs in cgTopBinding, but that tickled the
182 -- statics "error" call in initC.  I DON'T UNDERSTAND WHY!
183
184 cgTopRhs :: Id -> PlainStgRhs -> FCode (Id, CgIdInfo)
185         -- the Id is passed along for setting up a binding...
186
187 cgTopRhs name (StgRhsCon cc con args)
188   = forkStatics (cgTopRhsCon name con args (all zero_size args))
189   where
190     zero_size atom = getKindSize (getAtomKind atom) == 0
191
192 cgTopRhs name (StgRhsClosure cc bi fvs upd_flag args body)
193   = ASSERT(null fvs) -- There should be no free variables
194     forkStatics (cgTopRhsClosure name cc bi args body lf_info)
195   where
196     lf_info = mkClosureLFInfo True{-top level-} [{-no fvs-}] upd_flag args body
197 \end{code}