summaryrefslogtreecommitdiff
path: root/ghc/compiler/codeGen/CgExpr.lhs
blob: 5974df641d4a895543e6e614b2b4be8fa7c6c1e6 (plain)
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
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
%
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1995
%
%********************************************************
%*							*
\section[CgExpr]{Converting @StgExpr@s}
%*							*
%********************************************************

\begin{code}
#include "HsVersions.h"

module CgExpr (
	cgExpr, cgSccExpr, getPrimOpArgAmodes,

	-- and to make the interface self-sufficient...
	StgExpr, Id, CgState
    ) where

IMPORT_Trace		-- NB: not just for debugging
import Outputable	-- ToDo: rm (just for debugging)
import Pretty		-- ToDo: rm (just for debugging)

import StgSyn
import CgMonad
import AbsCSyn

import AbsPrel		( PrimOp(..), PrimOpResultInfo(..), HeapRequirement(..), 
    	    	    	  primOpHeapReq, getPrimOpResultInfo, PrimKind, 
    	    	    	  primOpCanTriggerGC
			  IF_ATTACK_PRAGMAS(COMMA tagOf_PrimOp)
			  IF_ATTACK_PRAGMAS(COMMA pprPrimOp)
			)
import AbsUniType	( isPrimType, getTyConDataCons )
import CLabelInfo	( CLabel, mkPhantomInfoTableLabel, mkInfoTableVecTblLabel )
import ClosureInfo	( LambdaFormInfo, mkClosureLFInfo )
import CgBindery	( getAtomAmodes )
import CgCase		( cgCase, saveVolatileVarsAndRegs )
import CgClosure	( cgRhsClosure )
import CgCon		( buildDynCon, cgReturnDataCon )
import CgHeapery	( allocHeap )
import CgLetNoEscape	( cgLetNoEscapeClosure )
import CgRetConv	-- various things...
import CgTailCall	( cgTailCall, performReturn, mkDynamicAlgReturnCode,
                          mkPrimReturnCode
                        )
import CostCentre	( setToAbleCostCentre, isDupdCC, CostCentre )
import Maybes		( Maybe(..) )
import PrimKind		( getKindSize )
import UniqSet
import Util
\end{code}

This module provides the support code for @StgToAbstractC@ to deal
with STG {\em expressions}.  See also @CgClosure@, which deals
with closures, and @CgCon@, which deals with constructors.

\begin{code}
cgExpr	:: PlainStgExpr		-- input
	-> Code			-- output
\end{code}

%********************************************************
%*							*
%*		Tail calls				*
%*							*
%********************************************************

``Applications'' mean {\em tail calls}, a service provided by module
@CgTailCall@.  This includes literals, which show up as
@(STGApp (StgLitAtom 42) [])@.

\begin{code}
cgExpr (StgApp fun args live_vars) = cgTailCall fun args live_vars
\end{code}

%********************************************************
%*							*
%*		STG ConApps  (for inline versions)	*
%*							*
%********************************************************

\begin{code}
cgExpr (StgConApp con args live_vars)
  = getAtomAmodes args `thenFC` \ amodes ->
    cgReturnDataCon con amodes (all zero_size args) live_vars
  where
    zero_size atom = getKindSize (getAtomKind atom) == 0
\end{code}

%********************************************************
%*							*
%*		STG PrimApps  (unboxed primitive ops)	*
%*							*
%********************************************************

Here is where we insert real live machine instructions.

\begin{code}
cgExpr x@(StgPrimApp op args live_vars)
  = -- trace ("cgExpr:PrimApp:"++(ppShow 80 (ppr PprDebug x))) (
    getPrimOpArgAmodes op args			`thenFC` \ arg_amodes ->
    let
	result_regs   = assignPrimOpResultRegs op
	result_amodes = map CReg result_regs
	may_gc  = primOpCanTriggerGC op
	dyn_tag = head result_amodes
	    -- The tag from a primitive op returning an algebraic data type
	    -- is returned in the first result_reg_amode
    in
    (if may_gc then
	-- Use registers for args, and assign args to the regs
	-- (Can-trigger-gc primops guarantee to have their args in regs)
	let
	    (arg_robust_amodes, liveness_mask, arg_assts) 
	      = makePrimOpArgsRobust op arg_amodes

	    liveness_arg = mkIntCLit liveness_mask
	in
 	returnFC (
	    arg_assts,
	    mkAbstractCs [
	      spat_prim_macro,
	      COpStmt result_amodes op
		      (pin_liveness op liveness_arg arg_robust_amodes)
		      liveness_mask
		      [{-no vol_regs-}],
	      spat_prim_stop_macro ]
	)
     else
	-- Use args from their current amodes.
	let
	  liveness_mask = panic "cgExpr: liveness of non-GC-ing primop touched\n"
	in
 	returnFC (
--	  DO NOT want CCallProfMacros in CSimultaneous stuff.  Yurgh.  (WDP 95/01)
--		Arises in compiling PreludeGlaST (and elsewhere??)
--	  mkAbstractCs [
--	    spat_prim_macro,
	    COpStmt result_amodes op arg_amodes liveness_mask [{-no vol_regs-}],
--	    spat_prim_stop_macro ],
	  AbsCNop
	)
    )				`thenFC` \ (do_before_stack_cleanup,
					     do_just_before_jump) ->

    case (getPrimOpResultInfo op) of

	ReturnsPrim kind ->
	    performReturn do_before_stack_cleanup
    	    	    	  (\ sequel -> robustifySequel may_gc sequel	
							`thenFC` \ (ret_asst, sequel') ->
			   absC (ret_asst `mkAbsCStmts` do_just_before_jump)
							`thenC`
			   mkPrimReturnCode sequel')
			  live_vars

	ReturnsAlg tycon ->
--OLD:	    evalCostCentreC "SET_RetCC" [CReg CurCostCentre]	`thenC`	
	    profCtrC SLIT("RET_NEW_IN_REGS") []			`thenC`

	    performReturn do_before_stack_cleanup
			  (\ sequel -> robustifySequel may_gc sequel
						    	`thenFC` \ (ret_asst, sequel') ->
			   absC (mkAbstractCs [ret_asst, 
                                               do_just_before_jump, 
					       info_ptr_assign])
			-- Must load info ptr here, not in do_just_before_stack_cleanup,
			-- because the info-ptr reg clashes with argument registers
			-- for the primop
								`thenC`
				      mkDynamicAlgReturnCode tycon dyn_tag sequel')
			  live_vars
	    where

	    -- Here, the destination _can_ be an update frame, so we need to make sure that
	    -- infoptr (R2) is loaded with the constructor's info ptr.

		info_ptr_assign = CAssign (CReg infoptr) info_lbl

		info_lbl
		  = -- OLD: pprTrace "ctrlReturn7:" (ppr PprDebug tycon) (
		    case (ctrlReturnConvAlg tycon) of
		      VectoredReturn _   -> vec_lbl
		      UnvectoredReturn _ -> dir_lbl
		    -- )

	        vec_lbl  = CTableEntry (CLbl (mkInfoTableVecTblLabel tycon) DataPtrKind) 
    	    	    	        dyn_tag DataPtrKind

		data_con = head (getTyConDataCons tycon)
		dir_lbl  = case dataReturnConvAlg data_con of
    	    		    	ReturnInRegs _ -> CLbl (mkPhantomInfoTableLabel data_con) 
						       DataPtrKind
    	    	    		ReturnInHeap   -> panic "CgExpr: can't return prim in heap"
					  -- Never used, and no point in generating
					  -- the code for it!
  where
    -- for all PrimOps except ccalls, we pin the liveness info
    -- on as the first "argument"
    -- ToDo: un-duplicate?

    pin_liveness (CCallOp _ _ _ _ _) _ args = args
    pin_liveness other_op liveness_arg args
      = liveness_arg :args

    -- We only need to worry about the sequel when we may GC and the
    -- sequel is OnStack.  If that's the case, arrange to pull the
    -- sequel out into RetReg before performing the primOp.

    robustifySequel True sequel@(OnStack _) = 
	sequelToAmode sequel			`thenFC` \ amode ->
	returnFC (CAssign (CReg RetReg) amode, InRetReg)
    robustifySequel _ sequel = returnFC (AbsCNop, sequel)
    
    spat_prim_macro	 = CCallProfCtrMacro SLIT("SET_ACTIVITY") [CLitLit SLIT("ACT_PRIM") IntKind]
    spat_prim_stop_macro = CCallProfCtrMacro SLIT("SET_ACTIVITY") [CLitLit SLIT("ACT_PRIM_STOP") IntKind]

\end{code}

%********************************************************
%*							*
%*		Case expressions			*
%*							*
%********************************************************
Case-expression conversion is complicated enough to have its own
module, @CgCase@.
\begin{code}

cgExpr (StgCase expr live_vars save_vars uniq alts)
  = cgCase expr live_vars save_vars uniq alts
\end{code}


%********************************************************
%*							*
%* 		Let and letrec				*
%*							*
%********************************************************
\subsection[let-and-letrec-codegen]{Converting @StgLet@ and @StgLetrec@}

\begin{code}
cgExpr (StgLet (StgNonRec name rhs) expr)
  = cgRhs name rhs	`thenFC` \ (name, info) ->
    addBindC name info 	`thenC`
    cgExpr expr

cgExpr (StgLet (StgRec pairs) expr)
  = fixC (\ new_bindings -> addBindsC new_bindings `thenC`
			    listFCs [ cgRhs b e | (b,e) <- pairs ]
    ) `thenFC` \ new_bindings ->

    addBindsC new_bindings `thenC`
    cgExpr expr
\end{code}

\begin{code}
cgExpr (StgLetNoEscape live_in_whole_let live_in_rhss bindings body)
  =    	-- Figure out what volatile variables to save
    nukeDeadBindings live_in_whole_let	`thenC`
    saveVolatileVarsAndRegs live_in_rhss 
    	    `thenFC` \ (save_assts, rhs_eob_info, maybe_cc_slot) ->

	-- ToDo: cost centre???

	-- Save those variables right now!	
    absC save_assts				`thenC`

	-- Produce code for the rhss
	-- and add suitable bindings to the environment
    cgLetNoEscapeBindings live_in_rhss rhs_eob_info maybe_cc_slot bindings `thenC`

	-- Do the body
    setEndOfBlockInfo rhs_eob_info (cgExpr body)
\end{code}


%********************************************************
%*							*
%*		SCC Expressions				*
%*							*
%********************************************************
\subsection[scc-codegen]{Converting StgSCC}

SCC expressions are treated specially. They set the current cost
centre.

For evaluation scoping we also need to save the cost centre in an
``restore CC frame''. We only need to do this once before setting all
nested SCCs.

\begin{code}
cgExpr scc_expr@(StgSCC ty cc expr)
--OLD:WDP:94/06  = evalPushRCCFrame (isPrimType ty) (cgSccExpr scc_expr)
  = cgSccExpr scc_expr
\end{code}

@cgSccExpr@ (also used in \tr{CgClosure}):
We *don't* set the cost centre for CAF/Dict cost centres
[Likewise Subsumed and NoCostCentre, but they probably
don't exist in an StgSCC expression.]
\begin{code}
cgSccExpr (StgSCC ty cc expr)
  = (if setToAbleCostCentre cc then
	costCentresC SLIT("SET_CCC")
	    [mkCCostCentre cc, mkIntCLit (if isDupdCC cc then 1 else 0)]
     else
	nopC)		`thenC`
    cgSccExpr expr
cgSccExpr other
  = cgExpr other
\end{code}

%********************************************************
%*							*
%*		Non-top-level bindings			*
%*							*
%********************************************************
\subsection[non-top-level-bindings]{Converting non-top-level bindings}

@cgBinding@ is only used for let/letrec, not for unboxed bindings.
So the kind should always be @PtrKind@.

We rely on the support code in @CgCon@ (to do constructors) and
in @CgClosure@ (to do closures).

\begin{code}
cgRhs :: Id -> PlainStgRhs -> FCode (Id, CgIdInfo)
	-- the Id is passed along so a binding can be set up

cgRhs name (StgRhsCon maybe_cc con args)
  = getAtomAmodes args		`thenFC` \ amodes ->
    buildDynCon name maybe_cc con amodes (all zero_size args)
				`thenFC` \ idinfo ->
    returnFC (name, idinfo)
  where
    zero_size atom = getKindSize (getAtomKind atom) == 0

cgRhs name (StgRhsClosure cc bi fvs upd_flag args body)
  = cgRhsClosure name cc bi fvs args body lf_info
  where
    lf_info = mkClosureLFInfo False{-not top level-} fvs upd_flag args body
\end{code}

\begin{code}
cgLetNoEscapeBindings live_in_rhss rhs_eob_info maybe_cc_slot (StgNonRec binder rhs)
  = cgLetNoEscapeRhs live_in_rhss rhs_eob_info maybe_cc_slot binder rhs	
    	    	    	    	`thenFC` \ (binder, info) ->
    addBindC binder info

cgLetNoEscapeBindings live_in_rhss rhs_eob_info maybe_cc_slot (StgRec pairs)
  = fixC (\ new_bindings ->
		addBindsC new_bindings 	`thenC`
		listFCs [ cgLetNoEscapeRhs full_live_in_rhss rhs_eob_info 
                          maybe_cc_slot b e | (b,e) <- pairs ]
    ) `thenFC` \ new_bindings ->

    addBindsC new_bindings
  where
    -- We add the binders to the live-in-rhss set so that we don't
    -- delete the bindings for the binder from the environment!
    full_live_in_rhss = live_in_rhss `unionUniqSets` (mkUniqSet [b | (b,r) <- pairs])

cgLetNoEscapeRhs 
    :: PlainStgLiveVars	-- Live in rhss
    -> EndOfBlockInfo 
    -> Maybe VirtualSpBOffset
    -> Id
    -> PlainStgRhs
    -> FCode (Id, CgIdInfo)

cgLetNoEscapeRhs full_live_in_rhss rhs_eob_info maybe_cc_slot binder
		 (StgRhsClosure cc bi _ upd_flag args body)
  = -- We could check the update flag, but currently we don't switch it off
    -- for let-no-escaped things, so we omit the check too!
    -- case upd_flag of
    --     Updatable -> panic "cgLetNoEscapeRhs"	-- Nothing to update!
    --     other     -> cgLetNoEscapeClosure binder cc bi live_in_whole_let live_in_rhss args body
    cgLetNoEscapeClosure binder cc bi full_live_in_rhss rhs_eob_info maybe_cc_slot args body

-- For a constructor RHS we want to generate a single chunk of code which 
-- can be jumped to from many places, which will return the constructor.
-- It's easy; just behave as if it was an StgRhsClosure with a ConApp inside!
cgLetNoEscapeRhs full_live_in_rhss rhs_eob_info maybe_cc_slot binder
    	    	 (StgRhsCon cc con args)
  = cgLetNoEscapeClosure binder cc stgArgOcc{-safe-} full_live_in_rhss rhs_eob_info maybe_cc_slot
	[] 	--No args; the binder is data structure, not a function
	(StgConApp con args full_live_in_rhss)
\end{code}

Some PrimOps require a {\em fixed} amount of heap allocation.  Rather
than tidy away ready for GC and do a full heap check, we simply
allocate a completely uninitialised block in-line, just like any other
thunk/constructor allocation, and pass it to the PrimOp as its first
argument.  Remember! The PrimOp is entirely responsible for
initialising the object.  In particular, the PrimOp had better not
trigger GC before it has filled it in, and even then it had better
make sure that the GC can find the object somehow.

Main current use: allocating SynchVars.

\begin{code}
getPrimOpArgAmodes op args
  = getAtomAmodes args		`thenFC` \ arg_amodes ->

    case primOpHeapReq op of

	FixedHeapRequired size -> allocHeap size `thenFC` \ amode ->
     	    	    	    	  returnFC (amode : arg_amodes)

	_   	    	       -> returnFC arg_amodes    
\end{code}