[project @ 1998-02-10 14:15:51 by simonpj]
[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         ( maybeCharLikeTyCon, maybeIntLikeTyCon )
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 \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 NonStandardThunk
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         LFThunk _ no_fvs updatable some_standard_form_thunk
749           -> returnFC True
750           -- Node must point to any standard-form thunk.
751           -- For example,
752           --            x = f y
753           -- generates a Vap thunk for (f y), and even if y is a global
754           -- variable we must still make Node point to the thunk before entering it
755           -- because that's what the standard-form code expects.
756
757         LFArgument  -> returnFC True
758         LFImported  -> returnFC True
759         LFBlackHole -> returnFC True
760                     -- BH entry may require Node to point
761
762         LFLetNoEscape _ _ -> returnFC False
763 \end{code}
764
765 The entry conventions depend on the type of closure being entered,
766 whether or not it has free variables, and whether we're running
767 sequentially or in parallel.
768
769 \begin{tabular}{lllll}
770 Closure Characteristics & Parallel & Node Req'd & Argument Passing & Enter Via \\
771 Unknown                         & no & yes & stack      & node \\
772 Known fun ($\ge$ 1 arg), no fvs         & no & no  & registers  & fast entry (enough args) \\
773 \ & \ & \ & \                                           & slow entry (otherwise) \\
774 Known fun ($\ge$ 1 arg), fvs    & no & yes & registers  & fast entry (enough args) \\
775 0 arg, no fvs @\r,\s@           & no & no  & n/a        & direct entry \\
776 0 arg, no fvs @\u@              & no & yes & n/a        & node \\
777 0 arg, fvs @\r,\s@              & no & yes & n/a        & direct entry \\
778 0 arg, fvs @\u@                 & no & yes & n/a        & node \\
779
780 Unknown                         & yes & yes & stack     & node \\
781 Known fun ($\ge$ 1 arg), no fvs         & yes & no  & registers & fast entry (enough args) \\
782 \ & \ & \ & \                                           & slow entry (otherwise) \\
783 Known fun ($\ge$ 1 arg), fvs    & yes & yes & registers & node \\
784 0 arg, no fvs @\r,\s@           & yes & no  & n/a       & direct entry \\
785 0 arg, no fvs @\u@              & yes & yes & n/a       & node \\
786 0 arg, fvs @\r,\s@              & yes & yes & n/a       & node \\
787 0 arg, fvs @\u@                 & yes & yes & n/a       & node\\
788 \end{tabular}
789
790 When black-holing, single-entry closures could also be entered via node
791 (rather than directly) to catch double-entry.
792
793 \begin{code}
794 data EntryConvention
795   = ViaNode                             -- The "normal" convention
796
797   | StdEntry CLabel                     -- Jump to this code, with args on stack
798              (Maybe CLabel)             -- possibly setting infoptr to this
799
800   | DirectEntry                         -- Jump directly to code, with args in regs
801         CLabel                          --   The code label
802         Int                             --   Its arity
803         [MagicId]                       --   Its register assignments (possibly empty)
804
805 getEntryConvention :: Id                -- Function being applied
806                    -> LambdaFormInfo    -- Its info
807                    -> [PrimRep]         -- Available arguments
808                    -> FCode EntryConvention
809
810 getEntryConvention id lf_info arg_kinds
811  =  nodeMustPointToIt lf_info   `thenFC` \ node_points ->
812     let
813         is_concurrent = opt_ForConcurrent
814     in
815     returnFC (
816
817     if (node_points && is_concurrent) then ViaNode else
818
819     case lf_info of
820
821         LFReEntrant _ arity _ ->
822             if arity == 0 || (length arg_kinds) < arity then
823                 StdEntry (mkStdEntryLabel id) Nothing
824             else
825                 DirectEntry (mkFastEntryLabel id arity) arity arg_regs
826           where
827             (arg_regs, _) = assignRegs live_regs (take arity arg_kinds)
828             live_regs = if node_points then [node] else []
829
830         LFCon con zero_arity
831                           -> let itbl = if zero_arity then
832                                         mkPhantomInfoTableLabel con
833                                         else
834                                         mkConInfoTableLabel con
835                              in
836                              --false:ASSERT (null arg_kinds)    -- Should have no args (meaning what?)
837                              StdEntry (mkConEntryLabel con) (Just itbl)
838
839         LFTuple tup zero_arity
840                           -> --false:ASSERT (null arg_kinds)    -- Should have no args (meaning what?)
841                              StdEntry (mkConEntryLabel tup) (Just (mkConInfoTableLabel tup))
842
843         LFThunk _ _ updatable std_form_info
844           -> if updatable
845              then ViaNode
846              else StdEntry (thunkEntryLabel id std_form_info updatable) Nothing
847
848         LFArgument  -> ViaNode
849         LFImported  -> ViaNode
850         LFBlackHole -> ViaNode  -- Presumably the black hole has by now
851                                 -- been updated, but we don't know with
852                                 -- what, so we enter via Node
853
854         LFLetNoEscape arity _
855           -> ASSERT(arity == length arg_kinds)
856              DirectEntry (mkStdEntryLabel id) arity arg_regs
857          where
858             (arg_regs, _) = assignRegs live_regs arg_kinds
859             live_regs     = if node_points then [node] else []
860     )
861
862 blackHoleOnEntry :: Bool        -- No-black-holing flag
863                  -> ClosureInfo
864                  -> Bool
865
866 -- Static closures are never themselves black-holed.
867 -- Updatable ones will be overwritten with a CAFList cell, which points to a black hole;
868 -- Single-entry ones have no fvs to plug, and we trust they don't form part of a loop.
869
870 blackHoleOnEntry no_black_holing (MkClosureInfo _ _ (StaticRep _ _)) = False
871
872 blackHoleOnEntry no_black_holing (MkClosureInfo _ lf_info _)
873   = case lf_info of
874         LFReEntrant _ _ _         -> False
875         LFThunk _ no_fvs updatable _
876           -> if updatable
877              then not no_black_holing
878              else not no_fvs
879         other -> panic "blackHoleOnEntry"       -- Should never happen
880
881 getStandardFormThunkInfo
882         :: LambdaFormInfo
883         -> Maybe [StgArg]               -- Nothing    => not a standard-form thunk
884                                         -- Just atoms => a standard-form thunk with payload atoms
885
886 getStandardFormThunkInfo (LFThunk _ _ _ (SelectorThunk scrutinee _ _))
887   = --trace "Selector thunk: missed opportunity to save info table + code"
888     Nothing
889         -- Just [StgVarArg scrutinee]
890         -- We can't save the info tbl + code until we have a way to generate
891         -- a fixed family thereof.
892
893 getStandardFormThunkInfo (LFThunk _ _ _ (VapThunk fun_id args fun_in_payload))
894   | fun_in_payload = Just (StgVarArg fun_id : args)
895   | otherwise      = Just args
896
897 getStandardFormThunkInfo other_lf_info = Nothing
898
899 maybeSelectorInfo (MkClosureInfo _ (LFThunk _ _ _ (SelectorThunk _ con offset)) _) = Just (con,offset)
900 maybeSelectorInfo _ = Nothing
901 \end{code}
902
903 Avoiding generating entries and info tables
904 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
905 At present, for every function we generate all of the following,
906 just in case.  But they aren't always all needed, as noted below:
907
908 [NB1: all of this applies only to *functions*.  Thunks always
909 have closure, info table, and entry code.]
910
911 [NB2: All are needed if the function is *exported*, just to play safe.]
912
913
914 * Fast-entry code  ALWAYS NEEDED
915
916 * Slow-entry code
917         Needed iff (a) we have any un-saturated calls to the function
918         OR         (b) the function is passed as an arg
919         OR         (c) we're in the parallel world and the function has free vars
920                         [Reason: in parallel world, we always enter functions
921                         with free vars via the closure.]
922
923 * The function closure
924         Needed iff (a) we have any un-saturated calls to the function
925         OR         (b) the function is passed as an arg
926         OR         (c) if the function has free vars (ie not top level)
927
928   Why case (a) here?  Because if the arg-satis check fails,
929   UpdatePAP stuffs a pointer to the function closure in the PAP.
930   [Could be changed; UpdatePAP could stuff in a code ptr instead,
931    but doesn't seem worth it.]
932
933   [NB: these conditions imply that we might need the closure
934   without the slow-entry code.  Here's how.
935
936         f x y = let g w = ...x..y..w...
937                 in
938                 ...(g t)...
939
940   Here we need a closure for g which contains x and y,
941   but since the calls are all saturated we just jump to the
942   fast entry point for g, with R1 pointing to the closure for g.]
943
944
945 * Standard info table
946         Needed iff (a) we have any un-saturated calls to the function
947         OR         (b) the function is passed as an arg
948         OR         (c) the function has free vars (ie not top level)
949
950         NB.  In the sequential world, (c) is only required so that the function closure has
951         an info table to point to, to keep the storage manager happy.
952         If (c) alone is true we could fake up an info table by choosing
953         one of a standard family of info tables, whose entry code just
954         bombs out.
955
956         [NB In the parallel world (c) is needed regardless because
957         we enter functions with free vars via the closure.]
958
959         If (c) is retained, then we'll sometimes generate an info table
960         (for storage mgr purposes) without slow-entry code.  Then we need
961         to use an error label in the info table to substitute for the absent
962         slow entry code.
963
964 * Standard vap-entry code
965   Standard vap-entry info table
966         Needed iff we have any updatable thunks of the standard vap-entry shape.
967
968 * Single-update vap-entry code
969   Single-update vap-entry info table
970         Needed iff we have any non-updatable thunks of the
971         standard vap-entry shape.
972
973
974 \begin{code}
975 staticClosureRequired
976         :: Id
977         -> StgBinderInfo
978         -> LambdaFormInfo
979         -> Bool
980 staticClosureRequired binder (StgBinderInfo arg_occ unsat_occ _ _ _)
981                       (LFReEntrant top_level _ _)       -- It's a function
982   = ASSERT( top_level )                 -- Assumption: it's a top-level, no-free-var binding
983     arg_occ             -- There's an argument occurrence
984     || unsat_occ        -- There's an unsaturated call
985     || externallyVisibleId binder
986
987 staticClosureRequired binder other_binder_info other_lf_info = True
988
989 slowFunEntryCodeRequired        -- Assumption: it's a function, not a thunk.
990         :: Id
991         -> StgBinderInfo
992         -> EntryConvention
993         -> Bool
994 slowFunEntryCodeRequired binder (StgBinderInfo arg_occ unsat_occ _ _ _) entry_conv
995   = arg_occ             -- There's an argument occurrence
996     || unsat_occ        -- There's an unsaturated call
997     || externallyVisibleId binder
998     || (case entry_conv of { DirectEntry _ _ _ -> False; other -> True })
999             {- The last case deals with the parallel world; a function usually
1000                as a DirectEntry convention, but if it doesn't we must generate slow-entry code -}
1001
1002 slowFunEntryCodeRequired binder NoStgBinderInfo _ = True
1003
1004 funInfoTableRequired
1005         :: Id
1006         -> StgBinderInfo
1007         -> LambdaFormInfo
1008         -> Bool
1009 funInfoTableRequired  binder (StgBinderInfo arg_occ unsat_occ _ _ _)
1010                      (LFReEntrant top_level _ _)
1011   = not top_level
1012     || arg_occ          -- There's an argument occurrence
1013     || unsat_occ        -- There's an unsaturated call
1014     || externallyVisibleId binder
1015
1016 funInfoTableRequired other_binder_info binder other_lf_info = True
1017
1018 -- We need the vector-apply entry points for a function if
1019 -- there's a vector-apply occurrence in this module
1020
1021 stdVapRequired, noUpdVapRequired :: StgBinderInfo -> Bool
1022
1023 stdVapRequired binder_info
1024   = case binder_info of
1025       StgBinderInfo _ _ std_vap_occ _ _ -> std_vap_occ
1026       _                                 -> False
1027
1028 noUpdVapRequired binder_info
1029   = case binder_info of
1030       StgBinderInfo _ _ _ no_upd_vap_occ _ -> no_upd_vap_occ
1031       _                                    -> False
1032 \end{code}
1033
1034 @lfArity@ extracts the arity of a function from its LFInfo
1035
1036 \begin{code}
1037 {- Not needed any more
1038
1039 lfArity_maybe (LFReEntrant _ arity _) = Just arity
1040
1041 -- Removed SLPJ March 97. I don't believe these two; 
1042 -- LFCon is used for construcor *applications*, not constructors!
1043 --
1044 -- lfArity_maybe (LFCon con _)        = Just (dataConArity con)
1045 -- lfArity_maybe (LFTuple con _)              = Just (dataConArity con)
1046
1047 lfArity_maybe other                   = Nothing
1048 -}
1049 \end{code}
1050
1051 %************************************************************************
1052 %*                                                                      *
1053 \subsection[ClosureInfo-misc-funs]{Misc functions about @ClosureInfo@, etc.}
1054 %*                                                                      *
1055 %************************************************************************
1056
1057 \begin{code}
1058
1059 isStaticClosure :: ClosureInfo -> Bool
1060 isStaticClosure  (MkClosureInfo _ _ rep) = isStaticRep  rep
1061
1062 closureId :: ClosureInfo -> Id
1063 closureId (MkClosureInfo id _ _) = id
1064
1065 closureSMRep :: ClosureInfo -> SMRep
1066 closureSMRep (MkClosureInfo _ _ sm_rep) = sm_rep
1067
1068 closureLFInfo :: ClosureInfo -> LambdaFormInfo
1069 closureLFInfo (MkClosureInfo _ lf_info _) = lf_info
1070
1071 closureUpdReqd :: ClosureInfo -> Bool
1072
1073 closureUpdReqd (MkClosureInfo _ (LFThunk _ _ upd _) _) = upd
1074 closureUpdReqd (MkClosureInfo _ LFBlackHole _)         = True
1075         -- Black-hole closures are allocated to receive the results of an
1076         -- alg case with a named default... so they need to be updated.
1077 closureUpdReqd other_closure                           = False
1078
1079 closureSingleEntry :: ClosureInfo -> Bool
1080
1081 closureSingleEntry (MkClosureInfo _ (LFThunk _ _ upd _) _) = not upd
1082 closureSingleEntry other_closure                           = False
1083 \end{code}
1084
1085 Note: @closureType@ returns appropriately specialised tycon and
1086 datacons.
1087 \begin{code}
1088 closureType :: ClosureInfo -> Maybe (TyCon, [Type], [Id])
1089
1090 -- First, a turgid special case.  When we are generating the
1091 -- standard code and info-table for Vaps (which is done when the function
1092 -- defn is encountered), we don't have a convenient Id to hand whose
1093 -- type is that of (f x y z).  So we need to figure out the type
1094 -- rather than take it from the Id. The Id is probably just "f"!
1095
1096 closureType (MkClosureInfo id (LFThunk _ _ _ (VapThunk fun_id args _)) _)
1097   = splitAlgTyConApp_maybe (fun_result_ty (length args) (idType fun_id))
1098
1099 closureType (MkClosureInfo id lf _) = splitAlgTyConApp_maybe (idType id)
1100 \end{code}
1101
1102 @closureReturnsUnpointedType@ is used to check whether a closure, {\em
1103 once it has eaten its arguments}, returns an unboxed type.  For
1104 example, the closure for a function:
1105 \begin{verbatim}
1106         f :: Int -> Int#
1107 \end{verbatim}
1108 returns an unboxed type.  This is important when dealing with stack
1109 overflow checks.
1110 \begin{code}
1111 closureReturnsUnpointedType :: ClosureInfo -> Bool
1112
1113 closureReturnsUnpointedType (MkClosureInfo fun_id (LFReEntrant _ arity _) _)
1114   = isUnpointedType (fun_result_ty arity (idType fun_id))
1115
1116 closureReturnsUnpointedType other_closure = False
1117         -- All non-function closures aren't functions,
1118         -- and hence are boxed, since they are heap alloc'd
1119
1120 -- fun_result_ty is a disgusting little bit of code that finds the result
1121 -- type of a function application.  It looks "through" new types.
1122 -- We don't have type args available any more, so we are pretty cavilier,
1123 -- and quite possibly plain wrong. Let's hope it doesn't matter if we are!
1124
1125 fun_result_ty arity ty
1126   | arity <= n_arg_tys
1127   = mkFunTys (drop arity arg_tys) res_ty
1128
1129   | otherwise
1130   = case splitAlgTyConApp_maybe res_ty of
1131       Nothing -> pprPanic "fun_result_ty:" (hsep [int arity,
1132                                                   ppr ty])
1133
1134       Just (tycon, tycon_arg_tys, [con]) | isNewTyCon tycon
1135            -> fun_result_ty (arity - n_arg_tys) rep_ty
1136            where
1137               ([rep_ty], _) = splitFunTys (applyTys (idType con) tycon_arg_tys)
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}