* Refactor CLabel.RtsLabel to CLabel.CmmLabel
[ghc-hetmet.git] / compiler / codeGen / CgClosure.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5 \section[CgClosure]{Code generation for closures}
6
7 This module provides the support code for @StgToAbstractC@ to deal
8 with {\em closures} on the RHSs of let(rec)s.  See also
9 @CgCon@, which deals with constructors.
10
11 \begin{code}
12 module CgClosure ( cgTopRhsClosure, 
13                    cgStdRhsClosure, 
14                    cgRhsClosure,
15                    emitBlackHoleCode,
16                    ) where
17
18 #include "HsVersions.h"
19
20 import {-# SOURCE #-} CgExpr ( cgExpr )
21
22 import CgMonad
23 import CgBindery
24 import CgHeapery
25 import CgStackery
26 import CgProf
27 import CgTicky
28 import CgParallel
29 import CgInfoTbls
30 import CgCallConv
31 import CgUtils
32 import ClosureInfo
33 import SMRep
34 import Cmm
35 import CmmUtils
36 import CLabel
37 import StgSyn
38 import CostCentre       
39 import Id
40 import Name
41 import Module
42 import ListSetOps
43 import Util
44 import BasicTypes
45 import StaticFlags
46 import DynFlags
47 import Constants
48 import Outputable
49 import FastString
50
51 import Data.List
52 \end{code}
53
54 %********************************************************
55 %*                                                      *
56 \subsection[closures-no-free-vars]{Top-level closures}
57 %*                                                      *
58 %********************************************************
59
60 For closures bound at top level, allocate in static space.
61 They should have no free variables.
62
63 \begin{code}
64 cgTopRhsClosure :: Id
65                 -> CostCentreStack      -- Optional cost centre annotation
66                 -> StgBinderInfo
67                 -> UpdateFlag
68                 -> [Id]         -- Args
69                 -> StgExpr
70                 -> FCode (Id, CgIdInfo)
71
72 cgTopRhsClosure id ccs binder_info upd_flag args body = do
73   {     -- LAY OUT THE OBJECT
74     let name = idName id
75   ; lf_info  <- mkClosureLFInfo id TopLevel [] upd_flag args
76   ; srt_info <- getSRTInfo
77   ; mod_name <- getModuleName
78   ; let descr         = closureDescription mod_name name
79         closure_info  = mkClosureInfo True id lf_info 0 0 srt_info descr
80         closure_label = mkLocalClosureLabel name $ idCafInfo id
81         cg_id_info    = stableIdInfo id (mkLblExpr closure_label) lf_info
82         closure_rep   = mkStaticClosureFields closure_info ccs True []
83
84          -- BUILD THE OBJECT, AND GENERATE INFO TABLE (IF NECESSARY)
85   ; emitDataLits closure_label closure_rep
86   ; forkClosureBody (closureCodeBody binder_info closure_info
87                                      ccs args body)
88
89   ; returnFC (id, cg_id_info) }
90 \end{code}
91
92 %********************************************************
93 %*                                                      *
94 \subsection[non-top-level-closures]{Non top-level closures}
95 %*                                                      *
96 %********************************************************
97
98 For closures with free vars, allocate in heap.
99
100 \begin{code}
101 cgStdRhsClosure
102         :: Id
103         -> CostCentreStack      -- Optional cost centre annotation
104         -> StgBinderInfo
105         -> [Id]                 -- Free vars
106         -> [Id]                 -- Args
107         -> StgExpr
108         -> LambdaFormInfo
109         -> [StgArg]             -- payload
110         -> FCode (Id, CgIdInfo)
111
112 cgStdRhsClosure bndr cc _bndr_info _fvs args body lf_info payload 
113   = do  -- AHA!  A STANDARD-FORM THUNK
114   {     -- LAY OUT THE OBJECT
115     amodes <- getArgAmodes payload
116   ; mod_name <- getModuleName
117   ; let (tot_wds, ptr_wds, amodes_w_offsets) 
118             = mkVirtHeapOffsets (isLFThunk lf_info) amodes
119
120         descr        = closureDescription mod_name (idName bndr)
121         closure_info = mkClosureInfo False      -- Not static
122                                      bndr lf_info tot_wds ptr_wds 
123                                      NoC_SRT    -- No SRT for a std-form closure
124                                      descr
125                 
126   ; (use_cc, blame_cc) <- chooseDynCostCentres cc args body
127
128         -- BUILD THE OBJECT
129   ; heap_offset <- allocDynClosure closure_info use_cc blame_cc amodes_w_offsets
130
131         -- RETURN
132   ; returnFC (bndr, heapIdInfo bndr heap_offset lf_info) }
133 \end{code}
134
135 Here's the general case.
136
137 \begin{code}
138 cgRhsClosure    :: Id
139                 -> CostCentreStack      -- Optional cost centre annotation
140                 -> StgBinderInfo
141                 -> [Id]                 -- Free vars
142                 -> UpdateFlag
143                 -> [Id]                 -- Args
144                 -> StgExpr
145                 -> FCode (Id, CgIdInfo)
146
147 cgRhsClosure bndr cc bndr_info fvs upd_flag args body = do
148   {     -- LAY OUT THE OBJECT
149         -- If the binder is itself a free variable, then don't store
150         -- it in the closure.  Instead, just bind it to Node on entry.
151         -- NB we can be sure that Node will point to it, because we
152         -- havn't told mkClosureLFInfo about this; so if the binder
153         -- _was_ a free var of its RHS, mkClosureLFInfo thinks it *is*
154         -- stored in the closure itself, so it will make sure that
155         -- Node points to it...
156     let
157         name         = idName bndr
158         bndr_is_a_fv = bndr `elem` fvs
159         reduced_fvs | bndr_is_a_fv = fvs `minusList` [bndr]
160                     | otherwise    = fvs
161
162   ; lf_info <- mkClosureLFInfo bndr NotTopLevel fvs upd_flag args
163   ; fv_infos <- mapFCs getCgIdInfo reduced_fvs
164   ; srt_info <- getSRTInfo
165   ; mod_name <- getModuleName
166   ; let bind_details :: [(CgIdInfo, VirtualHpOffset)]
167         (tot_wds, ptr_wds, bind_details) 
168            = mkVirtHeapOffsets (isLFThunk lf_info) (map add_rep fv_infos)
169
170         add_rep info = (cgIdInfoArgRep info, info)
171
172         descr        = closureDescription mod_name name
173         closure_info = mkClosureInfo False      -- Not static
174                                      bndr lf_info tot_wds ptr_wds
175                                      srt_info descr
176
177         -- BUILD ITS INFO TABLE AND CODE
178   ; forkClosureBody (do
179         {       -- Bind the fvs
180           let 
181               -- A function closure pointer may be tagged, so we
182               -- must take it into account when accessing the free variables.
183               mbtag       = tagForArity (length args)
184               bind_fv (info, offset)
185                 | Just tag <- mbtag
186                 = bindNewToUntagNode (cgIdInfoId info) offset (cgIdInfoLF info) tag
187                 | otherwise
188                 = bindNewToNode (cgIdInfoId info) offset (cgIdInfoLF info)
189         ; mapCs bind_fv bind_details
190
191                 -- Bind the binder itself, if it is a free var
192         ; whenC bndr_is_a_fv (bindNewToReg bndr nodeReg lf_info)
193         
194                 -- Compile the body
195         ; closureCodeBody bndr_info closure_info cc args body })
196
197         -- BUILD THE OBJECT
198   ; let
199         to_amode (info, offset) = do { amode <- idInfoToAmode info
200                                      ; return (amode, offset) }
201   ; (use_cc, blame_cc) <- chooseDynCostCentres cc args body
202   ; amodes_w_offsets <- mapFCs to_amode bind_details
203   ; heap_offset <- allocDynClosure closure_info use_cc blame_cc amodes_w_offsets
204
205         -- RETURN
206   ; returnFC (bndr, heapIdInfo bndr heap_offset lf_info) }
207
208
209 mkClosureLFInfo :: Id           -- The binder
210                 -> TopLevelFlag -- True of top level
211                 -> [Id]         -- Free vars
212                 -> UpdateFlag   -- Update flag
213                 -> [Id]         -- Args
214                 -> FCode LambdaFormInfo
215 mkClosureLFInfo bndr top fvs upd_flag args
216   | null args = return (mkLFThunk (idType bndr) top fvs upd_flag)
217   | otherwise = do { arg_descr <- mkArgDescr (idName bndr) args
218                    ; return (mkLFReEntrant top fvs args arg_descr) }
219 \end{code}
220
221
222 %************************************************************************
223 %*                                                                      *
224 \subsection[code-for-closures]{The code for closures}
225 %*                                                                      *
226 %************************************************************************
227
228 \begin{code}
229 closureCodeBody :: StgBinderInfo
230                 -> ClosureInfo     -- Lots of information about this closure
231                 -> CostCentreStack -- Optional cost centre attached to closure
232                 -> [Id]
233                 -> StgExpr
234                 -> Code
235 \end{code}
236
237 There are two main cases for the code for closures.  If there are {\em
238 no arguments}, then the closure is a thunk, and not in normal form.
239 So it should set up an update frame (if it is shared).
240 NB: Thunks cannot have a primitive type!
241
242 \begin{code}
243 closureCodeBody _binder_info cl_info cc [{- No args i.e. thunk -}] body = do
244   { body_absC <- getCgStmts $ do
245         { tickyEnterThunk cl_info
246         ; ldvEnterClosure cl_info  -- NB: Node always points when profiling
247         ; thunkWrapper cl_info $ do
248                 -- We only enter cc after setting up update so
249                 -- that cc of enclosing scope will be recorded
250                 -- in update frame CAF/DICT functions will be
251                 -- subsumed by this enclosing cc
252             { enterCostCentre cl_info cc body
253             ; stmtsC [CmmComment $ mkFastString $ showSDoc $ ppr body]
254             ; cgExpr body }
255         }
256     
257   ; emitClosureCodeAndInfoTable cl_info [] body_absC }
258 \end{code}
259
260 If there is /at least one argument/, then this closure is in
261 normal form, so there is no need to set up an update frame.
262
263 The Macros for GrAnSim are produced at the beginning of the
264 argSatisfactionCheck (by calling fetchAndReschedule).  There info if
265 Node points to closure is available. -- HWL
266
267 \begin{code}
268 closureCodeBody _binder_info cl_info cc args body 
269   = ASSERT( length args > 0 )
270   do {  -- Get the current virtual Sp (it might not be zero, 
271         -- eg. if we're compiling a let-no-escape).
272     vSp <- getVirtSp
273   ; let (reg_args, other_args) = assignCallRegs (addIdReps args)
274         (sp_top, stk_args)     = mkVirtStkOffsets vSp other_args
275
276         -- Allocate the global ticky counter
277   ; let ticky_ctr_lbl = mkRednCountsLabel (closureName cl_info) (clHasCafRefs cl_info)
278   ; emitTickyCounter cl_info args sp_top
279
280         -- ...and establish the ticky-counter 
281         -- label for this block
282   ; setTickyCtrLabel ticky_ctr_lbl $ do
283
284         -- Emit the slow-entry code
285   { reg_save_code <- mkSlowEntryCode cl_info reg_args
286
287         -- Emit the main entry code
288   ; blks <- forkProc $
289             mkFunEntryCode cl_info cc reg_args stk_args
290                            sp_top reg_save_code body
291   ; emitClosureCodeAndInfoTable cl_info [] blks
292   }}
293
294
295
296 mkFunEntryCode :: ClosureInfo
297                -> CostCentreStack
298                -> [(Id,GlobalReg)]        -- Args in regs
299                -> [(Id,VirtualSpOffset)]  -- Args on stack
300                -> VirtualSpOffset         -- Last allocated word on stack
301                -> CmmStmts                -- Register-save code in case of GC
302                -> StgExpr
303                -> Code
304 -- The main entry code for the closure
305 mkFunEntryCode cl_info cc reg_args stk_args sp_top reg_save_code body = do
306   {     -- Bind args to regs/stack as appropriate,
307         -- and record expected position of sps
308   ; bindArgsToRegs  reg_args
309   ; bindArgsToStack stk_args
310   ; setRealAndVirtualSp sp_top
311
312         -- Enter the cost-centre, if required
313         -- ToDo: It's not clear why this is outside the funWrapper,
314         --       but the tickyEnterFun is inside. Perhaps we can put
315         --       them together?
316   ; enterCostCentre cl_info cc body
317
318         -- Do the business
319   ; funWrapper cl_info reg_args reg_save_code $ do
320         { tickyEnterFun cl_info
321         ; cgExpr body }
322   }
323 \end{code}
324
325 The "slow entry" code for a function.  This entry point takes its
326 arguments on the stack.  It loads the arguments into registers
327 according to the calling convention, and jumps to the function's
328 normal entry point.  The function's closure is assumed to be in
329 R1/node.
330
331 The slow entry point is used in two places:
332
333  (a) unknown calls: eg. stg_PAP_entry 
334  (b) returning from a heap-check failure
335
336 \begin{code}
337 mkSlowEntryCode :: ClosureInfo -> [(Id,GlobalReg)] -> FCode CmmStmts
338 -- If this function doesn't have a specialised ArgDescr, we need
339 -- to generate the function's arg bitmap, slow-entry code, and
340 -- register-save code for the heap-check failure
341 -- Here, we emit the slow-entry code, and 
342 -- return the register-save assignments
343 mkSlowEntryCode cl_info reg_args
344   | Just (_, ArgGen _) <- closureFunInfo cl_info
345   = do  { emitSimpleProc slow_lbl (emitStmts load_stmts)
346         ; return save_stmts }
347   | otherwise = return noStmts
348   where
349      name = closureName cl_info
350      has_caf_refs = clHasCafRefs cl_info
351      slow_lbl = mkSlowEntryLabel name has_caf_refs
352
353      load_stmts = mkStmts load_assts `plusStmts` mkStmts [stk_adj_pop, jump_to_entry]
354      save_stmts = oneStmt stk_adj_push `plusStmts`  mkStmts save_assts
355
356      reps_w_regs :: [(CgRep,GlobalReg)]
357      reps_w_regs = [(idCgRep id, reg) | (id,reg) <- reverse reg_args]
358      (final_stk_offset, stk_offsets)
359         = mapAccumL (\off (rep,_) -> (off + cgRepSizeW rep, off))
360                     0 reps_w_regs
361
362      load_assts = zipWithEqual "mk_load" mk_load reps_w_regs stk_offsets
363      mk_load (rep,reg) offset = CmmAssign (CmmGlobal reg) 
364                                           (CmmLoad (cmmRegOffW spReg offset)
365                                                    (argMachRep rep))
366
367      save_assts = zipWithEqual "mk_save" mk_save reps_w_regs stk_offsets
368      mk_save (rep,reg) offset = ASSERT( argMachRep rep `cmmEqType` globalRegType reg )
369                                 CmmStore (cmmRegOffW spReg offset) 
370                                          (CmmReg (CmmGlobal reg))
371
372      stk_adj_pop   = CmmAssign spReg (cmmRegOffW spReg final_stk_offset)
373      stk_adj_push  = CmmAssign spReg (cmmRegOffW spReg (- final_stk_offset))
374      jump_to_entry = CmmJump (mkLblExpr (enterLocalIdLabel name has_caf_refs)) []
375 \end{code}
376
377
378 %************************************************************************
379 %*                                                                      *
380 \subsubsection[closure-code-wrappers]{Wrappers around closure code}
381 %*                                                                      *
382 %************************************************************************
383
384 \begin{code}
385 thunkWrapper:: ClosureInfo -> Code -> Code
386 thunkWrapper closure_info thunk_code = do
387   { let node_points = nodeMustPointToIt (closureLFInfo closure_info)
388
389     -- HWL: insert macros for GrAnSim; 2 versions depending on liveness of node
390     -- (we prefer fetchAndReschedule-style context switches to yield ones)
391   ; if node_points 
392     then granFetchAndReschedule [] node_points 
393     else granYield              [] node_points
394
395         -- Stack and/or heap checks
396   ; thunkEntryChecks closure_info $ do
397         {
398           dflags <- getDynFlags
399           -- Overwrite with black hole if necessary
400         ; whenC (blackHoleOnEntry dflags closure_info && node_points)
401                 (blackHoleIt closure_info)
402         ; setupUpdate closure_info thunk_code }
403                 -- setupUpdate *encloses* the thunk_code
404   }
405
406 funWrapper :: ClosureInfo       -- Closure whose code body this is
407            -> [(Id,GlobalReg)]  -- List of argument registers (if any)
408            -> CmmStmts          -- reg saves for the heap check failure
409            -> Code              -- Body of function being compiled
410            -> Code
411 funWrapper closure_info arg_regs reg_save_code fun_body = do
412   { let node_points = nodeMustPointToIt (closureLFInfo closure_info)
413
414   {-
415         -- Debugging: check that R1 has the correct tag
416   ; let tag = funTag closure_info
417   ; whenC (tag /= 0 && node_points) $ do
418         l <- newLabelC
419         stmtC (CmmCondBranch (CmmMachOp mo_wordEq [cmmGetTag (CmmReg nodeReg),
420                                                    CmmLit (mkIntCLit tag)]) l)
421         stmtC (CmmStore (CmmLit (mkWordCLit 0)) (CmmLit (mkWordCLit 0)))
422         labelC l
423   -}
424
425         -- Enter for Ldv profiling
426   ; whenC node_points (ldvEnterClosure closure_info)
427
428         -- GranSim yeild poin
429   ; granYield arg_regs node_points
430
431         -- Heap and/or stack checks wrap the function body
432   ; funEntryChecks closure_info reg_save_code 
433                    fun_body
434   }
435 \end{code}
436
437
438 %************************************************************************
439 %*                                                                      *
440 \subsubsubsection[update-and-BHs]{Update and black-hole wrappers}
441 %*                                                                      *
442 %************************************************************************
443
444
445 \begin{code}
446 blackHoleIt :: ClosureInfo -> Code
447 -- Only called for closures with no args
448 -- Node points to the closure
449 blackHoleIt closure_info = emitBlackHoleCode (closureSingleEntry closure_info)
450
451 emitBlackHoleCode :: Bool -> Code
452 emitBlackHoleCode is_single_entry = do
453
454   dflags <- getDynFlags
455
456         -- If we wanted to do eager blackholing with slop filling,
457         -- we'd need to do it at the *end* of a basic block, otherwise
458         -- we overwrite the free variables in the thunk that we still
459         -- need.  We have a patch for this from Andy Cheadle, but not
460         -- incorporated yet. --SDM [6/2004]
461         --
462         -- Profiling needs slop filling (to support LDV profiling), so
463         -- currently eager blackholing doesn't work with profiling.
464         --
465         -- Previously, eager blackholing was enabled when ticky-ticky
466         -- was on. But it didn't work, and it wasn't strictly necessary 
467         -- to bring back minimal ticky-ticky, so now EAGER_BLACKHOLING 
468         -- is unconditionally disabled. -- krc 1/2007
469
470   let eager_blackholing =  not opt_SccProfilingOn
471                         && dopt Opt_EagerBlackHoling dflags
472
473   if eager_blackholing
474      then do
475           tickyBlackHole (not is_single_entry)
476           let bh_info = CmmReg (CmmGlobal EagerBlackholeInfo)
477           stmtC (CmmStore (CmmReg nodeReg) bh_info)
478      else
479           nopC
480 \end{code}
481
482 \begin{code}
483 setupUpdate :: ClosureInfo -> Code -> Code      -- Only called for closures with no args
484         -- Nota Bene: this function does not change Node (even if it's a CAF),
485         -- so that the cost centre in the original closure can still be
486         -- extracted by a subsequent enterCostCentre
487 setupUpdate closure_info code
488   | closureReEntrant closure_info
489   = code
490
491   | not (isStaticClosure closure_info)
492   = if closureUpdReqd closure_info
493     then do { tickyPushUpdateFrame;  pushUpdateFrame (CmmReg nodeReg) code }
494     else do { tickyUpdateFrameOmitted; code }
495  
496   | otherwise   -- A static closure
497   = do  { tickyUpdateBhCaf closure_info
498
499         ; if closureUpdReqd closure_info
500           then do       -- Blackhole the (updatable) CAF:
501                 { upd_closure <- link_caf closure_info True
502                 ; pushUpdateFrame upd_closure code }
503           else do
504                 { -- krc: removed some ticky-related code here.
505                 ; tickyUpdateFrameOmitted
506                 ; code }
507     }
508
509
510 -----------------------------------------------------------------------------
511 -- Entering a CAF
512 --
513 -- When a CAF is first entered, it creates a black hole in the heap,
514 -- and updates itself with an indirection to this new black hole.
515 --
516 -- We update the CAF with an indirection to a newly-allocated black
517 -- hole in the heap.  We also set the blocking queue on the newly
518 -- allocated black hole to be empty.
519 --
520 -- Why do we make a black hole in the heap when we enter a CAF?
521 --    
522 --     - for a  generational garbage collector, which needs a fast
523 --       test for whether an updatee is in an old generation or not
524 --
525 --     - for the parallel system, which can implement updates more
526 --       easily if the updatee is always in the heap. (allegedly).
527 --
528 -- When debugging, we maintain a separate CAF list so we can tell when
529 -- a CAF has been garbage collected.
530
531 -- newCAF must be called before the itbl ptr is overwritten, since
532 -- newCAF records the old itbl ptr in order to do CAF reverting
533 -- (which Hugs needs to do in order that combined mode works right.)
534 --
535
536 -- ToDo [Feb 04]  This entire link_caf nonsense could all be moved
537 -- into the "newCAF" RTS procedure, which we call anyway, including
538 -- the allocation of the black-hole indirection closure.
539 -- That way, code size would fall, the CAF-handling code would 
540 -- be closer together, and the compiler wouldn't need to know
541 -- about off_indirectee etc.
542
543 link_caf :: ClosureInfo
544          -> Bool                -- True <=> updatable, False <=> single-entry
545          -> FCode CmmExpr       -- Returns amode for closure to be updated
546 -- To update a CAF we must allocate a black hole, link the CAF onto the
547 -- CAF list, then update the CAF to point to the fresh black hole.
548 -- This function returns the address of the black hole, so it can be
549 -- updated with the new value when available.  The reason for all of this
550 -- is that we only want to update dynamic heap objects, not static ones,
551 -- so that generational GC is easier.
552 link_caf cl_info _is_upd = do
553   {     -- Alloc black hole specifying CC_HDR(Node) as the cost centre
554   ; let use_cc   = costCentreFrom (CmmReg nodeReg)
555         blame_cc = use_cc
556   ; hp_offset <- allocDynClosure bh_cl_info use_cc blame_cc []
557   ; hp_rel    <- getHpRelOffset hp_offset
558
559         -- Call the RTS function newCAF to add the CAF to the CafList
560         -- so that the garbage collector can find them
561         -- This must be done *before* the info table pointer is overwritten, 
562         -- because the old info table ptr is needed for reversion
563   ; emitRtsCallWithVols rtsPackageId (fsLit "newCAF") [CmmHinted (CmmReg nodeReg) AddrHint] [node] False
564         -- node is live, so save it.
565
566         -- Overwrite the closure with a (static) indirection 
567         -- to the newly-allocated black hole
568   ; stmtsC [ CmmStore (cmmRegOffW nodeReg off_indirectee) hp_rel
569            , CmmStore (CmmReg nodeReg) ind_static_info ]
570
571   ; returnFC hp_rel }
572   where
573     bh_cl_info :: ClosureInfo
574     bh_cl_info = cafBlackHoleClosureInfo cl_info
575
576     ind_static_info :: CmmExpr
577     ind_static_info = mkLblExpr mkIndStaticInfoLabel
578
579     off_indirectee :: WordOff
580     off_indirectee = fixedHdrSize + oFFSET_StgInd_indirectee*wORD_SIZE
581 \end{code}
582
583
584 %************************************************************************
585 %*                                                                      *
586 \subsection[CgClosure-Description]{Profiling Closure Description.}
587 %*                                                                      *
588 %************************************************************************
589
590 For "global" data constructors the description is simply occurrence
591 name of the data constructor itself.  Otherwise it is determined by
592 @closureDescription@ from the let binding information.
593
594 \begin{code}
595 closureDescription :: Module            -- Module
596                    -> Name              -- Id of closure binding
597                    -> String
598         -- Not called for StgRhsCon which have global info tables built in
599         -- CgConTbls.lhs with a description generated from the data constructor
600 closureDescription mod_name name
601   = showSDocDumpOneLine (char '<' <>
602                     (if isExternalName name
603                       then ppr name -- ppr will include the module name prefix
604                       else pprModule mod_name <> char '.' <> ppr name) <>
605                     char '>')
606    -- showSDocDumpOneLine, because we want to see the unique on the Name.
607 \end{code}
608