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