2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
7 module CgCase ( cgCase, saveVolatileVarsAndRegs,
8 restoreCurrentCostCentre
11 #include "HsVersions.h"
13 import {-# SOURCE #-} CgExpr ( cgExpr )
45 import Control.Monad (when)
50 = GCMayHappen -- The scrutinee may involve GC, so everything must be
51 -- tidy before the code for the scrutinee.
53 | NoGC -- The scrutinee is a primitive value, or a call to a
54 -- primitive op which does no GC. Hence the case can
55 -- be done inline, without tidying up first.
58 It is quite interesting to decide whether to put a heap-check
59 at the start of each alternative. Of course we certainly have
60 to do so if the case forces an evaluation, or if there is a primitive
61 op which can trigger GC.
63 A more interesting situation is this:
70 default -> !C!; ...C...
73 where \tr{!x!} indicates a possible heap-check point. The heap checks
74 in the alternatives {\em can} be omitted, in which case the topmost
75 heapcheck will take their worst case into account.
77 In favour of omitting \tr{!B!}, \tr{!C!}:
79 - {\em May} save a heap overflow test,
80 if ...A... allocates anything. The other advantage
81 of this is that we can use relative addressing
82 from a single Hp to get at all the closures so allocated.
84 - No need to save volatile vars etc across the case
88 - May do more allocation than reqd. This sometimes bites us
89 badly. For example, nfib (ha!) allocates about 30\% more space if the
90 worst-casing is done, because many many calls to nfib are leaf calls
91 which don't need to allocate anything.
93 This never hurts us if there is only one alternative.
105 Special case #1: case of literal.
108 cgCase (StgLit lit) _live_in_whole_case _live_in_alts bndr
109 alt_type@(PrimAlt _) alts
110 = do { tmp_reg <- bindNewToTemp bndr
111 ; cm_lit <- cgLit lit
112 ; stmtC (CmmAssign (CmmLocal tmp_reg) (CmmLit cm_lit))
113 ; cgPrimAlts NoGC alt_type (CmmLocal tmp_reg) alts }
116 Special case #2: scrutinising a primitive-typed variable. No
117 evaluation required. We don't save volatile variables, nor do we do a
118 heap-check in the alternatives. Instead, the heap usage of the
119 alternatives is worst-cased and passed upstream. This can result in
120 allocating more heap than strictly necessary, but it will sometimes
121 eliminate a heap check altogether.
124 cgCase (StgApp v []) _live_in_whole_case _live_in_alts bndr
125 alt_type@(PrimAlt _) alts
126 -- Note [ticket #3132]: we might be looking at a case of a lifted Id
127 -- that was cast to an unlifted type. The Id will always be bottom,
128 -- but we don't want the code generator to fall over here. If we
129 -- just emit an assignment here, the assignment will be
130 -- type-incorrect Cmm. Hence we check that the types match, and if
131 -- they don't we'll fall through and emit the usual enter/return
132 -- code. Test case: codeGen/should_compile/3132.hs
133 | isUnLiftedType (idType v)
135 -- However, we also want to allow an assignment to be generated
136 -- in the case when the types are compatible, because this allows
137 -- some slightly-dodgy but occasionally-useful casts to be used,
138 -- such as in RtClosureInspect where we cast an HValue to a MutVar#
139 -- so we can print out the contents of the MutVar#. If we generate
140 -- code that enters the HValue, then we'll get a runtime panic, because
141 -- the HValue really is a MutVar#. The types are compatible though,
142 -- so we can just generate an assignment.
145 do { -- Careful! we can't just bind the default binder to the same thing
146 -- as the scrutinee, since it might be a stack location, and having
147 -- two bindings pointing at the same stack locn doesn't work (it
148 -- confuses nukeDeadBindings). Hence, use a new temp.
149 when (not reps_compatible) $
150 panic "cgCase: reps do not match, perhaps a dodgy unsafeCoerce?"
151 ; v_info <- getCgIdInfo v
152 ; amode <- idInfoToAmode v_info
153 ; tmp_reg <- bindNewToTemp bndr
154 ; stmtC (CmmAssign (CmmLocal tmp_reg) amode)
155 ; cgPrimAlts NoGC alt_type (CmmLocal tmp_reg) alts }
157 reps_compatible = idCgRep v == idCgRep bndr
160 Special case #3: inline PrimOps and foreign calls.
163 cgCase (StgOpApp (StgPrimOp primop) args _)
164 _live_in_whole_case live_in_alts bndr alt_type alts
165 | not (primOpOutOfLine primop)
166 = cgInlinePrimOp primop args bndr alt_type live_in_alts alts
169 TODO: Case-of-case of primop can probably be done inline too (but
170 maybe better to translate it out beforehand). See
171 ghc/lib/misc/PackedString.lhs for examples where this crops up (with
174 Special case #4: inline foreign calls: an unsafe foreign call can be done
175 right here, just like an inline primop.
178 cgCase (StgOpApp (StgFCallOp fcall _) args _)
179 _live_in_whole_case live_in_alts _bndr _alt_type alts
180 | unsafe_foreign_call
181 = ASSERT( isSingleton alts )
182 do -- *must* be an unboxed tuple alt.
183 -- exactly like the cgInlinePrimOp case for unboxed tuple alts..
184 { res_tmps <- mapFCs bindNewToTemp non_void_res_ids
185 ; let res_hints = map (typeForeignHint.idType) non_void_res_ids
186 ; cgForeignCall (zipWith CmmHinted res_tmps res_hints) fcall args live_in_alts
189 (_, res_ids, _, rhs) = head alts
190 non_void_res_ids = filter (nonVoidArg . idCgRep) res_ids
194 CCall (CCallSpec _ _ s) -> not (playSafe s)
197 Special case: scrutinising a non-primitive variable.
198 This can be done a little better than the general case, because
199 we can reuse/trim the stack slot holding the variable (if it is in one).
202 cgCase (StgApp fun args)
203 _live_in_whole_case live_in_alts bndr alt_type alts
204 = do { fun_info <- getCgIdInfo fun
205 ; arg_amodes <- getArgAmodes args
207 -- Nuking dead bindings *before* calculating the saves is the
208 -- value-add here. We might end up freeing up some slots currently
209 -- occupied by variables only required for the call.
210 -- NOTE: we need to look up the variables used in the call before
211 -- doing this, because some of them may not be in the environment
213 ; nukeDeadBindings live_in_alts
214 ; (save_assts, alts_eob_info, maybe_cc_slot)
215 <- saveVolatileVarsAndRegs live_in_alts
218 <- forkEval alts_eob_info
219 (allocStackTop retAddrSizeW >> nopC)
220 (do { deAllocStackTop retAddrSizeW
221 ; cgEvalAlts maybe_cc_slot bndr alt_type alts })
223 ; setEndOfBlockInfo scrut_eob_info
224 (performTailCall fun_info arg_amodes save_assts) }
227 Note about return addresses: we *always* push a return address, even
228 if because of an optimisation we end up jumping direct to the return
229 code (not through the address itself). The alternatives always assume
230 that the return address is on the stack. The return address is
231 required in case the alternative performs a heap check, since it
232 encodes the liveness of the slots in the activation record.
234 On entry to the case alternative, we can re-use the slot containing
235 the return address immediately after the heap check. That's what the
236 deAllocStackTop call is doing above.
238 Finally, here is the general case.
241 cgCase expr live_in_whole_case live_in_alts bndr alt_type alts
242 = do { -- Figure out what volatile variables to save
243 nukeDeadBindings live_in_whole_case
245 ; (save_assts, alts_eob_info, maybe_cc_slot)
246 <- saveVolatileVarsAndRegs live_in_alts
248 -- Save those variables right now!
249 ; emitStmts save_assts
251 -- generate code for the alts
253 <- forkEval alts_eob_info
254 (do { nukeDeadBindings live_in_alts
255 ; allocStackTop retAddrSizeW -- space for retn address
257 (do { deAllocStackTop retAddrSizeW
258 ; cgEvalAlts maybe_cc_slot bndr alt_type alts })
260 ; setEndOfBlockInfo scrut_eob_info (cgExpr expr)
264 There's a lot of machinery going on behind the scenes to manage the
265 stack pointer here. forkEval takes the virtual Sp and free list from
266 the first argument, and turns that into the *real* Sp for the second
267 argument. It also uses this virtual Sp as the args-Sp in the EOB info
268 returned, so that the scrutinee will trim the real Sp back to the
269 right place before doing whatever it does.
270 --SDM (who just spent an hour figuring this out, and didn't want to
273 Why don't we push the return address just before evaluating the
274 scrutinee? Because the slot reserved for the return address might
275 contain something useful, so we wait until performing a tail call or
276 return before pushing the return address (see
277 CgTailCall.pushReturnAddress).
279 This also means that the environment doesn't need to know about the
280 free stack slot for the return address (for generating bitmaps),
281 because we don't reserve it until just before the eval.
283 TODO!! Problem: however, we have to save the current cost centre
284 stack somewhere, because at the eval point the current CCS might be
285 different. So we pick a free stack slot and save CCCS in it. One
286 consequence of this is that activation records on the stack don't
287 follow the layout of closures when we're profiling. The CCS could be
288 anywhere within the record).
290 %************************************************************************
294 %************************************************************************
297 cgInlinePrimOp :: PrimOp -> [StgArg] -> Id -> AltType -> StgLiveVars
298 -> [(AltCon, [Id], [Bool], StgExpr)]
300 cgInlinePrimOp primop args bndr (PrimAlt _) live_in_alts alts
301 | isVoidArg (idCgRep bndr)
302 = ASSERT( con == DEFAULT && isSingleton alts && null bs )
303 do { -- VOID RESULT; just sequencing,
304 -- so get in there and do it
305 cgPrimOp [] primop args live_in_alts
308 (con,bs,_,rhs) = head alts
310 cgInlinePrimOp primop args bndr (PrimAlt tycon) live_in_alts alts
311 = do { -- PRIMITIVE ALTS, with non-void result
312 tmp_reg <- bindNewToTemp bndr
313 ; cgPrimOp [tmp_reg] primop args live_in_alts
314 ; cgPrimAlts NoGC (PrimAlt tycon) (CmmLocal tmp_reg) alts }
316 cgInlinePrimOp primop args _ (UbxTupAlt _) live_in_alts alts
317 = ASSERT( isSingleton alts )
318 do { -- UNBOXED TUPLE ALTS
319 -- No heap check, no yield, just get in there and do it.
320 -- NB: the case binder isn't bound to anything;
321 -- it has a unboxed tuple type
323 res_tmps <- mapFCs bindNewToTemp non_void_res_ids
324 ; cgPrimOp res_tmps primop args live_in_alts
327 (_, res_ids, _, rhs) = head alts
328 non_void_res_ids = filter (nonVoidArg . idCgRep) res_ids
330 cgInlinePrimOp primop args bndr (AlgAlt tycon) live_in_alts alts
331 = do { -- ENUMERATION TYPE RETURN
332 -- Typical: case a ># b of { True -> ..; False -> .. }
333 -- The primop itself returns an index into the table of
334 -- closures for the enumeration type.
335 tag_amode <- ASSERT( isEnumerationTyCon tycon )
336 do_enum_primop primop
338 -- Bind the default binder if necessary
339 -- (avoiding it avoids the assignment)
340 -- The deadness info is set by StgVarInfo
341 ; whenC (not (isDeadBinder bndr))
342 (do { tmp_reg <- bindNewToTemp bndr
345 (tagToClosure tycon tag_amode)) })
348 ; (branches, mb_deflt) <- cgAlgAlts NoGC Nothing{-cc_slot-}
352 ; emitSwitch tag_amode branches mb_deflt 0 (tyConFamilySize tycon - 1)
356 do_enum_primop :: PrimOp -> FCode CmmExpr -- Returns amode for result
357 do_enum_primop TagToEnumOp -- No code!
359 (_,e) <- getArgAmode arg
361 do_enum_primop primop
362 = do tmp <- newTemp bWord
363 cgPrimOp [tmp] primop args live_in_alts
364 returnFC (CmmReg (CmmLocal tmp))
366 cgInlinePrimOp _ _ bndr _ _ _
367 = pprPanic "cgCase: case of primop has polymorphic type" (ppr bndr)
370 %************************************************************************
372 \subsection[CgCase-alts]{Alternatives}
374 %************************************************************************
376 @cgEvalAlts@ returns an addressing mode for a continuation for the
377 alternatives of a @case@, used in a context when there
378 is some evaluation to be done.
381 cgEvalAlts :: Maybe VirtualSpOffset -- Offset of cost-centre to be restored, if any
385 -> FCode Sequel -- Any addr modes inside are guaranteed
386 -- to be a label so that we can duplicate it
387 -- without risk of duplicating code
389 cgEvalAlts cc_slot bndr alt_type@(PrimAlt tycon) alts
390 = do { let rep = tyConCgRep tycon
391 reg = dataReturnConvPrim rep -- Bottom for voidRep
393 ; abs_c <- forkProc $ do
394 { -- Bind the case binder, except if it's void
395 -- (reg is bottom in that case)
396 whenC (nonVoidArg rep) $
397 bindNewToReg bndr reg (mkLFArgument bndr)
398 ; restoreCurrentCostCentre cc_slot True
399 ; cgPrimAlts GCMayHappen alt_type reg alts }
401 ; lbl <- emitReturnTarget (idName bndr) abs_c
402 ; returnFC (CaseAlts lbl Nothing bndr) }
404 cgEvalAlts cc_slot bndr (UbxTupAlt _) [(con,args,_,rhs)]
405 = -- Unboxed tuple case
406 -- By now, the simplifier should have have turned it
407 -- into case e of (# a,b #) -> e
408 -- There shouldn't be a
409 -- case e of DEFAULT -> e
410 ASSERT2( case con of { DataAlt _ -> True; _ -> False },
411 text "cgEvalAlts: dodgy case of unboxed tuple type" )
412 do { -- forkAbsC for the RHS, so that the envt is
413 -- not changed for the emitReturn call
414 abs_c <- forkProc $ do
415 { (live_regs, ptrs, nptrs, _) <- bindUnboxedTupleComponents args
416 -- Restore the CC *after* binding the tuple components,
417 -- so that we get the stack offset of the saved CC right.
418 ; restoreCurrentCostCentre cc_slot True
419 -- Generate a heap check if necessary
420 -- and finally the code for the alternative
421 ; unbxTupleHeapCheck live_regs ptrs nptrs noStmts
423 ; lbl <- emitReturnTarget (idName bndr) abs_c
424 ; returnFC (CaseAlts lbl Nothing bndr) }
426 cgEvalAlts cc_slot bndr alt_type alts
427 = -- Algebraic and polymorphic case
428 do { -- Bind the default binder
429 bindNewToReg bndr nodeReg (mkLFArgument bndr)
431 -- Generate sequel info for use downstream
432 -- At the moment, we only do it if the type is vector-returnable.
433 -- Reason: if not, then it costs extra to label the
434 -- alternatives, because we'd get return code like:
436 -- switch TagReg { 0 : JMP(alt_1); 1 : JMP(alt_2) ..etc }
438 -- which is worse than having the alt code in the switch statement
440 ; (alts, mb_deflt) <- cgAlgAlts GCMayHappen cc_slot alt_type alts
442 ; (lbl, branches) <- emitAlgReturnTarget (idName bndr)
445 ; returnFC (CaseAlts lbl branches bndr) }
447 fam_sz = case alt_type of
448 AlgAlt tc -> tyConFamilySize tc
450 PrimAlt _ -> panic "cgEvalAlts: PrimAlt"
451 UbxTupAlt _ -> panic "cgEvalAlts: UbxTupAlt"
455 HWL comment on {\em GrAnSim\/} (adding GRAN_YIELDs for context switch): If
456 we do an inlining of the case no separate functions for returning are
457 created, so we don't have to generate a GRAN_YIELD in that case. This info
458 must be propagated to cgAlgAltRhs (where the GRAN_YIELD macro might be
459 emitted). Hence, the new Bool arg to cgAlgAltRhs.
461 %************************************************************************
463 \subsection[CgCase-alg-alts]{Algebraic alternatives}
465 %************************************************************************
467 In @cgAlgAlts@, none of the binders in the alternatives are
468 assumed to be yet bound.
470 HWL comment on {\em GrAnSim\/} (adding GRAN_YIELDs for context switch): The
471 last arg of cgAlgAlts indicates if we want a context switch at the
472 beginning of each alternative. Normally we want that. The only exception
473 are inlined alternatives.
477 -> Maybe VirtualSpOffset
478 -> AltType -- ** AlgAlt or PolyAlt only **
479 -> [StgAlt] -- The alternatives
480 -> FCode ( [(ConTagZ, CgStmts)], -- The branches
481 Maybe CgStmts ) -- The default case
483 cgAlgAlts gc_flag cc_slot alt_type alts
484 = do alts <- forkAlts [ cgAlgAlt gc_flag cc_slot alt_type alt | alt <- alts]
486 mb_deflt = case alts of -- DEFAULT is always first, if present
487 ((DEFAULT,blks) : _) -> Just blks
490 branches = [(dataConTagZ con, blks)
491 | (DataAlt con, blks) <- alts]
493 return (branches, mb_deflt)
497 -> Maybe VirtualSpOffset -- Turgid state
498 -> AltType -- ** AlgAlt or PolyAlt only **
500 -> FCode (AltCon, CgStmts)
502 cgAlgAlt gc_flag cc_slot alt_type (con, args, _use_mask, rhs)
503 = do { abs_c <- getCgStmts $ do
504 { bind_con_args con args
505 ; restoreCurrentCostCentre cc_slot True
506 ; maybeAltHeapCheck gc_flag alt_type (cgExpr rhs) }
507 ; return (con, abs_c) }
509 bind_con_args DEFAULT _ = nopC
510 bind_con_args (DataAlt dc) args = bindConArgs dc args
511 bind_con_args (LitAlt _) _ = panic "cgAlgAlt: LitAlt"
515 %************************************************************************
517 \subsection[CgCase-prim-alts]{Primitive alternatives}
519 %************************************************************************
521 @cgPrimAlts@ generates suitable a @CSwitch@
522 for dealing with the alternatives of a primitive @case@, given an
523 addressing mode for the thing to scrutinise. It also keeps track of
524 the maximum stack depth encountered down any branch.
526 As usual, no binders in the alternatives are yet bound.
530 -> AltType -- Always PrimAlt, but passed to maybeAltHeapCheck
531 -> CmmReg -- Scrutinee
532 -> [StgAlt] -- Alternatives
534 -- NB: cgPrimAlts emits code that does the case analysis.
535 -- It's often used in inline situations, rather than to genearte
536 -- a labelled return point. That's why its interface is a little
537 -- different to cgAlgAlts
539 -- INVARIANT: the default binder is already bound
540 cgPrimAlts gc_flag alt_type scrutinee alts
541 = do { tagged_absCs <- forkAlts (map (cgPrimAlt gc_flag alt_type) alts)
542 ; let ((DEFAULT, deflt_absC) : others) = tagged_absCs -- There is always a default
543 alt_absCs = [(lit,rhs) | (LitAlt lit, rhs) <- others]
544 ; emitLitSwitch (CmmReg scrutinee) alt_absCs deflt_absC }
548 -> StgAlt -- The alternative
549 -> FCode (AltCon, CgStmts) -- Its compiled form
551 cgPrimAlt gc_flag alt_type (con, [], [], rhs)
552 = ASSERT( case con of { DEFAULT -> True; LitAlt _ -> True; _ -> False } )
553 do { abs_c <- getCgStmts (maybeAltHeapCheck gc_flag alt_type (cgExpr rhs))
554 ; returnFC (con, abs_c) }
555 cgPrimAlt _ _ _ = panic "cgPrimAlt: non-empty lists"
559 %************************************************************************
561 \subsection[CgCase-tidy]{Code for tidying up prior to an eval}
563 %************************************************************************
568 -> AltType -- PolyAlt, PrimAlt, AlgAlt, but *not* UbxTupAlt
569 -> Code -- Continuation
571 maybeAltHeapCheck NoGC _ code = code
572 maybeAltHeapCheck GCMayHappen alt_type code = altHeapCheck alt_type code
574 saveVolatileVarsAndRegs
575 :: StgLiveVars -- Vars which should be made safe
576 -> FCode (CmmStmts, -- Assignments to do the saves
577 EndOfBlockInfo, -- sequel for the alts
578 Maybe VirtualSpOffset) -- Slot for current cost centre
580 saveVolatileVarsAndRegs vars
581 = do { var_saves <- saveVolatileVars vars
582 ; (maybe_cc_slot, cc_save) <- saveCurrentCostCentre
583 ; eob_info <- getEndOfBlockInfo
584 ; returnFC (var_saves `plusStmts` cc_save,
589 saveVolatileVars :: StgLiveVars -- Vars which should be made safe
590 -> FCode CmmStmts -- Assignments to to the saves
592 saveVolatileVars vars
593 = do { stmts_s <- mapFCs save_it (varSetElems vars)
594 ; return (foldr plusStmts noStmts stmts_s) }
597 = do { v <- getCAddrModeIfVolatile var
599 Nothing -> return noStmts -- Non-volatile
600 Just vol_amode -> save_var var vol_amode -- Aha! It's volatile
603 save_var var vol_amode
604 = do { slot <- allocPrimStack (idCgRep var)
605 ; rebindToStack var slot
606 ; sp_rel <- getSpRelOffset slot
607 ; returnFC (oneStmt (CmmStore sp_rel vol_amode)) }
610 ---------------------------------------------------------------------------
612 When we save the current cost centre (which is done for lexical
613 scoping), we allocate a free stack location, and return (a)~the
614 virtual offset of the location, to pass on to the alternatives, and
615 (b)~the assignment to do the save (just as for @saveVolatileVars@).
618 saveCurrentCostCentre ::
619 FCode (Maybe VirtualSpOffset, -- Where we decide to store it
620 CmmStmts) -- Assignment to save it
622 saveCurrentCostCentre
623 | not opt_SccProfilingOn
624 = returnFC (Nothing, noStmts)
626 = do { slot <- allocPrimStack PtrArg
627 ; sp_rel <- getSpRelOffset slot
628 ; returnFC (Just slot,
629 oneStmt (CmmStore sp_rel curCCS)) }
631 -- Sometimes we don't free the slot containing the cost centre after restoring it
632 -- (see CgLetNoEscape.cgLetNoEscapeBody).
633 restoreCurrentCostCentre :: Maybe VirtualSpOffset -> Bool -> Code
634 restoreCurrentCostCentre Nothing _freeit = nopC
635 restoreCurrentCostCentre (Just slot) freeit
636 = do { sp_rel <- getSpRelOffset slot
637 ; whenC freeit (freeStackSlots [slot])
638 ; stmtC (CmmStore curCCSAddr (CmmLoad sp_rel bWord)) }