e7c08940c5078eb9565b97f2d5e988cedbee25a4
[ghc-hetmet.git] / compiler / codeGen / CgCase.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 % $Id: CgCase.lhs,v 1.75 2005/06/21 10:44:41 simonmar Exp $
5 %
6 %********************************************************
7 %*                                                      *
8 \section[CgCase]{Converting @StgCase@ expressions}
9 %*                                                      *
10 %********************************************************
11
12 \begin{code}
13 module CgCase ( cgCase, saveVolatileVarsAndRegs, 
14                 restoreCurrentCostCentre
15         ) where
16
17 #include "HsVersions.h"
18
19 import {-# SOURCE #-} CgExpr  ( cgExpr )
20
21 import CgMonad
22 import StgSyn
23 import CgBindery        ( getArgAmodes,
24                           bindNewToReg, bindNewToTemp,
25                           getCgIdInfo, getArgAmode,
26                           rebindToStack, getCAddrModeIfVolatile,
27                           nukeDeadBindings, idInfoToAmode
28                         )
29 import CgCon            ( bindConArgs, bindUnboxedTupleComponents )
30 import CgHeapery        ( altHeapCheck, unbxTupleHeapCheck )
31 import CgCallConv       ( dataReturnConvPrim, ctrlReturnConvAlg,
32                           CtrlReturnConvention(..)
33                         )
34 import CgStackery       ( allocPrimStack, allocStackTop, getSpRelOffset,
35                           deAllocStackTop, freeStackSlots
36                         )
37 import CgTailCall       ( performTailCall )
38 import CgPrimOp         ( cgPrimOp )
39 import CgForeignCall    ( cgForeignCall )
40 import CgUtils          ( newTemp, cgLit, emitLitSwitch, emitSwitch,
41                           tagToClosure )
42 import CgProf           ( curCCS, curCCSAddr )
43 import CgInfoTbls       ( emitDirectReturnTarget, emitAlgReturnTarget, 
44                           dataConTagZ )
45 import SMRep            ( CgRep(..), retAddrSizeW, nonVoidArg, isVoidArg,
46                           idCgRep, tyConCgRep, typeHint )
47 import CmmUtils         ( CmmStmts, noStmts, oneStmt, plusStmts )
48 import Cmm
49 import MachOp           ( wordRep )
50 import ClosureInfo      ( mkLFArgument )
51 import StaticFlags      ( opt_SccProfilingOn )
52 import Id               ( Id, idName, isDeadBinder, idType )
53 import ForeignCall      ( ForeignCall(..), CCallSpec(..), playSafe )
54 import VarSet           ( varSetElems )
55 import CoreSyn          ( AltCon(..) )
56 import PrimOp           ( PrimOp(..), primOpOutOfLine )
57 import TyCon            ( isEnumerationTyCon, tyConFamilySize )
58 import Util             ( isSingleton )
59 import Outputable
60 \end{code}
61
62 \begin{code}
63 data GCFlag
64   = GCMayHappen -- The scrutinee may involve GC, so everything must be
65                 -- tidy before the code for the scrutinee.
66
67   | NoGC        -- The scrutinee is a primitive value, or a call to a
68                 -- primitive op which does no GC.  Hence the case can
69                 -- be done inline, without tidying up first.
70 \end{code}
71
72 It is quite interesting to decide whether to put a heap-check
73 at the start of each alternative.  Of course we certainly have
74 to do so if the case forces an evaluation, or if there is a primitive
75 op which can trigger GC.
76
77 A more interesting situation is this:
78
79  \begin{verbatim}
80         !A!;
81         ...A...
82         case x# of
83           0#      -> !B!; ...B...
84           default -> !C!; ...C...
85  \end{verbatim}
86
87 where \tr{!x!} indicates a possible heap-check point. The heap checks
88 in the alternatives {\em can} be omitted, in which case the topmost
89 heapcheck will take their worst case into account.
90
91 In favour of omitting \tr{!B!}, \tr{!C!}:
92
93  - {\em May} save a heap overflow test,
94         if ...A... allocates anything.  The other advantage
95         of this is that we can use relative addressing
96         from a single Hp to get at all the closures so allocated.
97
98  - No need to save volatile vars etc across the case
99
100 Against:
101
102   - May do more allocation than reqd.  This sometimes bites us
103         badly.  For example, nfib (ha!)  allocates about 30\% more space if the
104         worst-casing is done, because many many calls to nfib are leaf calls
105         which don't need to allocate anything.
106
107         This never hurts us if there is only one alternative.
108
109 \begin{code}
110 cgCase  :: StgExpr
111         -> StgLiveVars
112         -> StgLiveVars
113         -> Id
114         -> SRT
115         -> AltType
116         -> [StgAlt]
117         -> Code
118 \end{code}
119
120 Special case #1: case of literal.
121
122 \begin{code}
123 cgCase (StgLit lit) live_in_whole_case live_in_alts bndr srt 
124        alt_type@(PrimAlt tycon) alts
125   = do  { tmp_reg <- bindNewToTemp bndr
126         ; cm_lit <- cgLit lit
127         ; stmtC (CmmAssign tmp_reg (CmmLit cm_lit))
128         ; cgPrimAlts NoGC alt_type tmp_reg alts }
129 \end{code}
130
131 Special case #2: scrutinising a primitive-typed variable.       No
132 evaluation required.  We don't save volatile variables, nor do we do a
133 heap-check in the alternatives.  Instead, the heap usage of the
134 alternatives is worst-cased and passed upstream.  This can result in
135 allocating more heap than strictly necessary, but it will sometimes
136 eliminate a heap check altogether.
137
138 \begin{code}
139 cgCase (StgApp v []) live_in_whole_case live_in_alts bndr srt
140        alt_type@(PrimAlt tycon) alts
141   = do  { -- Careful! we can't just bind the default binder to the same thing
142           -- as the scrutinee, since it might be a stack location, and having
143           -- two bindings pointing at the same stack locn doesn't work (it
144           -- confuses nukeDeadBindings).  Hence, use a new temp.
145           v_info <- getCgIdInfo v
146         ; amode <- idInfoToAmode v_info
147         ; tmp_reg <- bindNewToTemp bndr
148         ; stmtC (CmmAssign tmp_reg amode)
149         ; cgPrimAlts NoGC alt_type tmp_reg alts }
150 \end{code}
151
152 Special case #3: inline PrimOps and foreign calls.
153
154 \begin{code}
155 cgCase (StgOpApp op@(StgPrimOp primop) args _) 
156        live_in_whole_case live_in_alts bndr srt alt_type alts
157   | not (primOpOutOfLine primop)
158   = cgInlinePrimOp primop args bndr alt_type live_in_alts alts
159 \end{code}
160
161 TODO: Case-of-case of primop can probably be done inline too (but
162 maybe better to translate it out beforehand).  See
163 ghc/lib/misc/PackedString.lhs for examples where this crops up (with
164 4.02).
165
166 Special case #4: inline foreign calls: an unsafe foreign call can be done
167 right here, just like an inline primop.
168
169 \begin{code}
170 cgCase (StgOpApp op@(StgFCallOp fcall _) args _) 
171        live_in_whole_case live_in_alts bndr srt alt_type alts
172   | unsafe_foreign_call
173   = ASSERT( isSingleton alts )
174     do  --  *must* be an unboxed tuple alt.
175         -- exactly like the cgInlinePrimOp case for unboxed tuple alts..
176         { res_tmps <- mapFCs bindNewToTemp non_void_res_ids
177         ; let res_hints = map (typeHint.idType) non_void_res_ids
178         ; cgForeignCall (zip res_tmps res_hints) fcall args live_in_alts
179         ; cgExpr rhs }
180   where
181    (_, res_ids, _, rhs) = head alts
182    non_void_res_ids = filter (nonVoidArg . idCgRep) res_ids
183
184    unsafe_foreign_call
185          = case fcall of
186                 CCall (CCallSpec _ _ s) -> not (playSafe s)
187                 _other                  -> False                                
188 \end{code}
189
190 Special case: scrutinising a non-primitive variable.
191 This can be done a little better than the general case, because
192 we can reuse/trim the stack slot holding the variable (if it is in one).
193
194 \begin{code}
195 cgCase (StgApp fun args)
196         live_in_whole_case live_in_alts bndr srt alt_type alts
197   = do  { fun_info <- getCgIdInfo fun
198         ; arg_amodes <- getArgAmodes args
199
200         -- Nuking dead bindings *before* calculating the saves is the
201         -- value-add here.  We might end up freeing up some slots currently
202         -- occupied by variables only required for the call.
203         -- NOTE: we need to look up the variables used in the call before
204         -- doing this, because some of them may not be in the environment
205         -- afterward.
206         ; nukeDeadBindings live_in_alts 
207         ; (save_assts, alts_eob_info, maybe_cc_slot)
208                 <- saveVolatileVarsAndRegs live_in_alts
209
210         ; scrut_eob_info
211             <- forkEval alts_eob_info 
212                         (allocStackTop retAddrSizeW >> nopC)
213                         (do { deAllocStackTop retAddrSizeW
214                             ; cgEvalAlts maybe_cc_slot bndr srt alt_type alts })
215
216         ; setEndOfBlockInfo (maybeReserveSeqFrame alt_type scrut_eob_info)
217                             (performTailCall fun_info arg_amodes save_assts) }
218 \end{code}
219
220 Note about return addresses: we *always* push a return address, even
221 if because of an optimisation we end up jumping direct to the return
222 code (not through the address itself).  The alternatives always assume
223 that the return address is on the stack.  The return address is
224 required in case the alternative performs a heap check, since it
225 encodes the liveness of the slots in the activation record.
226
227 On entry to the case alternative, we can re-use the slot containing
228 the return address immediately after the heap check.  That's what the
229 deAllocStackTop call is doing above.
230
231 Finally, here is the general case.
232
233 \begin{code}
234 cgCase expr live_in_whole_case live_in_alts bndr srt alt_type alts
235   = do  {       -- Figure out what volatile variables to save
236           nukeDeadBindings live_in_whole_case
237     
238         ; (save_assts, alts_eob_info, maybe_cc_slot)
239                 <- saveVolatileVarsAndRegs live_in_alts
240
241              -- Save those variables right now!
242         ; emitStmts save_assts
243
244             -- generate code for the alts
245         ; scrut_eob_info
246                <- forkEval alts_eob_info
247                            (do  { nukeDeadBindings live_in_alts
248                                 ; allocStackTop retAddrSizeW   -- space for retn address 
249                                 ; nopC })
250                            (do  { deAllocStackTop retAddrSizeW
251                                 ; cgEvalAlts maybe_cc_slot bndr srt alt_type alts })
252
253         ; setEndOfBlockInfo (maybeReserveSeqFrame alt_type scrut_eob_info)
254                             (cgExpr expr)
255     }
256 \end{code}
257
258 There's a lot of machinery going on behind the scenes to manage the
259 stack pointer here.  forkEval takes the virtual Sp and free list from
260 the first argument, and turns that into the *real* Sp for the second
261 argument.  It also uses this virtual Sp as the args-Sp in the EOB info
262 returned, so that the scrutinee will trim the real Sp back to the
263 right place before doing whatever it does.  
264   --SDM (who just spent an hour figuring this out, and didn't want to 
265          forget it).
266
267 Why don't we push the return address just before evaluating the
268 scrutinee?  Because the slot reserved for the return address might
269 contain something useful, so we wait until performing a tail call or
270 return before pushing the return address (see
271 CgTailCall.pushReturnAddress).  
272
273 This also means that the environment doesn't need to know about the
274 free stack slot for the return address (for generating bitmaps),
275 because we don't reserve it until just before the eval.
276
277 TODO!!  Problem: however, we have to save the current cost centre
278 stack somewhere, because at the eval point the current CCS might be
279 different.  So we pick a free stack slot and save CCCS in it.  One
280 consequence of this is that activation records on the stack don't
281 follow the layout of closures when we're profiling.  The CCS could be
282 anywhere within the record).
283
284 \begin{code}
285 maybeReserveSeqFrame PolyAlt (EndOfBlockInfo args_sp (CaseAlts amode stuff bndr _))
286    = EndOfBlockInfo (args_sp + retAddrSizeW) (CaseAlts amode stuff bndr True)
287 maybeReserveSeqFrame other scrut_eob_info = scrut_eob_info
288 \end{code}
289
290
291 %************************************************************************
292 %*                                                                      *
293                 Inline primops
294 %*                                                                      *
295 %************************************************************************
296
297 \begin{code}
298 cgInlinePrimOp primop args bndr (PrimAlt tycon) live_in_alts alts
299   | isVoidArg (idCgRep bndr)
300   = ASSERT( con == DEFAULT && isSingleton alts && null bs )
301     do  {       -- VOID RESULT; just sequencing, 
302                 -- so get in there and do it
303           cgPrimOp [] primop args live_in_alts
304         ; cgExpr rhs }
305   where
306     (con,bs,_,rhs) = head alts
307
308 cgInlinePrimOp primop args bndr (PrimAlt tycon) live_in_alts alts
309   = do  {       -- PRIMITIVE ALTS, with non-void result
310           tmp_reg <- bindNewToTemp bndr
311         ; cgPrimOp [tmp_reg] primop args live_in_alts
312         ; cgPrimAlts NoGC (PrimAlt tycon) tmp_reg alts }
313
314 cgInlinePrimOp primop args bndr (UbxTupAlt tycon) live_in_alts alts
315   = ASSERT( isSingleton alts )
316     do  {       -- UNBOXED TUPLE ALTS
317                 -- No heap check, no yield, just get in there and do it.
318                 -- NB: the case binder isn't bound to anything; 
319                 --     it has a unboxed tuple type
320           
321           res_tmps <- mapFCs bindNewToTemp non_void_res_ids
322         ; cgPrimOp res_tmps primop args live_in_alts
323         ; cgExpr rhs }
324   where
325    (_, res_ids, _, rhs) = head alts
326    non_void_res_ids = filter (nonVoidArg . idCgRep) res_ids
327
328 cgInlinePrimOp primop args bndr (AlgAlt tycon) live_in_alts alts
329   = do  {       -- ENUMERATION TYPE RETURN
330                 -- Typical: case a ># b of { True -> ..; False -> .. }
331                 -- The primop itself returns an index into the table of
332                 -- closures for the enumeration type.
333            tag_amode <- ASSERT( isEnumerationTyCon tycon )
334                         do_enum_primop primop
335
336                 -- Bind the default binder if necessary
337                 -- (avoiding it avoids the assignment)
338                 -- The deadness info is set by StgVarInfo
339         ; hmods <- getHomeModules
340         ; whenC (not (isDeadBinder bndr))
341                 (do { tmp_reg <- bindNewToTemp bndr
342                     ; stmtC (CmmAssign tmp_reg (tagToClosure hmods tycon tag_amode)) })
343
344                 -- Compile the alts
345         ; (branches, mb_deflt) <- cgAlgAlts NoGC Nothing{-cc_slot-}
346                                             (AlgAlt tycon) alts
347
348                 -- Do the switch
349         ; emitSwitch tag_amode branches mb_deflt 0 (tyConFamilySize tycon - 1)
350         }
351   where
352
353     do_enum_primop :: PrimOp -> FCode CmmExpr   -- Returns amode for result
354     do_enum_primop TagToEnumOp  -- No code!
355        | [arg] <- args = do
356          (_,e) <- getArgAmode arg
357          return e
358     do_enum_primop primop
359       = do tmp <- newTemp wordRep
360            cgPrimOp [tmp] primop args live_in_alts
361            returnFC (CmmReg tmp)
362
363 cgInlinePrimOp primop arg_amodes bndr PolyAlt live_in_alts alts
364   = pprPanic "cgCase: case of primop has polymorphic type" (ppr bndr)
365 \end{code}
366
367 %************************************************************************
368 %*                                                                      *
369 \subsection[CgCase-alts]{Alternatives}
370 %*                                                                      *
371 %************************************************************************
372
373 @cgEvalAlts@ returns an addressing mode for a continuation for the
374 alternatives of a @case@, used in a context when there
375 is some evaluation to be done.
376
377 \begin{code}
378 cgEvalAlts :: Maybe VirtualSpOffset     -- Offset of cost-centre to be restored, if any
379            -> Id
380            -> SRT                       -- SRT for the continuation
381            -> AltType
382            -> [StgAlt]
383            -> FCode Sequel      -- Any addr modes inside are guaranteed
384                                 -- to be a label so that we can duplicate it 
385                                 -- without risk of duplicating code
386
387 cgEvalAlts cc_slot bndr srt alt_type@(PrimAlt tycon) alts
388   = do  { let   rep = tyConCgRep tycon
389                 reg = dataReturnConvPrim rep    -- Bottom for voidRep
390
391         ; abs_c <- forkProc $ do
392                 {       -- Bind the case binder, except if it's void
393                         -- (reg is bottom in that case)
394                   whenC (nonVoidArg rep) $
395                   bindNewToReg bndr reg (mkLFArgument bndr)
396                 ; restoreCurrentCostCentre cc_slot True
397                 ; cgPrimAlts GCMayHappen alt_type reg alts }
398
399         ; lbl <- emitDirectReturnTarget (idName bndr) abs_c srt
400         ; returnFC (CaseAlts lbl Nothing bndr False) }
401
402 cgEvalAlts cc_slot bndr srt (UbxTupAlt _) [(con,args,_,rhs)]
403   =     -- Unboxed tuple case
404         -- By now, the simplifier should have have turned it
405         -- into         case e of (# a,b #) -> e
406         -- There shouldn't be a 
407         --              case e of DEFAULT -> e
408     ASSERT2( case con of { DataAlt _ -> True; other -> False },
409              text "cgEvalAlts: dodgy case of unboxed tuple type" )
410     do  {       -- forkAbsC for the RHS, so that the envt is
411                 -- not changed for the emitDirectReturn call
412           abs_c <- forkProc $ do 
413                 { (live_regs, ptrs, nptrs, _) <- bindUnboxedTupleComponents args
414                         -- Restore the CC *after* binding the tuple components, 
415                         -- so that we get the stack offset of the saved CC right.
416                 ; restoreCurrentCostCentre cc_slot True
417                         -- Generate a heap check if necessary
418                         -- and finally the code for the alternative
419                 ; unbxTupleHeapCheck live_regs ptrs nptrs noStmts
420                                      (cgExpr rhs) }
421         ; lbl <- emitDirectReturnTarget (idName bndr) abs_c srt
422         ; returnFC (CaseAlts lbl Nothing bndr False) }
423
424 cgEvalAlts cc_slot bndr srt alt_type alts
425   =     -- Algebraic and polymorphic case
426     do  {       -- Bind the default binder
427           bindNewToReg bndr nodeReg (mkLFArgument bndr)
428
429         -- Generate sequel info for use downstream
430         -- At the moment, we only do it if the type is vector-returnable.
431         -- Reason: if not, then it costs extra to label the
432         -- alternatives, because we'd get return code like:
433         --
434         --      switch TagReg { 0 : JMP(alt_1); 1 : JMP(alt_2) ..etc }
435         --
436         -- which is worse than having the alt code in the switch statement
437
438         ; (alts, mb_deflt) <- cgAlgAlts GCMayHappen cc_slot alt_type alts
439
440         ; (lbl, branches) <- emitAlgReturnTarget (idName bndr) 
441                                 alts mb_deflt srt ret_conv
442
443         ; returnFC (CaseAlts lbl branches bndr False) }
444   where
445     ret_conv = case alt_type of
446                 AlgAlt tc -> ctrlReturnConvAlg tc
447                 PolyAlt   -> UnvectoredReturn 0
448 \end{code}
449
450
451 HWL comment on {\em GrAnSim\/}  (adding GRAN_YIELDs for context switch): If
452 we  do  an inlining of the  case  no separate  functions  for returning are
453 created, so we don't have to generate a GRAN_YIELD in that case.  This info
454 must be  propagated  to cgAlgAltRhs (where the  GRAN_YIELD  macro might  be
455 emitted). Hence, the new Bool arg to cgAlgAltRhs.
456
457 %************************************************************************
458 %*                                                                      *
459 \subsection[CgCase-alg-alts]{Algebraic alternatives}
460 %*                                                                      *
461 %************************************************************************
462
463 In @cgAlgAlts@, none of the binders in the alternatives are
464 assumed to be yet bound.
465
466 HWL comment on {\em GrAnSim\/} (adding GRAN_YIELDs for context switch): The
467 last   arg of  cgAlgAlts  indicates  if we  want  a context   switch at the
468 beginning of  each alternative. Normally we  want that. The  only exception
469 are inlined alternatives.
470
471 \begin{code}
472 cgAlgAlts :: GCFlag
473        -> Maybe VirtualSpOffset
474        -> AltType                               --  ** AlgAlt or PolyAlt only **
475        -> [StgAlt]                              -- The alternatives
476        -> FCode ( [(ConTagZ, CgStmts)], -- The branches
477                   Maybe CgStmts )       -- The default case
478
479 cgAlgAlts gc_flag cc_slot alt_type alts
480   = do alts <- forkAlts [ cgAlgAlt gc_flag cc_slot alt_type alt | alt <- alts]
481        let
482             mb_deflt = case alts of -- DEFAULT is always first, if present
483                          ((DEFAULT,blks) : _) -> Just blks
484                          other                -> Nothing
485
486             branches = [(dataConTagZ con, blks) 
487                        | (DataAlt con, blks) <- alts]
488        -- in
489        return (branches, mb_deflt)
490
491
492 cgAlgAlt :: GCFlag
493          -> Maybe VirtualSpOffset       -- Turgid state
494          -> AltType                     --  ** AlgAlt or PolyAlt only **
495          -> StgAlt
496          -> FCode (AltCon, CgStmts)
497
498 cgAlgAlt gc_flag cc_slot alt_type (con, args, use_mask, rhs)
499   = do  { abs_c <- getCgStmts $ do
500                 { bind_con_args con args
501                 ; restoreCurrentCostCentre cc_slot True
502                 ; maybeAltHeapCheck gc_flag alt_type (cgExpr rhs) }
503         ; return (con, abs_c) }
504   where
505     bind_con_args DEFAULT      args = nopC
506     bind_con_args (DataAlt dc) args = bindConArgs dc args
507 \end{code}
508
509
510 %************************************************************************
511 %*                                                                      *
512 \subsection[CgCase-prim-alts]{Primitive alternatives}
513 %*                                                                      *
514 %************************************************************************
515
516 @cgPrimAlts@ generates suitable a @CSwitch@
517 for dealing with the alternatives of a primitive @case@, given an
518 addressing mode for the thing to scrutinise.  It also keeps track of
519 the maximum stack depth encountered down any branch.
520
521 As usual, no binders in the alternatives are yet bound.
522
523 \begin{code}
524 cgPrimAlts :: GCFlag
525            -> AltType   -- Always PrimAlt, but passed to maybeAltHeapCheck
526            -> CmmReg    -- Scrutinee
527            -> [StgAlt]  -- Alternatives
528            -> Code
529 -- NB: cgPrimAlts emits code that does the case analysis.
530 -- It's often used in inline situations, rather than to genearte
531 -- a labelled return point.  That's why its interface is a little
532 -- different to cgAlgAlts
533 --
534 -- INVARIANT: the default binder is already bound
535 cgPrimAlts gc_flag alt_type scrutinee alts
536   = do  { tagged_absCs <- forkAlts (map (cgPrimAlt gc_flag alt_type) alts)
537         ; let ((DEFAULT, deflt_absC) : others) = tagged_absCs   -- There is always a default
538               alt_absCs = [(lit,rhs) | (LitAlt lit, rhs) <- others]
539         ; emitLitSwitch (CmmReg scrutinee) alt_absCs deflt_absC }
540
541 cgPrimAlt :: GCFlag
542           -> AltType
543           -> StgAlt                             -- The alternative
544           -> FCode (AltCon, CgStmts)    -- Its compiled form
545
546 cgPrimAlt gc_flag alt_type (con, [], [], rhs)
547   = ASSERT( case con of { DEFAULT -> True; LitAlt _ -> True; other -> False } )
548     do  { abs_c <- getCgStmts (maybeAltHeapCheck gc_flag alt_type (cgExpr rhs)) 
549         ; returnFC (con, abs_c) }
550 \end{code}
551
552
553 %************************************************************************
554 %*                                                                      *
555 \subsection[CgCase-tidy]{Code for tidying up prior to an eval}
556 %*                                                                      *
557 %************************************************************************
558
559 \begin{code}
560 maybeAltHeapCheck 
561         :: GCFlag 
562         -> AltType      -- PolyAlt, PrimAlt, AlgAlt, but *not* UbxTupAlt
563         -> Code         -- Continuation
564         -> Code
565 maybeAltHeapCheck NoGC        _        code = code
566 maybeAltHeapCheck GCMayHappen alt_type code = altHeapCheck alt_type code
567
568 saveVolatileVarsAndRegs
569     :: StgLiveVars                    -- Vars which should be made safe
570     -> FCode (CmmStmts,               -- Assignments to do the saves
571               EndOfBlockInfo,         -- sequel for the alts
572               Maybe VirtualSpOffset)  -- Slot for current cost centre
573
574 saveVolatileVarsAndRegs vars
575   = do  { var_saves <- saveVolatileVars vars
576         ; (maybe_cc_slot, cc_save) <- saveCurrentCostCentre
577         ; eob_info <- getEndOfBlockInfo
578         ; returnFC (var_saves `plusStmts` cc_save,
579                     eob_info,
580                     maybe_cc_slot) }
581
582
583 saveVolatileVars :: StgLiveVars         -- Vars which should be made safe
584                  -> FCode CmmStmts      -- Assignments to to the saves
585
586 saveVolatileVars vars
587   = do  { stmts_s <- mapFCs save_it (varSetElems vars)
588         ; return (foldr plusStmts noStmts stmts_s) }
589   where
590     save_it var
591       = do { v <- getCAddrModeIfVolatile var
592            ; case v of
593                 Nothing         -> return noStmts          -- Non-volatile
594                 Just vol_amode  -> save_var var vol_amode  -- Aha! It's volatile
595         }
596
597     save_var var vol_amode
598       = do { slot <- allocPrimStack (idCgRep var)
599            ; rebindToStack var slot
600            ; sp_rel <- getSpRelOffset slot
601            ; returnFC (oneStmt (CmmStore sp_rel vol_amode)) }
602 \end{code}
603
604 ---------------------------------------------------------------------------
605
606 When we save the current cost centre (which is done for lexical
607 scoping), we allocate a free stack location, and return (a)~the
608 virtual offset of the location, to pass on to the alternatives, and
609 (b)~the assignment to do the save (just as for @saveVolatileVars@).
610
611 \begin{code}
612 saveCurrentCostCentre ::
613         FCode (Maybe VirtualSpOffset,   -- Where we decide to store it
614                CmmStmts)                -- Assignment to save it
615
616 saveCurrentCostCentre
617   | not opt_SccProfilingOn 
618   = returnFC (Nothing, noStmts)
619   | otherwise
620   = do  { slot <- allocPrimStack PtrArg
621         ; sp_rel <- getSpRelOffset slot
622         ; returnFC (Just slot,
623                     oneStmt (CmmStore sp_rel curCCS)) }
624
625 -- Sometimes we don't free the slot containing the cost centre after restoring it
626 -- (see CgLetNoEscape.cgLetNoEscapeBody).
627 restoreCurrentCostCentre :: Maybe VirtualSpOffset -> Bool -> Code
628 restoreCurrentCostCentre Nothing     _freeit = nopC
629 restoreCurrentCostCentre (Just slot) freeit
630  = do   { sp_rel <- getSpRelOffset slot
631         ; whenC freeit (freeStackSlots [slot])
632         ; stmtC (CmmStore curCCSAddr (CmmLoad sp_rel wordRep)) }
633 \end{code}
634