[project @ 1997-05-19 00:12:10 by sof]
[ghc-hetmet.git] / ghc / compiler / codeGen / ClosureInfo.lhs
1
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[ClosureInfo]{Data structures which describe closures}
5
6 Much of the rationale for these things is in the ``details'' part of
7 the STG paper.
8
9 \begin{code}
10 #include "HsVersions.h"
11
12 module ClosureInfo (
13         ClosureInfo, LambdaFormInfo, SMRep,     -- all abstract
14         StandardFormInfo,
15
16         EntryConvention(..),
17
18         mkClosureLFInfo, mkConLFInfo, mkSelectorLFInfo, mkVapLFInfo,
19         mkLFImported, mkLFArgument, mkLFLetNoEscape,
20
21         closureSize, closureHdrSize,
22         closureNonHdrSize, closureSizeWithoutFixedHdr,
23         closureGoodStuffSize, closurePtrsSize,
24         slopSize, fitsMinUpdSize,
25
26         layOutDynClosure, layOutDynCon, layOutStaticClosure,
27         layOutStaticNoFVClosure, layOutPhantomClosure,
28         mkVirtHeapOffsets,
29
30         nodeMustPointToIt, getEntryConvention,
31         blackHoleOnEntry,
32
33         staticClosureRequired,
34         slowFunEntryCodeRequired, funInfoTableRequired,
35         stdVapRequired, noUpdVapRequired,
36
37         closureId, infoTableLabelFromCI, fastLabelFromCI,
38         closureLabelFromCI,
39         entryLabelFromCI, 
40         closureLFInfo, closureSMRep, closureUpdReqd,
41         closureSingleEntry, closureSemiTag, closureType,
42         closureReturnsUnboxedType, getStandardFormThunkInfo,
43
44         isToplevClosure,
45         closureKind, closureTypeDescr,          -- profiling
46
47         isStaticClosure, allocProfilingMsg,
48         blackHoleClosureInfo,
49         maybeSelectorInfo,
50
51         dataConLiveness                         -- concurrency
52     ) where
53
54 IMP_Ubiq(){-uitous-}
55 IMPORT_DELOOPER(AbsCLoop)               -- here for paranoia-checking
56
57 import AbsCSyn
58 import StgSyn
59 import CgMonad
60
61 import Constants        ( mIN_UPD_SIZE, mIN_SIZE_NonUpdHeapObject,
62                           mAX_SPEC_ALL_PTRS, mAX_SPEC_MIXED_FIELDS,
63                           mAX_SPEC_ALL_NONPTRS,
64                           oTHER_TAG
65                         )
66 import CgRetConv        ( assignRegs, dataReturnConvAlg,
67                           DataReturnConvention(..)
68                         )
69 import CLabel           ( mkStdEntryLabel, mkFastEntryLabel,
70                           mkPhantomInfoTableLabel, mkInfoTableLabel,
71                           mkConInfoTableLabel, mkStaticClosureLabel, 
72                           mkBlackHoleInfoTableLabel, mkVapInfoTableLabel,
73                           mkStaticInfoTableLabel, mkStaticConEntryLabel,
74                           mkConEntryLabel, mkClosureLabel, mkVapEntryLabel
75                         )
76 import CmdLineOpts      ( opt_SccProfilingOn, opt_ForConcurrent )
77 import HeapOffs         ( intOff, addOff, totHdrSize, varHdrSize,
78                           SYN_IE(VirtualHeapOffset), HeapOffset
79                         )
80 import Id               ( idType, getIdArity,
81                           externallyVisibleId,
82                           dataConTag, fIRST_TAG,
83                           isDataCon, isNullaryDataCon, dataConTyCon,
84                           isTupleCon, SYN_IE(DataCon),
85                           GenId{-instance Eq-}, SYN_IE(Id)
86                         )
87 import IdInfo           ( ArityInfo(..) )
88 import Maybes           ( maybeToBool )
89 import Name             ( getOccString )
90 import PprStyle         ( PprStyle(..) )
91 import PprType          ( getTyDescription, GenType{-instance Outputable-} )
92 import Pretty           --ToDo:rm
93 import PrelInfo         ( maybeCharLikeTyCon, maybeIntLikeTyCon )
94 import PrimRep          ( getPrimRepSize, separateByPtrFollowness, PrimRep )
95 import SMRep            -- all of it
96 import TyCon            ( TyCon{-instance NamedThing-} )
97 import Type             ( isPrimType, splitForAllTy, splitFunTyExpandingDictsAndPeeking,
98                           mkFunTys, maybeAppSpecDataTyConExpandingDicts,
99                           SYN_IE(Type)
100                         )
101 import Util             ( isIn, mapAccumL, panic, pprPanic, assertPanic )
102 #if __GLASGOW_HASKELL__ >= 202
103 import Outputable       ( Outputable(..) )
104 #endif
105 \end{code}
106
107 The ``wrapper'' data type for closure information:
108
109 \begin{code}
110 data ClosureInfo
111   = MkClosureInfo
112         Id                      -- The thing bound to this closure
113         LambdaFormInfo          -- info derivable from the *source*
114         SMRep                   -- representation used by storage manager
115 \end{code}
116
117 %************************************************************************
118 %*                                                                      *
119 \subsection[ClosureInfo-OLD-DOC]{OLD DOCUMENTATION PROBABLY SUPERCEDED BY stg-details}
120 %*                                                                      *
121 %************************************************************************
122
123 We can optimise the function-entry code as follows.
124 \begin{itemize}
125
126 \item   If the ``function'' is not updatable, we can jump directly to its
127         entry code, rather than indirecting via the info pointer in the
128         closure.  (For updatable thunks we must go via the closure, in
129         case it has been updated.)
130
131 \item   If the former bullet applies, and the application we are
132         compiling gives the function as many arguments as it needs, we
133         can jump to its fast-entry code.  (This only applies if the
134         function has one or more args, because zero-arg closures have
135         no fast-entry code.)
136
137 \item   If the function is a top-level non-constructor or imported, there
138         is no need to make Node point to its closure.  In order for
139         this to be right, we need to ensure that:
140         \begin{itemize}
141         \item   If such closures are updatable then they push their
142                 static address in the update frame, not Node. Actually
143                 we create a black hole and push its address.
144
145         \item   The arg satisfaction check should load Node before jumping to
146                 UpdatePAP.
147
148         \item   Top-level constructor closures need careful handling.  If we are to
149                 jump direct to the constructor code, we must load Node first, even
150                 though they are top-level.  But if we go to their ``own''
151                 standard-entry code (which loads Node and then jumps to the
152                 constructor code) we don't need to load Node.
153         \end{itemize}
154 \end{itemize}
155
156
157 {\em Top level constructors (@mkStaticConEntryInfo@)}
158
159 \begin{verbatim}
160         x = {y,ys} \ {} Cons {y,ys}     -- Std form constructor
161 \end{verbatim}
162
163 x-closure: Cons-info-table, y-closure, ys-closure
164
165 x-entry: Node = x-closure; jump( Cons-entry )
166
167 x's EntryInfo in its own module:
168 \begin{verbatim}
169                 Base-label = Cons               -- Not x!!
170                 NodeMustPoint = True
171                 ClosureClass = Constructor
172 \end{verbatim}
173
174         So if x is entered, Node will be set up and
175         we'll jump direct to the Cons code.
176
177 x's EntryInfo in another module: (which may not know that x is a constructor)
178 \begin{verbatim}
179                 Base-label = x                  -- Is x!!
180                 NodeMustPoint = False           -- All imported things have False
181                 ClosureClass = non-committal
182 \end{verbatim}
183
184         If x is entered, we'll jump to x-entry, which will set up Node
185         before jumping to the standard Cons code
186
187 {\em Top level non-constructors (@mkStaticEntryInfo@)}
188 \begin{verbatim}
189         x = ...
190 \end{verbatim}
191
192 For updatable thunks, x-entry must push an allocated BH in update frame, not Node.
193
194 For non-zero arity, arg satis check must load Node before jumping to
195         UpdatePAP.
196
197 x's EntryInfo in its own module:
198 \begin{verbatim}
199                 Base-label = x
200                 NodeMustPoint = False
201                 ClosureClass = whatever
202 \end{verbatim}
203
204 {\em Inner constructors (@mkConEntryInfo@)}
205
206 \begin{verbatim}
207                 Base-label = Cons               -- Not x!!
208                 NodeMustPoint = True            -- If its arity were zero, it would
209                                                 -- have been lifted to top level
210                 ClosureClass = Constructor
211 \end{verbatim}
212
213 {\em Inner non-constructors (@mkEntryInfo@)}
214
215 \begin{verbatim}
216                 Base-label = x
217                 NodeMustPoint = True            -- If no free vars, would have been
218                                                 -- lifted to top level
219                 ClosureClass = whatever
220 \end{verbatim}
221
222 {\em Imported}
223
224 \begin{verbatim}
225                 Nothing,
226         or
227                 Base-label = x
228                 NodeMustPoint = False
229                 ClosureClass = whatever
230 \end{verbatim}
231
232 ==============
233 THINK: we could omit making Node point to top-level constructors
234 of arity zero; but that might interact nastily with updates.
235 ==============
236
237
238 ==========
239 The info we need to import for imported things is:
240
241 \begin{verbatim}
242         data ImportInfo = UnknownImportInfo
243                         | HnfImport Int         -- Not updatable, arity given
244                                                 -- Arity can be zero, for (eg) constrs
245                         | UpdatableImport       -- Must enter via the closure
246 \end{verbatim}
247
248 ToDo: move this stuff???
249
250 \begin{pseudocode}
251 mkStaticEntryInfo lbl cl_class
252   = MkEntryInfo lbl False cl_class
253
254 mkStaticConEntryInfo lbl
255   = MkEntryInfo lbl True ConstructorClosure
256
257 mkEntryInfo lbl cl_class
258   = MkEntryInfo lbl True cl_class
259
260 mkConEntryInfo lbl
261   = MkEntryInfo lbl True ConstructorClosure
262 \end{pseudocode}
263
264 %************************************************************************
265 %*                                                                      *
266 \subsection[ClosureInfo-datatypes]{Data types for closure information}
267 %*                                                                      *
268 %************************************************************************
269
270 %************************************************************************
271 %*                                                                      *
272 \subsubsection[LambdaFormInfo-datatype]{@LambdaFormInfo@: source-derivable info}
273 %*                                                                      *
274 %************************************************************************
275
276 \begin{code}
277 data LambdaFormInfo
278   = LFReEntrant         -- Reentrant closure; used for PAPs too
279         Bool            -- True if top level
280         Int             -- Arity
281         Bool            -- True <=> no fvs
282
283   | LFCon               -- Constructor
284         DataCon         -- The constructor (may be specialised)
285         Bool            -- True <=> zero arity
286
287   | LFTuple             -- Tuples
288         DataCon         -- The tuple constructor (may be specialised)
289         Bool            -- True <=> zero arity
290
291   | LFThunk             -- Thunk (zero arity)
292         Bool            -- True <=> top level
293         Bool            -- True <=> no free vars
294         Bool            -- True <=> updatable (i.e., *not* single-entry)
295         StandardFormInfo
296
297   | LFArgument          -- Used for function arguments.  We know nothing about
298                         -- this closure.  Treat like updatable "LFThunk"...
299
300   | LFImported          -- Used for imported things.  We know nothing about this
301                         -- closure.  Treat like updatable "LFThunk"...
302                         -- Imported things which we do know something about use
303                         -- one of the other LF constructors (eg LFReEntrant for
304                         -- known functions)
305
306   | LFLetNoEscape       -- See LetNoEscape module for precise description of
307                         -- these "lets".
308         Int             -- arity;
309         StgLiveVars-- list of variables live in the RHS of the let.
310                         -- (ToDo: maybe not used)
311
312   | LFBlackHole         -- Used for the closures allocated to hold the result
313                         -- of a CAF.  We want the target of the update frame to
314                         -- be in the heap, so we make a black hole to hold it.
315
316   -- This last one is really only for completeness;
317   -- it isn't actually used for anything interesting
318   {- | LFIndirection -}
319
320 data StandardFormInfo   -- Tells whether this thunk has one of a small number
321                         -- of standard forms
322
323   = NonStandardThunk    -- No, it isn't
324
325  | SelectorThunk
326        Id               -- Scrutinee
327        DataCon          -- Constructor
328        Int              -- 0-origin offset of ak within the "goods" of constructor
329                         -- (Recall that the a1,...,an may be laid out in the heap
330                         --  in a non-obvious order.)
331
332 {- A SelectorThunk is of form
333
334      case x of
335        con a1,..,an -> ak
336
337    and the constructor is from a single-constr type.
338    If we can't convert the heap-offset of the selectee into an Int, e.g.,
339    it's "GEN_VHS+i", we just give up.
340 -}
341
342   | VapThunk
343         Id                      -- Function
344         [StgArg]                -- Args
345         Bool                    -- True <=> the function is not top-level, so
346                                 -- must be stored in the thunk too
347
348 {- A VapThunk is of form
349
350         f a1 ... an
351
352    where f is a known function, with arity n
353    So for this thunk we can use the label for f's heap-entry
354    info table (generated when f's defn was dealt with),
355    rather than generating a one-off info table and entry code
356    for this one thunk.
357 -}
358
359
360 mkLFArgument    = LFArgument
361 mkLFBlackHole   = LFBlackHole
362 mkLFLetNoEscape = LFLetNoEscape
363
364 mkLFImported :: Id -> LambdaFormInfo
365 mkLFImported id
366   = case getIdArity id of
367       ArityExactly 0    -> LFThunk True{-top-lev-} True{-no fvs-}
368                                    True{-updatable-} NonStandardThunk
369       ArityExactly n    -> LFReEntrant True n True  -- n > 0
370       other             -> LFImported   -- Not sure of exact arity
371 \end{code}
372
373 %************************************************************************
374 %*                                                                      *
375 \subsection[ClosureInfo-construction]{Functions which build LFInfos}
376 %*                                                                      *
377 %************************************************************************
378
379 @mkClosureLFInfo@ figures out the appropriate LFInfo for the closure.
380
381 \begin{code}
382 mkClosureLFInfo :: Bool         -- True of top level
383                 -> [Id]         -- Free vars
384                 -> UpdateFlag   -- Update flag
385                 -> [Id]         -- Args
386                 -> LambdaFormInfo
387
388 mkClosureLFInfo top fvs upd_flag args@(_:_)  -- Non-empty args
389   = LFReEntrant top (length args) (null fvs)
390
391 mkClosureLFInfo top fvs ReEntrant []
392   = LFReEntrant top 0 (null fvs)
393
394 mkClosureLFInfo top fvs upd_flag []
395   = LFThunk top (null fvs) (isUpdatable upd_flag) NonStandardThunk
396
397 isUpdatable ReEntrant   = False
398 isUpdatable SingleEntry = False
399 isUpdatable Updatable   = True
400 \end{code}
401
402 @mkConLFInfo@ is similar, for constructors.
403
404 \begin{code}
405 mkConLFInfo :: DataCon -> LambdaFormInfo
406
407 mkConLFInfo con
408   = -- the isNullaryDataCon will do this: ASSERT(isDataCon con)
409     (if isTupleCon con then LFTuple else LFCon) con (isNullaryDataCon con)
410
411 mkSelectorLFInfo scrutinee con offset
412   = LFThunk False False True (SelectorThunk scrutinee con offset)
413
414 mkVapLFInfo fvs upd_flag fun_id args fun_in_vap
415   = LFThunk False (null fvs) (isUpdatable upd_flag) (VapThunk fun_id args fun_in_vap)
416 \end{code}
417
418
419 %************************************************************************
420 %*                                                                      *
421 \subsection[ClosureInfo-sizes]{Functions about closure {\em sizes}}
422 %*                                                                      *
423 %************************************************************************
424
425 \begin{code}
426 closureSize :: ClosureInfo -> HeapOffset
427 closureSize cl_info@(MkClosureInfo _ _ sm_rep)
428   = totHdrSize sm_rep `addOff` (intOff (closureNonHdrSize cl_info))
429
430 closureSizeWithoutFixedHdr :: ClosureInfo -> HeapOffset
431 closureSizeWithoutFixedHdr cl_info@(MkClosureInfo _ _ sm_rep)
432   = varHdrSize sm_rep `addOff` (intOff (closureNonHdrSize cl_info))
433
434 closureHdrSize :: ClosureInfo -> HeapOffset
435 closureHdrSize (MkClosureInfo _ _ sm_rep)
436   = totHdrSize sm_rep
437
438 closureNonHdrSize :: ClosureInfo -> Int
439 closureNonHdrSize cl_info@(MkClosureInfo _ lf_info sm_rep)
440   = tot_wds + computeSlopSize tot_wds sm_rep (closureUpdReqd cl_info) --ToDo: pass lf_info?
441   where
442     tot_wds = closureGoodStuffSize cl_info
443
444 closureGoodStuffSize :: ClosureInfo -> Int
445 closureGoodStuffSize (MkClosureInfo _ _ sm_rep)
446   = let (ptrs, nonptrs) = sizes_from_SMRep sm_rep
447     in  ptrs + nonptrs
448
449 closurePtrsSize :: ClosureInfo -> Int
450 closurePtrsSize (MkClosureInfo _ _ sm_rep)
451   = let (ptrs, _) = sizes_from_SMRep sm_rep
452     in  ptrs
453
454 -- not exported:
455 sizes_from_SMRep (SpecialisedRep k ptrs nonptrs _)   = (ptrs, nonptrs)
456 sizes_from_SMRep (GenericRep       ptrs nonptrs _)   = (ptrs, nonptrs)
457 sizes_from_SMRep (BigTupleRep      ptrs)             = (ptrs, 0)
458 sizes_from_SMRep (MuTupleRep       ptrs)             = (ptrs, 0)
459 sizes_from_SMRep (DataRep               nonptrs)     = (0, nonptrs)
460 sizes_from_SMRep BlackHoleRep                        = (0, 0)
461 sizes_from_SMRep (StaticRep        ptrs nonptrs)     = (ptrs, nonptrs)
462 #ifdef DEBUG
463 sizes_from_SMRep PhantomRep       = panic "sizes_from_SMRep: PhantomRep"
464 sizes_from_SMRep DynamicRep       = panic "sizes_from_SMRep: DynamicRep"
465 #endif
466 \end{code}
467
468 \begin{code}
469 fitsMinUpdSize :: ClosureInfo -> Bool
470 fitsMinUpdSize (MkClosureInfo _ _ BlackHoleRep) = True
471 fitsMinUpdSize cl_info = isSpecRep (closureSMRep cl_info) && closureNonHdrSize cl_info <= mIN_UPD_SIZE
472 \end{code}
473
474 Computing slop size.  WARNING: this looks dodgy --- it has deep
475 knowledge of what the storage manager does with the various
476 representations...
477
478 Slop Requirements:
479 \begin{itemize}
480 \item
481 Updateable closures must be @mIN_UPD_SIZE@.
482         \begin{itemize}
483         \item
484         Cons cell requires 2 words
485         \item
486         Indirections require 1 word
487         \item
488         Appels collector indirections 2 words
489         \end{itemize}
490 THEREFORE: @mIN_UPD_SIZE = 2@.
491
492 \item
493 Collectable closures which are allocated in the heap
494 must be @mIN_SIZE_NonUpdHeapObject@.
495
496 Copying collector forward pointer requires 1 word
497
498 THEREFORE: @mIN_SIZE_NonUpdHeapObject = 1@
499
500 \item
501 @SpecialisedRep@ closures closures may require slop:
502         \begin{itemize}
503         \item
504         @ConstantRep@ and @CharLikeRep@ closures always use the address of
505         a static closure. They are never allocated or
506         collected (eg hold forwarding pointer) hence never any slop.
507
508         \item
509         @IntLikeRep@ are never updatable.
510         May need slop to be collected (as they will be size 1 or more
511         this probably has no affect)
512
513         \item
514         @SpecRep@ may be updateable and will be collectable
515
516         \item
517         @StaticRep@ may require slop if updatable. Non-updatable ones are OK.
518
519         \item
520         @GenericRep@ closures will always be larger so never require slop.
521         \end{itemize}
522
523         ***** ToDo: keep an eye on this!
524 \end{itemize}
525
526 \begin{code}
527 slopSize cl_info@(MkClosureInfo _ lf_info sm_rep)
528   = computeSlopSize (closureGoodStuffSize cl_info) sm_rep (closureUpdReqd cl_info)
529
530 computeSlopSize :: Int -> SMRep -> Bool -> Int
531
532 computeSlopSize tot_wds (SpecialisedRep ConstantRep _ _ _) _
533   = 0
534 computeSlopSize tot_wds (SpecialisedRep CharLikeRep _ _ _) _
535   = 0
536
537 computeSlopSize tot_wds (SpecialisedRep _ _ _ _) True   -- Updatable
538   = max 0 (mIN_UPD_SIZE - tot_wds)
539 computeSlopSize tot_wds (StaticRep _ _) True            -- Updatable
540   = max 0 (mIN_UPD_SIZE - tot_wds)
541 computeSlopSize tot_wds BlackHoleRep _                  -- Updatable
542   = max 0 (mIN_UPD_SIZE - tot_wds)
543
544 computeSlopSize tot_wds (SpecialisedRep _ _ _ _) False  -- Not updatable
545   = max 0 (mIN_SIZE_NonUpdHeapObject - tot_wds)
546
547 computeSlopSize tot_wds other_rep _                     -- Any other rep
548   = 0
549 \end{code}
550
551 %************************************************************************
552 %*                                                                      *
553 \subsection[layOutDynClosure]{Lay out a dynamic closure}
554 %*                                                                      *
555 %************************************************************************
556
557 \begin{code}
558 layOutDynClosure, layOutStaticClosure
559         :: Id                       -- STG identifier w/ which this closure assoc'd
560         -> (a -> PrimRep)           -- function w/ which to be able to get a PrimRep
561         -> [a]                      -- the "things" being layed out
562         -> LambdaFormInfo           -- what sort of closure it is
563         -> (ClosureInfo,            -- info about the closure
564             [(a, VirtualHeapOffset)])   -- things w/ offsets pinned on them
565
566 layOutDynClosure name kind_fn things lf_info
567   = (MkClosureInfo name lf_info sm_rep,
568      things_w_offsets)
569   where
570     (tot_wds,            -- #ptr_wds + #nonptr_wds
571      ptr_wds,            -- #ptr_wds
572      things_w_offsets) = mkVirtHeapOffsets sm_rep kind_fn things
573     sm_rep = chooseDynSMRep lf_info tot_wds ptr_wds
574
575 layOutStaticClosure name kind_fn things lf_info
576   = (MkClosureInfo name lf_info (StaticRep ptr_wds (tot_wds - ptr_wds)),
577      things_w_offsets)
578   where
579     (tot_wds,            -- #ptr_wds + #nonptr_wds
580      ptr_wds,            -- #ptr_wds
581      things_w_offsets) = mkVirtHeapOffsets (StaticRep bot bot) kind_fn things
582     bot = panic "layoutStaticClosure"
583
584 layOutStaticNoFVClosure :: Id -> LambdaFormInfo -> ClosureInfo
585 layOutStaticNoFVClosure name lf_info
586   = MkClosureInfo name lf_info (StaticRep ptr_wds nonptr_wds)
587  where
588   -- I am very uncertain that this is right - it will show up when testing
589   -- my dynamic loading code.  ADR
590   -- (If it's not right, we'll have to grab the kinds of the arguments from
591   --  somewhere.)
592   ptr_wds = 0
593   nonptr_wds = 0
594
595 layOutPhantomClosure :: Id -> LambdaFormInfo -> ClosureInfo
596 layOutPhantomClosure name lf_info = MkClosureInfo name lf_info PhantomRep
597 \end{code}
598
599 A wrapper for when used with data constructors:
600 \begin{code}
601 layOutDynCon :: DataCon
602              -> (a -> PrimRep)
603              -> [a]
604              -> (ClosureInfo, [(a,VirtualHeapOffset)])
605
606 layOutDynCon con kind_fn args
607   = ASSERT(isDataCon con)
608     layOutDynClosure con kind_fn args (mkConLFInfo con)
609 \end{code}
610
611
612 %************************************************************************
613 %*                                                                      *
614 \subsection[SMreps]{Choosing SM reps}
615 %*                                                                      *
616 %************************************************************************
617
618 \begin{code}
619 chooseDynSMRep
620         :: LambdaFormInfo
621         -> Int -> Int           -- Tot wds, ptr wds
622         -> SMRep
623
624 chooseDynSMRep lf_info tot_wds ptr_wds
625   = let
626          nonptr_wds = tot_wds - ptr_wds
627
628          updatekind = case lf_info of
629              LFThunk _ _ upd _  -> if upd then SMUpdatable else SMSingleEntry
630              LFBlackHole        -> SMUpdatable
631              _                  -> SMNormalForm
632     in
633     if (nonptr_wds == 0 && ptr_wds <= mAX_SPEC_ALL_PTRS)
634             || (tot_wds <= mAX_SPEC_MIXED_FIELDS)
635             || (ptr_wds == 0 && nonptr_wds <= mAX_SPEC_ALL_NONPTRS) then
636         let
637           spec_kind  = case lf_info of
638
639            (LFTuple _ True) -> ConstantRep
640
641            (LFTuple _ _)  -> SpecRep
642
643            (LFCon _ True) -> ConstantRep
644
645            (LFCon con _ ) -> if maybeToBool (maybeCharLikeTyCon tycon) then CharLikeRep
646                              else if maybeToBool (maybeIntLikeTyCon tycon) then IntLikeRep
647                              else SpecRep
648                              where
649                              tycon = dataConTyCon con
650
651            _              -> SpecRep
652         in
653         SpecialisedRep spec_kind ptr_wds nonptr_wds updatekind
654     else
655         GenericRep ptr_wds nonptr_wds updatekind
656 \end{code}
657
658
659 %************************************************************************
660 %*                                                                      *
661 \subsection[mkVirtHeapOffsets]{Assigning heap offsets in a closure}
662 %*                                                                      *
663 %************************************************************************
664
665 @mkVirtHeapOffsets@ (the heap version) always returns boxed things with
666 smaller offsets than the unboxed things, and furthermore, the offsets in
667 the result list
668
669 \begin{code}
670 mkVirtHeapOffsets :: SMRep      -- Representation to be used by storage manager
671           -> (a -> PrimRep)     -- To be able to grab kinds;
672                                 --      w/ a kind, we can find boxedness
673           -> [a]                -- Things to make offsets for
674           -> (Int,              -- *Total* number of words allocated
675               Int,              -- Number of words allocated for *pointers*
676               [(a, VirtualHeapOffset)])
677                                 -- Things with their offsets from start of object
678                                 --      in order of increasing offset
679
680 -- First in list gets lowest offset, which is initial offset + 1.
681
682 mkVirtHeapOffsets sm_rep kind_fun things
683   = let (ptrs, non_ptrs)              = separateByPtrFollowness kind_fun things
684         (wds_of_ptrs, ptrs_w_offsets) = mapAccumL computeOffset 0 ptrs
685         (tot_wds, non_ptrs_w_offsets) = mapAccumL computeOffset wds_of_ptrs non_ptrs
686     in
687         (tot_wds, wds_of_ptrs, ptrs_w_offsets ++ non_ptrs_w_offsets)
688   where
689     offset_of_first_word = totHdrSize sm_rep
690     computeOffset wds_so_far thing
691       = (wds_so_far + (getPrimRepSize . kind_fun) thing,
692          (thing, (offset_of_first_word `addOff` (intOff wds_so_far)))
693         )
694 \end{code}
695
696 %************************************************************************
697 %*                                                                      *
698 \subsection[ClosureInfo-4-questions]{Four major questions about @ClosureInfo@}
699 %*                                                                      *
700 %************************************************************************
701
702 Be sure to see the stg-details notes about these...
703
704 \begin{code}
705 nodeMustPointToIt :: LambdaFormInfo -> FCode Bool
706 nodeMustPointToIt lf_info
707   = let
708         do_profiling = opt_SccProfilingOn
709     in
710     case lf_info of
711         LFReEntrant top arity no_fvs -> returnFC (
712             not no_fvs ||   -- Certainly if it has fvs we need to point to it
713
714             not top -- If it is not top level we will point to it
715                     --   We can have a \r closure with no_fvs which
716                     --   is not top level as special case cgRhsClosure
717                     --   has been dissabled in favour of let floating
718
719                 -- For lex_profiling we also access the cost centre for a
720                 -- non-inherited function i.e. not top level
721                 -- the  not top  case above ensures this is ok.
722             )
723
724         LFCon   _ zero_arity -> returnFC True
725         LFTuple _ zero_arity -> returnFC True
726
727         -- Strictly speaking, the above two don't need Node to point
728         -- to it if the arity = 0.  But this is a *really* unlikely
729         -- situation.  If we know it's nil (say) and we are entering
730         -- it. Eg: let x = [] in x then we will certainly have inlined
731         -- x, since nil is a simple atom.  So we gain little by not
732         -- having Node point to known zero-arity things.  On the other
733         -- hand, we do lose something; Patrick's code for figuring out
734         -- when something has been updated but not entered relies on
735         -- having Node point to the result of an update.  SLPJ
736         -- 27/11/92.
737
738         LFThunk _ no_fvs updatable _
739           -> returnFC (updatable || not no_fvs || do_profiling)
740
741           -- For the non-updatable (single-entry case):
742           --
743           -- True if has fvs (in which case we need access to them, and we
744           --                should black-hole it)
745           -- or profiling (in which case we need to recover the cost centre
746           --             from inside it)
747
748         LFArgument  -> returnFC True
749         LFImported  -> returnFC True
750         LFBlackHole -> returnFC True
751                     -- BH entry may require Node to point
752
753         LFLetNoEscape _ _ -> returnFC False
754 \end{code}
755
756 The entry conventions depend on the type of closure being entered,
757 whether or not it has free variables, and whether we're running
758 sequentially or in parallel.
759
760 \begin{tabular}{lllll}
761 Closure Characteristics & Parallel & Node Req'd & Argument Passing & Enter Via \\
762 Unknown                         & no & yes & stack      & node \\
763 Known fun ($\ge$ 1 arg), no fvs         & no & no  & registers  & fast entry (enough args) \\
764 \ & \ & \ & \                                           & slow entry (otherwise) \\
765 Known fun ($\ge$ 1 arg), fvs    & no & yes & registers  & fast entry (enough args) \\
766 0 arg, no fvs @\r,\s@           & no & no  & n/a        & direct entry \\
767 0 arg, no fvs @\u@              & no & yes & n/a        & node \\
768 0 arg, fvs @\r,\s@              & no & yes & n/a        & direct entry \\
769 0 arg, fvs @\u@                 & no & yes & n/a        & node \\
770
771 Unknown                         & yes & yes & stack     & node \\
772 Known fun ($\ge$ 1 arg), no fvs         & yes & no  & registers & fast entry (enough args) \\
773 \ & \ & \ & \                                           & slow entry (otherwise) \\
774 Known fun ($\ge$ 1 arg), fvs    & yes & yes & registers & node \\
775 0 arg, no fvs @\r,\s@           & yes & no  & n/a       & direct entry \\
776 0 arg, no fvs @\u@              & yes & yes & n/a       & node \\
777 0 arg, fvs @\r,\s@              & yes & yes & n/a       & node \\
778 0 arg, fvs @\u@                 & yes & yes & n/a       & node\\
779 \end{tabular}
780
781 When black-holing, single-entry closures could also be entered via node
782 (rather than directly) to catch double-entry.
783
784 \begin{code}
785 data EntryConvention
786   = ViaNode                             -- The "normal" convention
787
788   | StdEntry CLabel                     -- Jump to this code, with args on stack
789              (Maybe CLabel)             -- possibly setting infoptr to this
790
791   | DirectEntry                         -- Jump directly to code, with args in regs
792         CLabel                          --   The code label
793         Int                             --   Its arity
794         [MagicId]                       --   Its register assignments (possibly empty)
795
796 getEntryConvention :: Id                -- Function being applied
797                    -> LambdaFormInfo    -- Its info
798                    -> [PrimRep]         -- Available arguments
799                    -> FCode EntryConvention
800
801 getEntryConvention id lf_info arg_kinds
802  =  nodeMustPointToIt lf_info   `thenFC` \ node_points ->
803     let
804         is_concurrent = opt_ForConcurrent
805     in
806     returnFC (
807
808     if (node_points && is_concurrent) then ViaNode else
809
810     case lf_info of
811
812         LFReEntrant _ arity _ ->
813             if arity == 0 || (length arg_kinds) < arity then
814                 StdEntry (mkStdEntryLabel id) Nothing
815             else
816                 DirectEntry (mkFastEntryLabel id arity) arity arg_regs
817           where
818             (arg_regs, _) = assignRegs live_regs (take arity arg_kinds)
819             live_regs = if node_points then [node] else []
820
821         LFCon con zero_arity
822                           -> let itbl = if zero_arity then
823                                         mkPhantomInfoTableLabel con
824                                         else
825                                         mkConInfoTableLabel con
826                              in
827                              --false:ASSERT (null arg_kinds)    -- Should have no args (meaning what?)
828                              StdEntry (mkConEntryLabel con) (Just itbl)
829
830         LFTuple tup zero_arity
831                           -> --false:ASSERT (null arg_kinds)    -- Should have no args (meaning what?)
832                              StdEntry (mkConEntryLabel tup) (Just (mkConInfoTableLabel tup))
833
834         LFThunk _ _ updatable std_form_info
835           -> if updatable
836              then ViaNode
837              else StdEntry (thunkEntryLabel id std_form_info updatable) Nothing
838
839         LFArgument  -> ViaNode
840         LFImported  -> ViaNode
841         LFBlackHole -> ViaNode  -- Presumably the black hole has by now
842                                 -- been updated, but we don't know with
843                                 -- what, so we enter via Node
844
845         LFLetNoEscape arity _
846           -> ASSERT(arity == length arg_kinds)
847              DirectEntry (mkStdEntryLabel id) arity arg_regs
848          where
849             (arg_regs, _) = assignRegs live_regs arg_kinds
850             live_regs     = if node_points then [node] else []
851     )
852
853 blackHoleOnEntry :: Bool        -- No-black-holing flag
854                  -> ClosureInfo
855                  -> Bool
856
857 -- Static closures are never themselves black-holed.
858 -- Updatable ones will be overwritten with a CAFList cell, which points to a black hole;
859 -- Single-entry ones have no fvs to plug, and we trust they don't form part of a loop.
860
861 blackHoleOnEntry no_black_holing (MkClosureInfo _ _ (StaticRep _ _)) = False
862
863 blackHoleOnEntry no_black_holing (MkClosureInfo _ lf_info _)
864   = case lf_info of
865         LFReEntrant _ _ _         -> False
866         LFThunk _ no_fvs updatable _
867           -> if updatable
868              then not no_black_holing
869              else not no_fvs
870         other -> panic "blackHoleOnEntry"       -- Should never happen
871
872 getStandardFormThunkInfo
873         :: LambdaFormInfo
874         -> Maybe [StgArg]               -- Nothing    => not a standard-form thunk
875                                         -- Just atoms => a standard-form thunk with payload atoms
876
877 getStandardFormThunkInfo (LFThunk _ _ _ (SelectorThunk scrutinee _ _))
878   = --trace "Selector thunk: missed opportunity to save info table + code"
879     Nothing
880         -- Just [StgVarArg scrutinee]
881         -- We can't save the info tbl + code until we have a way to generate
882         -- a fixed family thereof.
883
884 getStandardFormThunkInfo (LFThunk _ _ _ (VapThunk fun_id args fun_in_payload))
885   | fun_in_payload = Just (StgVarArg fun_id : args)
886   | otherwise      = Just args
887
888 getStandardFormThunkInfo other_lf_info = Nothing
889
890 maybeSelectorInfo (MkClosureInfo _ (LFThunk _ _ _ (SelectorThunk _ con offset)) _) = Just (con,offset)
891 maybeSelectorInfo _ = Nothing
892 \end{code}
893
894 Avoiding generating entries and info tables
895 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
896 At present, for every function we generate all of the following,
897 just in case.  But they aren't always all needed, as noted below:
898
899 [NB1: all of this applies only to *functions*.  Thunks always
900 have closure, info table, and entry code.]
901
902 [NB2: All are needed if the function is *exported*, just to play safe.]
903
904
905 * Fast-entry code  ALWAYS NEEDED
906
907 * Slow-entry code
908         Needed iff (a) we have any un-saturated calls to the function
909         OR         (b) the function is passed as an arg
910         OR         (c) we're in the parallel world and the function has free vars
911                         [Reason: in parallel world, we always enter functions
912                         with free vars via the closure.]
913
914 * The function closure
915         Needed iff (a) we have any un-saturated calls to the function
916         OR         (b) the function is passed as an arg
917         OR         (c) if the function has free vars (ie not top level)
918
919   Why case (a) here?  Because if the arg-satis check fails,
920   UpdatePAP stuffs a pointer to the function closure in the PAP.
921   [Could be changed; UpdatePAP could stuff in a code ptr instead,
922    but doesn't seem worth it.]
923
924   [NB: these conditions imply that we might need the closure
925   without the slow-entry code.  Here's how.
926
927         f x y = let g w = ...x..y..w...
928                 in
929                 ...(g t)...
930
931   Here we need a closure for g which contains x and y,
932   but since the calls are all saturated we just jump to the
933   fast entry point for g, with R1 pointing to the closure for g.]
934
935
936 * Standard info table
937         Needed iff (a) we have any un-saturated calls to the function
938         OR         (b) the function is passed as an arg
939         OR         (c) the function has free vars (ie not top level)
940
941         NB.  In the sequential world, (c) is only required so that the function closure has
942         an info table to point to, to keep the storage manager happy.
943         If (c) alone is true we could fake up an info table by choosing
944         one of a standard family of info tables, whose entry code just
945         bombs out.
946
947         [NB In the parallel world (c) is needed regardless because
948         we enter functions with free vars via the closure.]
949
950         If (c) is retained, then we'll sometimes generate an info table
951         (for storage mgr purposes) without slow-entry code.  Then we need
952         to use an error label in the info table to substitute for the absent
953         slow entry code.
954
955 * Standard vap-entry code
956   Standard vap-entry info table
957         Needed iff we have any updatable thunks of the standard vap-entry shape.
958
959 * Single-update vap-entry code
960   Single-update vap-entry info table
961         Needed iff we have any non-updatable thunks of the
962         standard vap-entry shape.
963
964
965 \begin{code}
966 staticClosureRequired
967         :: Id
968         -> StgBinderInfo
969         -> LambdaFormInfo
970         -> Bool
971 staticClosureRequired binder (StgBinderInfo arg_occ unsat_occ _ _ _)
972                       (LFReEntrant top_level _ _)       -- It's a function
973   = ASSERT( top_level )                 -- Assumption: it's a top-level, no-free-var binding
974     arg_occ             -- There's an argument occurrence
975     || unsat_occ        -- There's an unsaturated call
976     || externallyVisibleId binder
977
978 staticClosureRequired binder other_binder_info other_lf_info = True
979
980 slowFunEntryCodeRequired        -- Assumption: it's a function, not a thunk.
981         :: Id
982         -> StgBinderInfo
983         -> Bool
984 slowFunEntryCodeRequired binder (StgBinderInfo arg_occ unsat_occ _ _ _)
985   = arg_occ             -- There's an argument occurrence
986     || unsat_occ        -- There's an unsaturated call
987     || externallyVisibleId binder
988     {- HAS FREE VARS AND IS PARALLEL WORLD -}
989
990 slowFunEntryCodeRequired binder NoStgBinderInfo = True
991
992 funInfoTableRequired
993         :: Id
994         -> StgBinderInfo
995         -> LambdaFormInfo
996         -> Bool
997 funInfoTableRequired  binder (StgBinderInfo arg_occ unsat_occ _ _ _)
998                      (LFReEntrant top_level _ _)
999   = not top_level
1000     || arg_occ          -- There's an argument occurrence
1001     || unsat_occ        -- There's an unsaturated call
1002     || externallyVisibleId binder
1003
1004 funInfoTableRequired other_binder_info binder other_lf_info = True
1005
1006 -- We need the vector-apply entry points for a function if
1007 -- there's a vector-apply occurrence in this module
1008
1009 stdVapRequired, noUpdVapRequired :: StgBinderInfo -> Bool
1010
1011 stdVapRequired binder_info
1012   = case binder_info of
1013       StgBinderInfo _ _ std_vap_occ _ _ -> std_vap_occ
1014       _                                 -> False
1015
1016 noUpdVapRequired binder_info
1017   = case binder_info of
1018       StgBinderInfo _ _ _ no_upd_vap_occ _ -> no_upd_vap_occ
1019       _                                    -> False
1020 \end{code}
1021
1022 @lfArity@ extracts the arity of a function from its LFInfo
1023
1024 \begin{code}
1025 {- Not needed any more
1026
1027 lfArity_maybe (LFReEntrant _ arity _) = Just arity
1028
1029 -- Removed SLPJ March 97. I don't believe these two; 
1030 -- LFCon is used for construcor *applications*, not constructors!
1031 --
1032 -- lfArity_maybe (LFCon con _)        = Just (dataConArity con)
1033 -- lfArity_maybe (LFTuple con _)              = Just (dataConArity con)
1034
1035 lfArity_maybe other                   = Nothing
1036 -}
1037 \end{code}
1038
1039 %************************************************************************
1040 %*                                                                      *
1041 \subsection[ClosureInfo-misc-funs]{Misc functions about @ClosureInfo@, etc.}
1042 %*                                                                      *
1043 %************************************************************************
1044
1045 \begin{code}
1046
1047 isStaticClosure :: ClosureInfo -> Bool
1048 isStaticClosure  (MkClosureInfo _ _ rep) = isStaticRep  rep
1049
1050 closureId :: ClosureInfo -> Id
1051 closureId (MkClosureInfo id _ _) = id
1052
1053 closureSMRep :: ClosureInfo -> SMRep
1054 closureSMRep (MkClosureInfo _ _ sm_rep) = sm_rep
1055
1056 closureLFInfo :: ClosureInfo -> LambdaFormInfo
1057 closureLFInfo (MkClosureInfo _ lf_info _) = lf_info
1058
1059 closureUpdReqd :: ClosureInfo -> Bool
1060
1061 closureUpdReqd (MkClosureInfo _ (LFThunk _ _ upd _) _) = upd
1062 closureUpdReqd (MkClosureInfo _ LFBlackHole _)         = True
1063         -- Black-hole closures are allocated to receive the results of an
1064         -- alg case with a named default... so they need to be updated.
1065 closureUpdReqd other_closure                           = False
1066
1067 closureSingleEntry :: ClosureInfo -> Bool
1068
1069 closureSingleEntry (MkClosureInfo _ (LFThunk _ _ upd _) _) = not upd
1070 closureSingleEntry other_closure                           = False
1071 \end{code}
1072
1073 Note: @closureType@ returns appropriately specialised tycon and
1074 datacons.
1075 \begin{code}
1076 closureType :: ClosureInfo -> Maybe (TyCon, [Type], [Id])
1077
1078 -- First, a turgid special case.  When we are generating the
1079 -- standard code and info-table for Vaps (which is done when the function
1080 -- defn is encountered), we don't have a convenient Id to hand whose
1081 -- type is that of (f x y z).  So we need to figure out the type
1082 -- rather than take it from the Id. The Id is probably just "f"!
1083
1084 closureType (MkClosureInfo id (LFThunk _ _ _ (VapThunk fun_id args _)) _)
1085   = maybeAppSpecDataTyConExpandingDicts (fun_result_ty (length args) fun_id)
1086
1087 closureType (MkClosureInfo id lf _) = maybeAppSpecDataTyConExpandingDicts (idType id)
1088 \end{code}
1089
1090 @closureReturnsUnboxedType@ is used to check whether a closure, {\em
1091 once it has eaten its arguments}, returns an unboxed type.  For
1092 example, the closure for a function:
1093 \begin{verbatim}
1094         f :: Int -> Int#
1095 \end{verbatim}
1096 returns an unboxed type.  This is important when dealing with stack
1097 overflow checks.
1098 \begin{code}
1099 closureReturnsUnboxedType :: ClosureInfo -> Bool
1100
1101 closureReturnsUnboxedType (MkClosureInfo fun_id (LFReEntrant _ arity _) _)
1102   = isPrimType (fun_result_ty arity fun_id)
1103
1104 closureReturnsUnboxedType other_closure = False
1105         -- All non-function closures aren't functions,
1106         -- and hence are boxed, since they are heap alloc'd
1107
1108 -- ToDo: need anything like this in Type.lhs?
1109 fun_result_ty arity id
1110   = let
1111         (arg_tys, res_ty)  = splitFunTyExpandingDictsAndPeeking (idType id)
1112     in
1113 --    ASSERT(arity >= 0 && length arg_tys >= arity)
1114     (if (arity >= 0 && length arg_tys >= arity) then (\x->x) else pprPanic "fun_result_ty:" (hsep [int arity, ppr PprShowAll id, ppr PprDebug (idType id)])) $
1115     mkFunTys (drop arity arg_tys) res_ty
1116 \end{code}
1117
1118 \begin{code}
1119 closureSemiTag :: ClosureInfo -> Int
1120
1121 closureSemiTag (MkClosureInfo _ lf_info _)
1122   = case lf_info of
1123       LFCon data_con _ -> dataConTag data_con - fIRST_TAG
1124       LFTuple _ _      -> 0
1125       _                -> fromInteger oTHER_TAG
1126 \end{code}
1127
1128 \begin{code}
1129 isToplevClosure :: ClosureInfo -> Bool
1130
1131 isToplevClosure (MkClosureInfo _ lf_info _)
1132   = case lf_info of
1133       LFReEntrant top _ _ -> top
1134       LFThunk top _ _ _   -> top
1135       _ -> panic "ClosureInfo:isToplevClosure"
1136 \end{code}
1137
1138 Label generation.
1139
1140 \begin{code}
1141 fastLabelFromCI :: ClosureInfo -> CLabel
1142 fastLabelFromCI (MkClosureInfo id lf_info _)
1143 {-      [SLPJ Changed March 97]
1144          (was ok, but is the only call to lfArity, 
1145           and the id should guarantee to have the correct arity in it.
1146
1147   = case lfArity_maybe lf_info of
1148         Just arity -> 
1149 -}
1150   = case getIdArity id of
1151         ArityExactly arity -> mkFastEntryLabel id arity
1152         other              -> pprPanic "fastLabelFromCI" (ppr PprDebug id)
1153
1154 infoTableLabelFromCI :: ClosureInfo -> CLabel
1155 infoTableLabelFromCI (MkClosureInfo id lf_info rep)
1156   = case lf_info of
1157         LFCon con _     -> mkConInfoPtr con rep
1158         LFTuple tup _   -> mkConInfoPtr tup rep
1159
1160         LFBlackHole     -> mkBlackHoleInfoTableLabel
1161
1162         LFThunk _ _ upd_flag (VapThunk fun_id args _) -> mkVapInfoTableLabel fun_id upd_flag
1163                                         -- Use the standard vap info table
1164                                         -- for the function, rather than a one-off one
1165                                         -- for this particular closure
1166
1167 {-      For now, we generate individual info table and entry code for selector thunks,
1168         so their info table should be labelled in the standard way.
1169         The only special thing about them is that the info table has a field which
1170         tells the GC that it really is a selector.
1171
1172         Later, perhaps, we'll have some standard RTS code for selector-thunk info tables,
1173         in which case this line will spring back to life.
1174
1175         LFThunk _ _ upd_flag (SelectorThunk _ _ offset) -> mkSelectorInfoTableLabel upd_flag offset
1176                                         -- Ditto for selectors
1177 -}
1178
1179         other -> {-NO: if isStaticRep rep
1180                  then mkStaticInfoTableLabel id
1181                  else -} mkInfoTableLabel id
1182
1183 mkConInfoPtr :: Id -> SMRep -> CLabel
1184 mkConInfoPtr con rep
1185   = ASSERT(isDataCon con)
1186     case rep of
1187       PhantomRep    -> mkPhantomInfoTableLabel con
1188       StaticRep _ _ -> mkStaticInfoTableLabel  con
1189       _             -> mkConInfoTableLabel     con
1190
1191 mkConEntryPtr :: Id -> SMRep -> CLabel
1192 mkConEntryPtr con rep
1193   = ASSERT(isDataCon con)
1194     case rep of
1195       StaticRep _ _ -> mkStaticConEntryLabel con
1196       _             -> mkConEntryLabel con
1197
1198
1199 closureLabelFromCI (MkClosureInfo id _ rep) 
1200         | isConstantRep rep
1201         = mkStaticClosureLabel id
1202         -- This case catches those pesky static closures for nullary constructors
1203
1204 closureLabelFromCI (MkClosureInfo id _ other_rep)   = mkClosureLabel id
1205
1206 entryLabelFromCI :: ClosureInfo -> CLabel
1207 entryLabelFromCI (MkClosureInfo id lf_info rep)
1208   = case lf_info of
1209         LFThunk _ _ upd_flag std_form_info -> thunkEntryLabel id std_form_info upd_flag
1210         LFCon con _                        -> mkConEntryPtr con rep
1211         LFTuple tup _                      -> mkConEntryPtr tup rep
1212         other                              -> mkStdEntryLabel id
1213
1214 -- thunkEntryLabel is a local help function, not exported.  It's used from both
1215 -- entryLabelFromCI and getEntryConvention.
1216 -- I don't think it needs to deal with the SelectorThunk case
1217 -- Well, it's falling over now, so I've made it deal with it.  (JSM)
1218
1219 thunkEntryLabel thunk_id (VapThunk fun_id args _) is_updatable
1220   = mkVapEntryLabel fun_id is_updatable
1221 thunkEntryLabel thunk_id _ is_updatable
1222   = mkStdEntryLabel thunk_id
1223 \end{code}
1224
1225 \begin{code}
1226 allocProfilingMsg :: ClosureInfo -> FAST_STRING
1227
1228 allocProfilingMsg (MkClosureInfo _ lf_info _)
1229   = case lf_info of
1230       LFReEntrant _ _ _         -> SLIT("ALLOC_FUN")
1231       LFCon _ _                 -> SLIT("ALLOC_CON")
1232       LFTuple _ _               -> SLIT("ALLOC_CON")
1233       LFThunk _ _ _ _           -> SLIT("ALLOC_THK")
1234       LFBlackHole               -> SLIT("ALLOC_BH")
1235       LFImported                -> panic "ALLOC_IMP"
1236 \end{code}
1237
1238 We need a black-hole closure info to pass to @allocDynClosure@ when we
1239 want to allocate the black hole on entry to a CAF.
1240
1241 \begin{code}
1242 blackHoleClosureInfo (MkClosureInfo id _ _)
1243   = MkClosureInfo id LFBlackHole BlackHoleRep
1244 \end{code}
1245
1246 The register liveness when returning from a constructor.  For
1247 simplicity, we claim just [node] is live for all but PhantomRep's.  In
1248 truth, this means that non-constructor info tables also claim node,
1249 but since their liveness information is never used, we don't care.
1250
1251 \begin{code}
1252 dataConLiveness (MkClosureInfo con _ PhantomRep)
1253   = case (dataReturnConvAlg con) of
1254       ReturnInRegs regs -> mkLiveRegsMask regs
1255       ReturnInHeap -> panic "dataConLiveness:PhantomRep in heap???"
1256
1257 dataConLiveness _ = mkLiveRegsMask [node]
1258 \end{code}
1259
1260 %************************************************************************
1261 %*                                                                      *
1262 \subsection[ClosureInfo-Profiling-funs]{Misc functions about for profiling info.}
1263 %*                                                                      *
1264 %************************************************************************
1265
1266 Profiling requires three pices of information to be determined for
1267 each closure's info table --- kind, description and type.
1268
1269 The description is stored directly in the @CClosureInfoTable@ when the
1270 info table is built.
1271
1272 The kind is determined from the @LambdaForm@ stored in the closure
1273 info using @closureKind@.
1274
1275 The type is determined from the type information stored with the @Id@
1276 in the closure info using @closureTypeDescr@.
1277
1278 \begin{code}
1279 closureKind :: ClosureInfo -> String
1280
1281 closureKind (MkClosureInfo _ lf _)
1282   = case lf of
1283       LFReEntrant _ n _         -> if n > 0 then "FN_K" else "THK_K"
1284       LFCon _ _                 -> "CON_K"
1285       LFTuple _ _               -> "CON_K"
1286       LFThunk _ _ _ _           -> "THK_K"
1287       LFBlackHole               -> "THK_K" -- consider BHs as thunks for the moment... (ToDo?)
1288       LFImported                -> panic "IMP_KIND"
1289
1290 closureTypeDescr :: ClosureInfo -> String
1291 closureTypeDescr (MkClosureInfo id lf _)
1292   = if (isDataCon id) then                       -- DataCon has function types
1293         getOccString (dataConTyCon id)           -- We want the TyCon not the ->
1294     else
1295         getTyDescription (idType id)
1296 \end{code}