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