89d4baa5c899301ea095dfea9f859488fc058b26
[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 [(Bool, [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         maybe_split       = if (switch_is_on (EnsureSplittableC (panic "codeGen:esc")))
65                             then CSplitMarker
66                             else AbsCNop
67
68         cinfo = MkCompInfo switch_is_on int_switch_set mod_name
69     in
70
71 {- OLD:
72     pprTrace "codeGen:" (ppCat [
73     (case (switch_is_on StgDoLetNoEscapes) of
74         False -> ppStr "False?"
75         True  -> ppStr "True?"
76     ),
77     (case (int_switch_set ReturnInRegsThreshold) of
78         Nothing -> ppStr "Nothing!"
79         Just  n -> ppCat [ppStr "Just", ppInt n]
80     ),
81     (case (int_switch_set UnfoldingUseThreshold) of
82         Nothing -> ppStr "Nothing!"
83         Just  n -> ppCat [ppStr "Just", ppInt n]
84     ),
85     (case (int_switch_set UnfoldingCreationThreshold) of
86         Nothing -> ppStr "Nothing!"
87         Just  n -> ppCat [ppStr "Just", ppInt n]
88     )
89     ]) $
90 -}
91     if not doing_profiling then
92         mkAbstractCs [
93             genStaticConBits cinfo gen_tycons tycon_specs,
94             initC cinfo (cgTopBindings maybe_split stg_pgm) ]
95
96     else -- yes, cost-centre profiling:
97          -- Besides the usual stuff, we must produce:
98          --
99          -- * Declarations for the cost-centres defined in this module;
100          -- * Code to participate in "registering" all the cost-centres
101          --   in the program (done at startup time when the pgm is run).
102          --
103          -- (The local cost-centres involved in this are passed
104          -- into the code-generator, as are the imported-modules' names.)
105          --
106          -- Note: we don't register/etc if compiling Prelude bits.
107
108         mkAbstractCs [
109                 if compiling_prelude
110                 then AbsCNop
111                 else mkAbstractCs [mkAbstractCs (map (CCostCentreDecl True)  local_CCs),
112                                    mkAbstractCs (map (CCostCentreDecl False) extern_CCs),
113                                    mkCcRegister local_CCs import_names],
114
115                 genStaticConBits cinfo gen_tycons tycon_specs,
116                 initC cinfo (cgTopBindings maybe_split stg_pgm) ]
117   where
118     -----------------
119     grp_name  = case (stringSwitchSet sw_lookup_fn SccGroup) of
120                   Just xx -> _PK_ xx
121                   Nothing -> mod_name   -- default: module name
122
123     -----------------
124     mkCcRegister ccs import_names
125       = let 
126             register_ccs     = mkAbstractCs (map mk_register ccs)
127             register_imports = mkAbstractCs (map mk_import_register import_names)
128         in
129         mkAbstractCs [
130             CCallProfCCMacro SLIT("START_REGISTER_CCS") [CLitLit (modnameToC (SLIT("_reg") _APPEND_ mod_name)) AddrKind],
131             register_ccs,
132             register_imports,
133             CCallProfCCMacro SLIT("END_REGISTER_CCS") []
134         ]
135       where
136         mk_register cc
137           = CCallProfCCMacro SLIT("REGISTER_CC") [mkCCostCentre cc]
138
139         mk_import_register import_name
140           = CCallProfCCMacro SLIT("REGISTER_IMPORT") [CLitLit (modnameToC (SLIT("_reg") _APPEND_ import_name)) AddrKind]
141 \end{code}
142
143 %************************************************************************
144 %*                                                                      *
145 \subsection[codegen-top-bindings]{Converting top-level STG bindings}
146 %*                                                                      *
147 %************************************************************************
148
149 @cgTopBindings@ is only used for top-level bindings, since they need
150 to be allocated statically (not in the heap) and need to be labelled.
151 No unboxed bindings can happen at top level.
152
153 In the code below, the static bindings are accumulated in the
154 @MkCgState@, and transferred into the ``statics'' slot by @forkStatics@.
155 This is so that we can write the top level processing in a compositional
156 style, with the increasing static environment being plumbed as a state
157 variable.
158
159 \begin{code}
160 cgTopBindings :: AbstractC -> PlainStgProgram -> Code
161
162 cgTopBindings split bindings = mapCs (cgTopBinding split) bindings
163   
164 cgTopBinding :: AbstractC -> PlainStgBinding -> Code
165
166 cgTopBinding split (StgNonRec name rhs) 
167   = absC split          `thenC`
168     cgTopRhs name rhs   `thenFC` \ (name, info) ->
169     addBindC name info
170
171 cgTopBinding split (StgRec pairs) 
172   = absC 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
178 -- Urgh!  I tried moving the forkStatics call from the rhss of cgTopRhs
179 -- to enclose the listFCs in cgTopBinding, but that tickled the
180 -- statics "error" call in initC.  I DON'T UNDERSTAND WHY!
181
182 cgTopRhs :: Id -> PlainStgRhs -> FCode (Id, CgIdInfo)
183         -- the Id is passed along for setting up a binding...
184
185 cgTopRhs name (StgRhsCon cc con args)
186   = forkStatics (cgTopRhsCon name con args (all zero_size args))
187   where
188     zero_size atom = getKindSize (getAtomKind atom) == 0
189
190 cgTopRhs name (StgRhsClosure cc bi fvs upd_flag args body)
191   = ASSERT(null fvs) -- There should be no free variables
192     forkStatics (cgTopRhsClosure name cc bi args body lf_info)
193   where
194     lf_info = mkClosureLFInfo True{-top level-} [{-no fvs-}] upd_flag args body
195 \end{code}