Big collection of patches for the new codegen branch.
[ghc-hetmet.git] / compiler / codeGen / StgCmmBind.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Stg to C-- code generation: bindings
4 --
5 -- (c) The University of Glasgow 2004-2006
6 --
7 -----------------------------------------------------------------------------
8
9 module StgCmmBind ( 
10         cgTopRhsClosure, 
11         cgBind,
12         emitBlackHoleCode,
13         pushUpdateFrame
14   ) where
15
16 #include "HsVersions.h"
17
18 import StgCmmExpr
19 import StgCmmMonad
20 import StgCmmExpr
21 import StgCmmEnv
22 import StgCmmCon
23 import StgCmmHeap
24 import StgCmmProf
25 import StgCmmTicky
26 import StgCmmGran
27 import StgCmmLayout
28 import StgCmmUtils
29 import StgCmmClosure
30
31 import MkZipCfgCmm
32 import CoreSyn          ( AltCon(..) )
33 import SMRep
34 import Cmm
35 import CmmUtils
36 import CLabel
37 import StgSyn
38 import CostCentre       
39 import Id
40 import Monad (foldM, liftM)
41 import Name
42 import Module
43 import ListSetOps
44 import Util
45 import BasicTypes
46 import Constants
47 import Outputable
48 import FastString
49 import Maybes
50
51 import Data.List
52
53 ------------------------------------------------------------------------
54 --              Top-level bindings
55 ------------------------------------------------------------------------
56
57 -- For closures bound at top level, allocate in static space.
58 -- They should have no free variables.
59
60 cgTopRhsClosure :: Id
61                 -> CostCentreStack      -- Optional cost centre annotation
62                 -> StgBinderInfo
63                 -> UpdateFlag
64                 -> SRT
65                 -> [Id]                 -- Args
66                 -> StgExpr
67                 -> FCode CgIdInfo
68
69 cgTopRhsClosure id ccs _ upd_flag srt args body = do
70   {     -- LAY OUT THE OBJECT
71     let name = idName id
72   ; lf_info  <- mkClosureLFInfo id TopLevel [] upd_flag args
73   ; srt_info <- getSRTInfo srt
74   ; mod_name <- getModuleName
75   ; let descr         = closureDescription mod_name name
76         closure_info  = mkClosureInfo True id lf_info 0 0 srt_info descr
77         closure_label = mkLocalClosureLabel name (idCafInfo id)
78         cg_id_info    = litIdInfo id lf_info (CmmLabel closure_label)
79         closure_rep   = mkStaticClosureFields closure_info ccs True []
80
81          -- BUILD THE OBJECT, AND GENERATE INFO TABLE (IF NECESSARY)
82   ; emitDataLits closure_label closure_rep
83   ; let fv_details :: [(NonVoid Id, VirtualHpOffset)]
84         (_, _, fv_details) = mkVirtHeapOffsets (isLFThunk lf_info) 
85                                                (addIdReps [])
86   -- Don't drop the non-void args until the closure info has been made
87   ; forkClosureBody (closureCodeBody True id closure_info ccs srt_info
88                                      (nonVoidIds args) (length args) body fv_details)
89
90   ; pprTrace "arity for" (ppr id <+> ppr (length args) <+> ppr args) $
91     returnFC cg_id_info }
92
93 ------------------------------------------------------------------------
94 --              Non-top-level bindings
95 ------------------------------------------------------------------------
96
97 cgBind :: StgBinding -> FCode ()
98 cgBind (StgNonRec name rhs)
99   = do  { ((info, init), body) <- getCodeR $ cgRhs name rhs
100         ; addBindC (cg_id info) info
101         ; emit (init <*> body) }
102
103 cgBind (StgRec pairs)
104   = do  { ((new_binds, inits), body) <- getCodeR $ fixC (\ new_binds_inits -> 
105                do { addBindsC $ fst new_binds_inits -- avoid premature deconstruction
106                   ; liftM unzip $ listFCs [ cgRhs b e | (b,e) <- pairs ] })
107        ; addBindsC new_binds
108        ; emit (catAGraphs inits <*> body) }
109
110 {- Recursive let-bindings are tricky.
111    Consider the following pseudocode:
112      let x = \_ ->  ... y ...
113          y = \_ ->  ... z ...
114          z = \_ ->  ... x ...
115      in ...
116    For each binding, we need to allocate a closure, and each closure must
117    capture the address of the other closures.
118    We want to generate the following C-- code:
119      // Initialization Code
120      x = hp - 24; // heap address of x's closure
121      y = hp - 40; // heap address of x's closure
122      z = hp - 64; // heap address of x's closure
123      // allocate and initialize x
124      m[hp-8]   = ...
125      m[hp-16]  = y       // the closure for x captures y
126      m[hp-24] = x_info;
127      // allocate and initialize y
128      m[hp-32] = z;       // the closure for y captures z
129      m[hp-40] = y_info;
130      // allocate and initialize z
131      ...
132      
133    For each closure, we must generate not only the code to allocate and
134    initialize the closure itself, but also some Initialization Code that
135    sets a variable holding the closure pointer.
136    The complication here is that we don't know the heap offsets a priori,
137    which has two consequences:
138      1. we need a fixpoint
139      2. we can't trivially separate the Initialization Code from the
140         code that compiles the right-hand-sides
141
142    Note: We don't need this complication with let-no-escapes, because
143    in that case, the names are bound to labels in the environment,
144    and we don't need to emit any code to witness that binding.
145 -}
146
147 --------------------
148 cgRhs :: Id -> StgRhs -> FCode (CgIdInfo, CmmAGraph)
149    -- The Id is passed along so a binding can be set up
150    -- The returned values are the binding for the environment
151    -- and the Initialization Code that witnesses the binding
152
153 cgRhs name (StgRhsCon maybe_cc con args)
154   = buildDynCon name maybe_cc con args
155
156 cgRhs name (StgRhsClosure cc bi fvs upd_flag srt args body)
157   = pprTrace "cgRhs closure" (ppr name <+> ppr args) $
158     mkRhsClosure name cc bi (nonVoidIds fvs) upd_flag srt args body
159
160 ------------------------------------------------------------------------
161 --              Non-constructor right hand sides
162 ------------------------------------------------------------------------
163
164 mkRhsClosure :: Id -> CostCentreStack -> StgBinderInfo
165              -> [NonVoid Id]                    -- Free vars
166              -> UpdateFlag -> SRT
167              -> [Id]                            -- Args
168              -> StgExpr
169              -> FCode (CgIdInfo, CmmAGraph)
170
171 {- mkRhsClosure looks for two special forms of the right-hand side:
172         a) selector thunks
173         b) AP thunks
174
175 If neither happens, it just calls mkClosureLFInfo.  You might think
176 that mkClosureLFInfo should do all this, but it seems wrong for the
177 latter to look at the structure of an expression
178
179 Note [Selectors]
180 ~~~~~~~~~~~~~~~~
181 We look at the body of the closure to see if it's a selector---turgid,
182 but nothing deep.  We are looking for a closure of {\em exactly} the
183 form:
184
185 ...  = [the_fv] \ u [] ->
186          case the_fv of
187            con a_1 ... a_n -> a_i
188
189 Note [Ap thunks]
190 ~~~~~~~~~~~~~~~~
191 A more generic AP thunk of the form
192
193         x = [ x_1...x_n ] \.. [] -> x_1 ... x_n
194
195 A set of these is compiled statically into the RTS, so we just use
196 those.  We could extend the idea to thunks where some of the x_i are
197 global ids (and hence not free variables), but this would entail
198 generating a larger thunk.  It might be an option for non-optimising
199 compilation, though.
200
201 We only generate an Ap thunk if all the free variables are pointers,
202 for semi-obvious reasons.
203
204 -}
205
206 ---------- Note [Selectors] ------------------
207 mkRhsClosure    bndr cc bi
208                 [NonVoid the_fv]                -- Just one free var
209                 upd_flag                -- Updatable thunk
210                 _srt
211                 []                      -- A thunk
212                 body@(StgCase (StgApp scrutinee [{-no args-}])
213                       _ _ _ _   -- ignore uniq, etc.
214                       (AlgAlt _)
215                       [(DataAlt con, params, _use_mask,
216                             (StgApp selectee [{-no args-}]))])
217   |  the_fv == scrutinee                -- Scrutinee is the only free variable
218   && maybeToBool maybe_offset           -- Selectee is a component of the tuple
219   && offset_into_int <= mAX_SPEC_SELECTEE_SIZE  -- Offset is small enough
220   = -- NOT TRUE: ASSERT(is_single_constructor)
221     -- The simplifier may have statically determined that the single alternative
222     -- is the only possible case and eliminated the others, even if there are
223     -- other constructors in the datatype.  It's still ok to make a selector
224     -- thunk in this case, because we *know* which constructor the scrutinee
225     -- will evaluate to.
226     --
227     -- srt is discarded; it must be empty
228     cgStdThunk bndr cc bi body lf_info [StgVarArg the_fv]
229   where
230     lf_info               = mkSelectorLFInfo bndr offset_into_int
231                                  (isUpdatable upd_flag)
232     (_, params_w_offsets) = layOutDynConstr con (addIdReps params)
233                         -- Just want the layout
234     maybe_offset          = assocMaybe params_w_offsets (NonVoid selectee)
235     Just the_offset       = maybe_offset
236     offset_into_int       = the_offset - fixedHdrSize
237
238 ---------- Note [Ap thunks] ------------------
239 mkRhsClosure    bndr cc bi
240                 fvs
241                 upd_flag
242                 _srt
243                 []                      -- No args; a thunk
244                 body@(StgApp fun_id args)
245
246   | args `lengthIs` (arity-1)
247         && all isFollowableArg (map (idCgRep . stripNV) fvs) 
248         && isUpdatable upd_flag
249         && arity <= mAX_SPEC_AP_SIZE 
250
251                    -- Ha! an Ap thunk
252   = cgStdThunk bndr cc bi body lf_info payload
253   where
254         lf_info = mkApLFInfo bndr upd_flag arity
255         -- the payload has to be in the correct order, hence we can't
256         -- just use the fvs.
257         payload = StgVarArg fun_id : args
258         arity   = length fvs
259
260 ---------- Default case ------------------
261 mkRhsClosure bndr cc _ fvs upd_flag srt args body
262   = do  {       -- LAY OUT THE OBJECT
263         -- If the binder is itself a free variable, then don't store
264         -- it in the closure.  Instead, just bind it to Node on entry.
265         -- NB we can be sure that Node will point to it, because we
266         -- haven't told mkClosureLFInfo about this; so if the binder
267         -- _was_ a free var of its RHS, mkClosureLFInfo thinks it *is*
268         -- stored in the closure itself, so it will make sure that
269         -- Node points to it...
270         ; let
271                 is_elem      = isIn "cgRhsClosure"
272                 bndr_is_a_fv = (NonVoid bndr) `is_elem` fvs
273                 reduced_fvs | bndr_is_a_fv = fvs `minusList` [NonVoid bndr]
274                             | otherwise    = fvs
275
276                 
277         -- MAKE CLOSURE INFO FOR THIS CLOSURE
278         ; lf_info <- mkClosureLFInfo bndr NotTopLevel fvs upd_flag args
279         ; mod_name <- getModuleName
280         ; c_srt <- getSRTInfo srt
281         ; let   name  = idName bndr
282                 descr = closureDescription mod_name name
283                 fv_details :: [(NonVoid Id, VirtualHpOffset)]
284                 (tot_wds, ptr_wds, fv_details) 
285                    = mkVirtHeapOffsets (isLFThunk lf_info) 
286                                        (addIdReps (map stripNV reduced_fvs))
287                 closure_info = mkClosureInfo False      -- Not static
288                                              bndr lf_info tot_wds ptr_wds
289                                              c_srt descr
290
291         -- BUILD ITS INFO TABLE AND CODE
292         ; forkClosureBody $
293                 -- forkClosureBody: (a) ensure that bindings in here are not seen elsewhere
294                 --                  (b) ignore Sequel from context; use empty Sequel
295                 -- And compile the body
296                 closureCodeBody False bndr closure_info cc c_srt (nonVoidIds args)
297                                 (length args) body fv_details
298
299         -- BUILD THE OBJECT
300         ; (use_cc, blame_cc) <- chooseDynCostCentres cc args body
301         ; emit (mkComment $ mkFastString "calling allocDynClosure")
302         ; let toVarArg (NonVoid a, off) = (NonVoid (StgVarArg a), off)
303         ; (tmp, init) <- allocDynClosure closure_info use_cc blame_cc 
304                                          (map toVarArg fv_details)
305         
306         -- RETURN
307         ; return $ (regIdInfo bndr lf_info tmp, init) }
308
309 -- Use with care; if used inappropriately, it could break invariants.
310 stripNV :: NonVoid a -> a
311 stripNV (NonVoid a) = a
312
313 -------------------------
314 cgStdThunk
315         :: Id
316         -> CostCentreStack      -- Optional cost centre annotation
317         -> StgBinderInfo        -- XXX: not used??
318         -> StgExpr
319         -> LambdaFormInfo
320         -> [StgArg]                     -- payload
321         -> FCode (CgIdInfo, CmmAGraph)
322
323 cgStdThunk bndr cc _bndr_info body lf_info payload
324   = do  -- AHA!  A STANDARD-FORM THUNK
325   {     -- LAY OUT THE OBJECT
326     mod_name <- getModuleName
327   ; let (tot_wds, ptr_wds, payload_w_offsets) 
328             = mkVirtHeapOffsets (isLFThunk lf_info) (addArgReps payload)
329
330         descr = closureDescription mod_name (idName bndr)
331         closure_info = mkClosureInfo False      -- Not static
332                                      bndr lf_info tot_wds ptr_wds 
333                                      NoC_SRT    -- No SRT for a std-form closure
334                                      descr
335
336   ; (use_cc, blame_cc) <- chooseDynCostCentres cc [{- no args-}] body
337
338         -- BUILD THE OBJECT
339   ; (tmp, init) <- allocDynClosure closure_info use_cc blame_cc payload_w_offsets
340
341         -- RETURN
342   ; returnFC $ (regIdInfo bndr lf_info tmp, init) }
343
344 mkClosureLFInfo :: Id           -- The binder
345                 -> TopLevelFlag -- True of top level
346                 -> [NonVoid Id] -- Free vars
347                 -> UpdateFlag   -- Update flag
348                 -> [Id]         -- Args
349                 -> FCode LambdaFormInfo
350 mkClosureLFInfo bndr top fvs upd_flag args
351   | null args = return (mkLFThunk (idType bndr) top (map stripNV fvs) upd_flag)
352   | otherwise = do { arg_descr <- mkArgDescr (idName bndr) args
353                    ; return (mkLFReEntrant top (map stripNV fvs) args arg_descr) }
354
355
356 ------------------------------------------------------------------------
357 --              The code for closures}
358 ------------------------------------------------------------------------
359
360 closureCodeBody :: Bool            -- whether this is a top-level binding
361                 -> Id              -- the closure's name
362                 -> ClosureInfo     -- Lots of information about this closure
363                 -> CostCentreStack -- Optional cost centre attached to closure
364                 -> C_SRT
365                 -> [NonVoid Id]    -- incoming args to the closure
366                 -> Int             -- arity, including void args
367                 -> StgExpr
368                 -> [(NonVoid Id, VirtualHpOffset)] -- the closure's free variables
369                 -> FCode ()
370
371 {- There are two main cases for the code for closures.  
372
373 * If there are *no arguments*, then the closure is a thunk, and not in
374   normal form. So it should set up an update frame (if it is
375   shared). NB: Thunks cannot have a primitive type!
376
377 * If there is *at least one* argument, then this closure is in
378   normal form, so there is no need to set up an update frame.
379
380   The Macros for GrAnSim are produced at the beginning of the
381   argSatisfactionCheck (by calling fetchAndReschedule).  
382   There info if Node points to closure is available. -- HWL -}
383
384 closureCodeBody top_lvl bndr cl_info cc srt args arity body fv_details
385   | length args == 0 -- No args i.e. thunk
386   = emitClosureProcAndInfoTable top_lvl bndr cl_info [] $
387       (\ (node, _) -> thunkCode cl_info fv_details cc srt node arity body)
388
389 closureCodeBody top_lvl bndr cl_info cc srt args arity body fv_details
390   = ASSERT( length args > 0 )
391     do  {       -- Allocate the global ticky counter,
392                 -- and establish the ticky-counter 
393                 -- label for this block
394           let ticky_ctr_lbl = mkRednCountsLabel (closureName cl_info) $ clHasCafRefs cl_info
395         ; emitTickyCounter cl_info (map stripNV args)
396         ; setTickyCtrLabel ticky_ctr_lbl $ do
397
398         -- Emit the main entry code
399         ; emitClosureProcAndInfoTable top_lvl bndr cl_info args $ \(node, arg_regs) -> do
400                 -- Emit the slow-entry code (for entering a closure through a PAP)
401                 { mkSlowEntryCode cl_info arg_regs
402
403                 ; let lf_info = closureLFInfo cl_info
404                       node_points = nodeMustPointToIt lf_info
405                 ; tickyEnterFun cl_info
406                 ; whenC node_points (ldvEnterClosure cl_info)
407                 ; granYield arg_regs node_points
408
409                         -- Main payload
410                 ; entryHeapCheck node arity arg_regs srt $ do
411                 { enterCostCentre cl_info cc body
412                 ; fv_bindings <- mapM bind_fv fv_details
413                 ; load_fvs node lf_info fv_bindings -- Load free vars out of closure *after*
414                 ; cgExpr body }}            -- heap check, to reduce live vars over check
415
416   }
417
418 -- A function closure pointer may be tagged, so we
419 -- must take it into account when accessing the free variables.
420 bind_fv :: (NonVoid Id, VirtualHpOffset) -> FCode (LocalReg, WordOff)
421 bind_fv (id, off) = do { reg <- rebindToReg id; return (reg, off) }
422
423 load_fvs :: LocalReg -> LambdaFormInfo -> [(LocalReg, WordOff)] -> FCode ()
424 load_fvs node lf_info = mapCs (\ (reg, off) ->
425       pprTrace "get tag for" (ppr reg <+> ppr tag) $ emit $ mkTaggedObjectLoad reg node off tag)
426   where tag = lfDynTag lf_info
427
428 -----------------------------------------
429 -- The "slow entry" code for a function.  This entry point takes its
430 -- arguments on the stack.  It loads the arguments into registers
431 -- according to the calling convention, and jumps to the function's
432 -- normal entry point.  The function's closure is assumed to be in
433 -- R1/node.
434 -- 
435 -- The slow entry point is used for unknown calls: eg. stg_PAP_entry 
436
437 mkSlowEntryCode :: ClosureInfo -> [LocalReg] -> FCode ()
438 -- If this function doesn't have a specialised ArgDescr, we need
439 -- to generate the function's arg bitmap and slow-entry code.
440 -- Here, we emit the slow-entry code.
441 mkSlowEntryCode cl_info (_ : arg_regs) -- first arg should already be in `Node'
442   | Just (_, ArgGen _) <- closureFunInfo cl_info
443   = emitProcWithConvention Slow (CmmInfo Nothing Nothing CmmNonInfoTable) slow_lbl
444                            arg_regs jump
445   | otherwise = return ()
446   where
447      caf_refs = clHasCafRefs cl_info
448      name     = closureName cl_info
449      slow_lbl = mkSlowEntryLabel  name caf_refs
450      fast_lbl = enterLocalIdLabel name caf_refs
451      jump = mkJump (mkLblExpr fast_lbl) (map (CmmReg . CmmLocal) arg_regs)
452                    initUpdFrameOff
453 mkSlowEntryCode _ [] = panic "entering a closure with no arguments?"
454
455 -----------------------------------------
456 thunkCode :: ClosureInfo -> [(NonVoid Id, VirtualHpOffset)] -> CostCentreStack ->
457              C_SRT -> LocalReg -> Int -> StgExpr -> FCode ()
458 thunkCode cl_info fv_details cc srt node arity body 
459   = do  { let node_points = nodeMustPointToIt (closureLFInfo cl_info)
460         ; tickyEnterThunk cl_info
461         ; ldvEnterClosure cl_info  -- NB: Node always points when profiling
462         ; granThunk node_points
463
464         -- Heap overflow check
465         ; entryHeapCheck node arity [] srt $ do
466         {       -- Overwrite with black hole if necessary
467                 -- but *after* the heap-overflow check
468           whenC (blackHoleOnEntry cl_info && node_points)
469                 (blackHoleIt cl_info)
470
471                 -- Push update frame
472         ; setupUpdate cl_info node $
473                 -- We only enter cc after setting up update so
474                 -- that cc of enclosing scope will be recorded
475                 -- in update frame CAF/DICT functions will be
476                 -- subsumed by this enclosing cc
477             do { enterCostCentre cl_info cc body
478                ; let lf_info = closureLFInfo cl_info
479                ; fv_bindings <- mapM bind_fv fv_details
480                ; load_fvs node lf_info fv_bindings
481                ; cgExpr body }}}
482
483
484 ------------------------------------------------------------------------
485 --              Update and black-hole wrappers
486 ------------------------------------------------------------------------
487
488 blackHoleIt :: ClosureInfo -> FCode ()
489 -- Only called for closures with no args
490 -- Node points to the closure
491 blackHoleIt closure_info = emitBlackHoleCode (closureSingleEntry closure_info)
492
493 emitBlackHoleCode :: Bool -> FCode ()
494 emitBlackHoleCode is_single_entry 
495   | eager_blackholing = do 
496         tickyBlackHole (not is_single_entry)
497         emit (mkStore (CmmReg nodeReg) (CmmLit (CmmLabel bh_lbl)))
498   | otherwise = 
499         nopC
500   where
501     bh_lbl | is_single_entry = mkRtsDataLabel (sLit "stg_SE_BLACKHOLE_info")
502            | otherwise       = mkRtsDataLabel (sLit "stg_BLACKHOLE_info")
503
504         -- If we wanted to do eager blackholing with slop filling,
505         -- we'd need to do it at the *end* of a basic block, otherwise
506         -- we overwrite the free variables in the thunk that we still
507         -- need.  We have a patch for this from Andy Cheadle, but not
508         -- incorporated yet. --SDM [6/2004]
509         --
510         -- Profiling needs slop filling (to support LDV profiling), so
511         -- currently eager blackholing doesn't work with profiling.
512         --
513         -- Previously, eager blackholing was enabled when ticky-ticky
514         -- was on. But it didn't work, and it wasn't strictly necessary 
515         -- to bring back minimal ticky-ticky, so now EAGER_BLACKHOLING 
516         -- is unconditionally disabled. -- krc 1/2007
517
518     eager_blackholing = False 
519
520 setupUpdate :: ClosureInfo -> LocalReg -> FCode () -> FCode ()
521         -- Nota Bene: this function does not change Node (even if it's a CAF),
522         -- so that the cost centre in the original closure can still be
523         -- extracted by a subsequent enterCostCentre
524 setupUpdate closure_info node body
525   | closureReEntrant closure_info
526   = body
527
528   | not (isStaticClosure closure_info)
529   = if closureUpdReqd closure_info
530     then do { tickyPushUpdateFrame;
531             ; pushUpdateFrame [CmmReg (CmmLocal node),
532                                mkLblExpr mkUpdInfoLabel] body }
533     else do { tickyUpdateFrameOmitted; body}
534  
535   | otherwise   -- A static closure
536   = do  { tickyUpdateBhCaf closure_info
537
538         ; if closureUpdReqd closure_info
539           then do       -- Blackhole the (updatable) CAF:
540                 { upd_closure <- link_caf closure_info True
541                 ; pushUpdateFrame [CmmReg (CmmLocal upd_closure),
542                                    mkLblExpr mkUpdInfoLabel] body }
543           else do {tickyUpdateFrameOmitted; body}
544     }
545
546 -- Push the update frame on the stack in the Entry area,
547 -- leaving room for the return address that is already
548 -- at the old end of the area.
549 pushUpdateFrame :: [CmmExpr] -> FCode () -> FCode ()
550 pushUpdateFrame es body
551   = do updfr  <- getUpdFrameOff
552        offset <- foldM push updfr es
553        withUpdFrameOff offset body
554      where push off e =
555              do emit (mkStore (CmmStackSlot (CallArea Old) base) e)
556                 return base
557              where base = off + widthInBytes (cmmExprWidth e)
558
559 -----------------------------------------------------------------------------
560 -- Entering a CAF
561 --
562 -- When a CAF is first entered, it creates a black hole in the heap,
563 -- and updates itself with an indirection to this new black hole.
564 --
565 -- We update the CAF with an indirection to a newly-allocated black
566 -- hole in the heap.  We also set the blocking queue on the newly
567 -- allocated black hole to be empty.
568 --
569 -- Why do we make a black hole in the heap when we enter a CAF?
570 --    
571 --     - for a  generational garbage collector, which needs a fast
572 --       test for whether an updatee is in an old generation or not
573 --
574 --     - for the parallel system, which can implement updates more
575 --       easily if the updatee is always in the heap. (allegedly).
576 --
577 -- When debugging, we maintain a separate CAF list so we can tell when
578 -- a CAF has been garbage collected.
579
580 -- newCAF must be called before the itbl ptr is overwritten, since
581 -- newCAF records the old itbl ptr in order to do CAF reverting
582 -- (which Hugs needs to do in order that combined mode works right.)
583 --
584
585 -- ToDo [Feb 04]  This entire link_caf nonsense could all be moved
586 -- into the "newCAF" RTS procedure, which we call anyway, including
587 -- the allocation of the black-hole indirection closure.
588 -- That way, code size would fall, the CAF-handling code would 
589 -- be closer together, and the compiler wouldn't need to know
590 -- about off_indirectee etc.
591
592 link_caf :: ClosureInfo
593          -> Bool                -- True <=> updatable, False <=> single-entry
594          -> FCode LocalReg      -- Returns amode for closure to be updated
595 -- To update a CAF we must allocate a black hole, link the CAF onto the
596 -- CAF list, then update the CAF to point to the fresh black hole.
597 -- This function returns the address of the black hole, so it can be
598 -- updated with the new value when available.  The reason for all of this
599 -- is that we only want to update dynamic heap objects, not static ones,
600 -- so that generational GC is easier.
601 link_caf cl_info is_upd = do
602   {     -- Alloc black hole specifying CC_HDR(Node) as the cost centre
603   ; let use_cc   = costCentreFrom (CmmReg nodeReg)
604         blame_cc = use_cc
605   ; (hp_rel, init) <- allocDynClosure bh_cl_info use_cc blame_cc []
606   ; emit init
607
608         -- Call the RTS function newCAF to add the CAF to the CafList
609         -- so that the garbage collector can find them
610         -- This must be done *before* the info table pointer is overwritten, 
611         -- because the old info table ptr is needed for reversion
612   ; emitRtsCallWithVols (sLit "newCAF") [(CmmReg nodeReg,AddrHint)] [node] False
613         -- node is live, so save it.
614
615         -- Overwrite the closure with a (static) indirection 
616         -- to the newly-allocated black hole
617   ; emit (mkStore (cmmRegOffW nodeReg off_indirectee) (CmmReg (CmmLocal hp_rel)) <*>
618           mkStore (CmmReg nodeReg) ind_static_info)
619
620   ; return hp_rel }
621   where
622     bh_cl_info :: ClosureInfo
623     bh_cl_info | is_upd    = cafBlackHoleClosureInfo   cl_info
624                | otherwise = seCafBlackHoleClosureInfo cl_info
625
626     ind_static_info :: CmmExpr
627     ind_static_info = mkLblExpr mkIndStaticInfoLabel
628
629     off_indirectee :: WordOff
630     off_indirectee = fixedHdrSize + oFFSET_StgInd_indirectee*wORD_SIZE
631
632
633 ------------------------------------------------------------------------
634 --              Profiling 
635 ------------------------------------------------------------------------
636
637 -- For "global" data constructors the description is simply occurrence
638 -- name of the data constructor itself.  Otherwise it is determined by
639 -- @closureDescription@ from the let binding information.
640
641 closureDescription :: Module            -- Module
642                    -> Name              -- Id of closure binding
643                    -> String
644         -- Not called for StgRhsCon which have global info tables built in
645         -- CgConTbls.lhs with a description generated from the data constructor
646 closureDescription mod_name name
647   = showSDocDump (char '<' <>
648                     (if isExternalName name
649                       then ppr name -- ppr will include the module name prefix
650                       else pprModule mod_name <> char '.' <> ppr name) <>
651                     char '>')
652    -- showSDocDump, because we want to see the unique on the Name.
653