| 1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
 | %
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
%
\section[CodeGen]{@CodeGen@: main module of the code generator}
This module says how things get going at the top level.
@codeGen@ is the interface to the outside world.  The \tr{cgTop*}
functions drive the mangling of top-level bindings.
%************************************************************************
%*									*
\subsection[codeGen-outside-interface]{The code generator's offering to the world}
%*									*
%************************************************************************
\begin{code}
#include "HsVersions.h"
module CodeGen ( codeGen ) where
IMP_Ubiq(){-uitous-}
import StgSyn
import CgMonad
import AbsCSyn
import AbsCUtils	( mkAbstractCs, mkAbsCStmts )
import Bag		( foldBag )
import CgBindery	( CgIdInfo )
import CgClosure	( cgTopRhsClosure )
import CgCon		( cgTopRhsCon )
import CgConTbls	( genStaticConBits )
import ClosureInfo	( mkClosureLFInfo )
import CmdLineOpts	( opt_SccProfilingOn, opt_CompilingGhcInternals,
			  opt_EnsureSplittableC, opt_SccGroup
			)
import CostCentre       ( CostCentre )
import CStrings		( modnameToC )
import FiniteMap	( FiniteMap )
import Id               ( SYN_IE(Id) )
import Maybes		( maybeToBool )
import Name             ( SYN_IE(Module) )
import PrimRep		( getPrimRepSize, PrimRep(..) )
import Type             ( SYN_IE(Type) )
import TyCon            ( TyCon )
import Util		( panic, assertPanic )
\end{code}
\begin{code}
codeGen :: FAST_STRING		-- module name
	-> ([CostCentre],	-- local cost-centres needing declaring/registering
	    [CostCentre])	-- "extern" cost-centres needing declaring
	-> [Module]		-- import names
	-> [TyCon]		-- tycons with data constructors to convert
	-> FiniteMap TyCon [(Bool, [Maybe Type])]
				-- tycon specialisation info
	-> [StgBinding]	-- bindings to convert
	-> AbstractC		-- output
codeGen mod_name (local_CCs, extern_CCs) import_names gen_tycons tycon_specs stg_pgm
  = let
	doing_profiling   = opt_SccProfilingOn
	compiling_prelude = opt_CompilingGhcInternals
	maybe_split       = if opt_EnsureSplittableC then CSplitMarker else AbsCNop
	cinfo             = MkCompInfo mod_name
    in
    if not doing_profiling then
	mkAbstractCs [
	    genStaticConBits cinfo gen_tycons tycon_specs,
	    initC cinfo (cgTopBindings maybe_split stg_pgm) ]
    else -- yes, cost-centre profiling:
	 -- Besides the usual stuff, we must produce:
	 --
    	 -- * Declarations for the cost-centres defined in this module;
	 -- * Code to participate in "registering" all the cost-centres
	 --   in the program (done at startup time when the pgm is run).
	 --
	 -- (The local cost-centres involved in this are passed
	 -- into the code-generator, as are the imported-modules' names.)
	 --
	 -- Note: we don't register/etc if compiling Prelude bits.
	mkAbstractCs [
		if compiling_prelude
		then AbsCNop
		else mkAbstractCs [mkAbstractCs (map (CCostCentreDecl True)  local_CCs),
				   mkAbstractCs (map (CCostCentreDecl False) extern_CCs),
				   mkCcRegister local_CCs import_names],
		genStaticConBits cinfo gen_tycons tycon_specs,
		initC cinfo (cgTopBindings maybe_split stg_pgm) ]
  where
    -----------------
    grp_name  = case opt_SccGroup of
		  Just xx -> _PK_ xx
		  Nothing -> mod_name	-- default: module name
    -----------------
    mkCcRegister ccs import_names
      = let
	    register_ccs     = mkAbstractCs (map mk_register ccs)
	    register_imports
	      = foldr (mkAbsCStmts . mk_import_register) AbsCNop import_names
	in
	mkAbstractCs [
	    CCallProfCCMacro SLIT("START_REGISTER_CCS") [CLitLit (modnameToC (SLIT("_reg") _APPEND_ mod_name)) AddrRep],
	    register_ccs,
	    register_imports,
	    CCallProfCCMacro SLIT("END_REGISTER_CCS") []
	]
      where
	mk_register cc
	  = CCallProfCCMacro SLIT("REGISTER_CC") [mkCCostCentre cc]
	mk_import_register import_name
	  = CCallProfCCMacro SLIT("REGISTER_IMPORT") [CLitLit (modnameToC (SLIT("_reg") _APPEND_ import_name)) AddrRep]
\end{code}
%************************************************************************
%*									*
\subsection[codegen-top-bindings]{Converting top-level STG bindings}
%*									*
%************************************************************************
@cgTopBindings@ is only used for top-level bindings, since they need
to be allocated statically (not in the heap) and need to be labelled.
No unboxed bindings can happen at top level.
In the code below, the static bindings are accumulated in the
@MkCgState@, and transferred into the ``statics'' slot by @forkStatics@.
This is so that we can write the top level processing in a compositional
style, with the increasing static environment being plumbed as a state
variable.
\begin{code}
cgTopBindings :: AbstractC -> [StgBinding] -> Code
cgTopBindings split bindings = mapCs (cgTopBinding split) bindings
cgTopBinding :: AbstractC -> StgBinding -> Code
cgTopBinding split (StgNonRec name rhs)
  = absC split		`thenC`
    cgTopRhs name rhs	`thenFC` \ (name, info) ->
    addBindC name info
cgTopBinding split (StgRec pairs)
  = absC split		`thenC`
    fixC (\ new_binds -> addBindsC new_binds	`thenC`
			 mapFCs ( \ (b,e) -> cgTopRhs b e ) pairs
    )			`thenFC` \ new_binds ->
    addBindsC new_binds
-- Urgh!  I tried moving the forkStatics call from the rhss of cgTopRhs
-- to enclose the listFCs in cgTopBinding, but that tickled the
-- statics "error" call in initC.  I DON'T UNDERSTAND WHY!
cgTopRhs :: Id -> StgRhs -> FCode (Id, CgIdInfo)
	-- the Id is passed along for setting up a binding...
cgTopRhs name (StgRhsCon cc con args)
  = forkStatics (cgTopRhsCon name con args (all zero_size args))
  where
    zero_size atom = getPrimRepSize (getArgPrimRep atom) == 0
cgTopRhs name (StgRhsClosure cc bi fvs upd_flag args body)
  = ASSERT(null fvs) -- There should be no free variables
    forkStatics (cgTopRhsClosure name cc bi args body lf_info)
  where
    lf_info = mkClosureLFInfo True{-top level-} [{-no fvs-}] upd_flag args
\end{code}
 |