1 /* ----------------------------------------------------------------------------
3 * (c) The GHC Team, 1998-2003
5 * Support for heap profiling
7 * --------------------------------------------------------------------------*/
9 #include "PosixSource.h"
13 #include "Profiling.h"
17 #include "RetainerProfile.h"
18 #include "LdvProfile.h"
21 #include "sm/GCThread.h"
25 /* -----------------------------------------------------------------------------
26 * era stores the current time period. It is the same as the
27 * number of censuses that have been performed.
30 * era must be no longer than LDV_SHIFT (15 or 30) bits.
32 * era is initialized to 1 in initHeapProfiling().
34 * max_era is initialized to 2^LDV_SHIFT in initHeapProfiling().
35 * When era reaches max_era, the profiling stops because a closure can
36 * store only up to (max_era - 1) as its creation or last use time.
37 * -------------------------------------------------------------------------- */
41 /* -----------------------------------------------------------------------------
44 * For most heap profiles each closure identity gets a simple count
45 * of live words in the heap at each census. However, if we're
46 * selecting by biography, then we have to keep the various
47 * lag/drag/void counters for each identity.
48 * -------------------------------------------------------------------------- */
49 typedef struct _counter
{
54 long prim
; // total size of 'inherently used' closures
55 long not_used
; // total size of 'never used' closures
56 long used
; // total size of 'used at least once' closures
57 long void_total
; // current total size of 'destroyed without being used' closures
58 long drag_total
; // current total size of 'used at least once and waiting to die'
61 struct _counter
*next
;
65 initLDVCtr( counter
*ctr
)
68 ctr
->c
.ldv
.not_used
= 0;
70 ctr
->c
.ldv
.void_total
= 0;
71 ctr
->c
.ldv
.drag_total
= 0;
75 double time
; // the time in MUT time when the census is made
80 // for LDV profiling, when just displaying by LDV
88 static Census
*censuses
= NULL
;
89 static nat n_censuses
= 0;
92 static void aggregateCensusInfo( void );
95 static void dumpCensus( Census
*census
);
97 static rtsBool
closureSatisfiesConstraints( StgClosure
* p
);
99 /* ----------------------------------------------------------------------------
100 * Find the "closure identity", which is a unique pointer representing
101 * the band to which this closure's heap space is attributed in the
103 * ------------------------------------------------------------------------- */
105 closureIdentity( StgClosure
*p
)
107 switch (RtsFlags
.ProfFlags
.doHeapProfile
) {
111 return p
->header
.prof
.ccs
;
113 return p
->header
.prof
.ccs
->cc
->module
;
115 return GET_PROF_DESC(get_itbl(p
));
117 return GET_PROF_TYPE(get_itbl(p
));
118 case HEAP_BY_RETAINER
:
119 // AFAIK, the only closures in the heap which might not have a
120 // valid retainer set are DEAD_WEAK closures.
121 if (isRetainerSetFieldValid(p
))
122 return retainerSetOf(p
);
127 case HEAP_BY_CLOSURE_TYPE
:
131 switch (info
->type
) {
139 case CONSTR_NOCAF_STATIC
:
140 return GET_CON_DESC(itbl_to_con_itbl(info
));
142 return closure_type_names
[info
->type
];
148 barf("closureIdentity");
152 /* --------------------------------------------------------------------------
153 * Profiling type predicates
154 * ----------------------------------------------------------------------- */
156 STATIC_INLINE rtsBool
157 doingLDVProfiling( void )
159 return (RtsFlags
.ProfFlags
.doHeapProfile
== HEAP_BY_LDV
160 || RtsFlags
.ProfFlags
.bioSelector
!= NULL
);
163 STATIC_INLINE rtsBool
164 doingRetainerProfiling( void )
166 return (RtsFlags
.ProfFlags
.doHeapProfile
== HEAP_BY_RETAINER
167 || RtsFlags
.ProfFlags
.retainerSelector
!= NULL
);
169 #endif /* PROFILING */
171 // Precesses a closure 'c' being destroyed whose size is 'size'.
172 // Make sure that LDV_recordDead() is not invoked on 'inherently used' closures
173 // such as TSO; they should not be involved in computing dragNew or voidNew.
175 // Even though era is checked in both LdvCensusForDead() and
176 // LdvCensusKillAll(), we still need to make sure that era is > 0 because
177 // LDV_recordDead() may be called from elsewhere in the runtime system. E.g.,
178 // when a thunk is replaced by an indirection object.
182 LDV_recordDead( StgClosure
*c
, nat size
)
188 if (era
> 0 && closureSatisfiesConstraints(c
)) {
189 size
-= sizeofW(StgProfHeader
);
190 ASSERT(LDVW(c
) != 0);
191 if ((LDVW((c
)) & LDV_STATE_MASK
) == LDV_STATE_CREATE
) {
192 t
= (LDVW((c
)) & LDV_CREATE_MASK
) >> LDV_SHIFT
;
194 if (RtsFlags
.ProfFlags
.bioSelector
== NULL
) {
195 censuses
[t
].void_total
+= (long)size
;
196 censuses
[era
].void_total
-= (long)size
;
197 ASSERT(censuses
[t
].void_total
< censuses
[t
].not_used
);
199 id
= closureIdentity(c
);
200 ctr
= lookupHashTable(censuses
[t
].hash
, (StgWord
)id
);
201 ASSERT( ctr
!= NULL
);
202 ctr
->c
.ldv
.void_total
+= (long)size
;
203 ctr
= lookupHashTable(censuses
[era
].hash
, (StgWord
)id
);
205 ctr
= arenaAlloc(censuses
[era
].arena
, sizeof(counter
));
207 insertHashTable(censuses
[era
].hash
, (StgWord
)id
, ctr
);
209 ctr
->next
= censuses
[era
].ctrs
;
210 censuses
[era
].ctrs
= ctr
;
212 ctr
->c
.ldv
.void_total
-= (long)size
;
216 t
= LDVW((c
)) & LDV_LAST_MASK
;
218 if (RtsFlags
.ProfFlags
.bioSelector
== NULL
) {
219 censuses
[t
+1].drag_total
+= size
;
220 censuses
[era
].drag_total
-= size
;
223 id
= closureIdentity(c
);
224 ctr
= lookupHashTable(censuses
[t
+1].hash
, (StgWord
)id
);
225 ASSERT( ctr
!= NULL
);
226 ctr
->c
.ldv
.drag_total
+= (long)size
;
227 ctr
= lookupHashTable(censuses
[era
].hash
, (StgWord
)id
);
229 ctr
= arenaAlloc(censuses
[era
].arena
, sizeof(counter
));
231 insertHashTable(censuses
[era
].hash
, (StgWord
)id
, ctr
);
233 ctr
->next
= censuses
[era
].ctrs
;
234 censuses
[era
].ctrs
= ctr
;
236 ctr
->c
.ldv
.drag_total
-= (long)size
;
244 /* --------------------------------------------------------------------------
245 * Initialize censuses[era];
246 * ----------------------------------------------------------------------- */
249 initEra(Census
*census
)
251 census
->hash
= allocHashTable();
253 census
->arena
= newArena();
255 census
->not_used
= 0;
258 census
->void_total
= 0;
259 census
->drag_total
= 0;
263 freeEra(Census
*census
)
265 if (RtsFlags
.ProfFlags
.bioSelector
!= NULL
)
266 // when bioSelector==NULL, these are freed in heapCensus()
268 arenaFree(census
->arena
);
269 freeHashTable(census
->hash
, NULL
);
273 /* --------------------------------------------------------------------------
274 * Increases era by 1 and initialize census[era].
275 * Reallocates gi[] and increases its size if needed.
276 * ----------------------------------------------------------------------- */
282 if (doingLDVProfiling()) {
285 if (era
== max_era
) {
286 errorBelch("maximum number of censuses reached; use +RTS -i to reduce");
287 stg_exit(EXIT_FAILURE
);
290 if (era
== n_censuses
) {
292 censuses
= stgReallocBytes(censuses
, sizeof(Census
) * n_censuses
,
296 #endif /* PROFILING */
298 initEra( &censuses
[era
] );
301 /* ----------------------------------------------------------------------------
302 * Heap profiling by info table
303 * ------------------------------------------------------------------------- */
305 #if !defined(PROFILING)
307 static char *hp_filename
;
309 void initProfiling1 (void)
313 void freeProfiling (void)
317 void initProfiling2 (void)
321 prog
= stgMallocBytes(strlen(prog_name
) + 1, "initProfiling2");
322 strcpy(prog
, prog_name
);
323 #ifdef mingw32_HOST_OS
324 // on Windows, drop the .exe suffix if there is one
327 suff
= strrchr(prog
,'.');
328 if (suff
!= NULL
&& !strcmp(suff
,".exe")) {
334 if (RtsFlags
.ProfFlags
.doHeapProfile
) {
335 /* Initialise the log file name */
336 hp_filename
= stgMallocBytes(strlen(prog
) + 6, "hpFileName");
337 sprintf(hp_filename
, "%s.hp", prog
);
339 /* open the log file */
340 if ((hp_file
= fopen(hp_filename
, "w")) == NULL
) {
341 debugBelch("Can't open profiling report file %s\n",
343 RtsFlags
.ProfFlags
.doHeapProfile
= 0;
353 void endProfiling( void )
357 #endif /* !PROFILING */
360 printSample(rtsBool beginSample
, StgDouble sampleValue
)
362 StgDouble fractionalPart
, integralPart
;
363 fractionalPart
= modf(sampleValue
, &integralPart
);
364 fprintf(hp_file
, "%s %" FMT_Word64
".%02" FMT_Word64
"\n",
365 (beginSample ?
"BEGIN_SAMPLE" : "END_SAMPLE"),
366 (StgWord64
)integralPart
, (StgWord64
)(fractionalPart
* 100));
372 /* --------------------------------------------------------------------------
373 * Initialize the heap profilier
374 * ----------------------------------------------------------------------- */
376 initHeapProfiling(void)
378 if (! RtsFlags
.ProfFlags
.doHeapProfile
) {
383 if (doingLDVProfiling() && doingRetainerProfiling()) {
384 errorBelch("cannot mix -hb and -hr");
385 stg_exit(EXIT_FAILURE
);
389 // we only count eras if we're doing LDV profiling. Otherwise era
392 if (doingLDVProfiling()) {
400 // max_era = 2^LDV_SHIFT
401 max_era
= 1 << LDV_SHIFT
;
404 censuses
= stgMallocBytes(sizeof(Census
) * n_censuses
, "initHeapProfiling");
406 initEra( &censuses
[era
] );
408 /* initProfilingLogFile(); */
409 fprintf(hp_file
, "JOB \"%s", prog_name
);
414 for(count
= 1; count
< prog_argc
; count
++)
415 fprintf(hp_file
, " %s", prog_argv
[count
]);
416 fprintf(hp_file
, " +RTS");
417 for(count
= 0; count
< rts_argc
; count
++)
418 fprintf(hp_file
, " %s", rts_argv
[count
]);
420 #endif /* PROFILING */
422 fprintf(hp_file
, "\"\n" );
424 fprintf(hp_file
, "DATE \"%s\"\n", time_str());
426 fprintf(hp_file
, "SAMPLE_UNIT \"seconds\"\n");
427 fprintf(hp_file
, "VALUE_UNIT \"bytes\"\n");
429 printSample(rtsTrue
, 0);
430 printSample(rtsFalse
, 0);
433 if (doingRetainerProfiling()) {
434 initRetainerProfiling();
442 endHeapProfiling(void)
446 if (! RtsFlags
.ProfFlags
.doHeapProfile
) {
451 if (doingRetainerProfiling()) {
452 endRetainerProfiling();
457 if (doingLDVProfiling()) {
460 aggregateCensusInfo();
461 for (t
= 1; t
< era
; t
++) {
462 dumpCensus( &censuses
[t
] );
468 if (doingLDVProfiling()) {
470 for (t
= 1; t
<= era
; t
++) {
471 freeEra( &censuses
[t
] );
474 freeEra( &censuses
[0] );
477 freeEra( &censuses
[0] );
482 seconds
= mut_user_time();
483 printSample(rtsTrue
, seconds
);
484 printSample(rtsFalse
, seconds
);
492 buf_append(char *p
, const char *q
, char *end
)
496 for (m
= 0; p
< end
; p
++, q
++, m
++) {
498 if (*q
== '\0') { break; }
504 fprint_ccs(FILE *fp
, CostCentreStack
*ccs
, nat max_length
)
506 char buf
[max_length
+1], *p
, *buf_end
;
508 // MAIN on its own gets printed as "MAIN", otherwise we ignore MAIN.
509 if (ccs
== CCS_MAIN
) {
514 fprintf(fp
, "(%ld)", ccs
->ccsID
);
517 buf_end
= buf
+ max_length
+ 1;
519 // keep printing components of the stack until we run out of space
520 // in the buffer. If we run out of space, end with "...".
521 for (; ccs
!= NULL
&& ccs
!= CCS_MAIN
; ccs
= ccs
->prevStack
) {
523 // CAF cost centres print as M.CAF, but we leave the module
524 // name out of all the others to save space.
525 if (!strcmp(ccs
->cc
->label
,"CAF")) {
526 p
+= buf_append(p
, ccs
->cc
->module
, buf_end
);
527 p
+= buf_append(p
, ".CAF", buf_end
);
529 p
+= buf_append(p
, ccs
->cc
->label
, buf_end
);
530 if (ccs
->prevStack
!= NULL
&& ccs
->prevStack
!= CCS_MAIN
) {
531 p
+= buf_append(p
, "/", buf_end
);
536 sprintf(buf
+max_length
-4, "...");
540 fprintf(fp
, "%s", buf
);
544 strMatchesSelector( char* str
, char* sel
)
547 // debugBelch("str_matches_selector %s %s\n", str, sel);
549 // Compare str against wherever we've got to in sel.
551 while (*p
!= '\0' && *sel
!= ',' && *sel
!= '\0' && *p
== *sel
) {
554 // Match if all of str used and have reached the end of a sel fragment.
555 if (*p
== '\0' && (*sel
== ',' || *sel
== '\0'))
558 // No match. Advance sel to the start of the next elem.
559 while (*sel
!= ',' && *sel
!= '\0') sel
++;
560 if (*sel
== ',') sel
++;
562 /* Run out of sel ?? */
563 if (*sel
== '\0') return rtsFalse
;
567 #endif /* PROFILING */
569 /* -----------------------------------------------------------------------------
570 * Figure out whether a closure should be counted in this census, by
571 * testing against all the specified constraints.
572 * -------------------------------------------------------------------------- */
574 closureSatisfiesConstraints( StgClosure
* p
)
576 #if !defined(PROFILING)
577 (void)p
; /* keep gcc -Wall happy */
582 // The CCS has a selected field to indicate whether this closure is
583 // deselected by not being mentioned in the module, CC, or CCS
585 if (!p
->header
.prof
.ccs
->selected
) {
589 if (RtsFlags
.ProfFlags
.descrSelector
) {
590 b
= strMatchesSelector( (GET_PROF_DESC(get_itbl((StgClosure
*)p
))),
591 RtsFlags
.ProfFlags
.descrSelector
);
592 if (!b
) return rtsFalse
;
594 if (RtsFlags
.ProfFlags
.typeSelector
) {
595 b
= strMatchesSelector( (GET_PROF_TYPE(get_itbl((StgClosure
*)p
))),
596 RtsFlags
.ProfFlags
.typeSelector
);
597 if (!b
) return rtsFalse
;
599 if (RtsFlags
.ProfFlags
.retainerSelector
) {
602 // We must check that the retainer set is valid here. One
603 // reason it might not be valid is if this closure is a
604 // a newly deceased weak pointer (i.e. a DEAD_WEAK), since
605 // these aren't reached by the retainer profiler's traversal.
606 if (isRetainerSetFieldValid((StgClosure
*)p
)) {
607 rs
= retainerSetOf((StgClosure
*)p
);
609 for (i
= 0; i
< rs
->num
; i
++) {
610 b
= strMatchesSelector( rs
->element
[i
]->cc
->label
,
611 RtsFlags
.ProfFlags
.retainerSelector
);
612 if (b
) return rtsTrue
;
619 #endif /* PROFILING */
622 /* -----------------------------------------------------------------------------
623 * Aggregate the heap census info for biographical profiling
624 * -------------------------------------------------------------------------- */
627 aggregateCensusInfo( void )
631 counter
*c
, *d
, *ctrs
;
634 if (!doingLDVProfiling()) return;
636 // Aggregate the LDV counters when displaying by biography.
637 if (RtsFlags
.ProfFlags
.doHeapProfile
== HEAP_BY_LDV
) {
638 long void_total
, drag_total
;
640 // Now we compute void_total and drag_total for each census
641 // After the program has finished, the void_total field of
642 // each census contains the count of words that were *created*
643 // in this era and were eventually void. Conversely, if a
644 // void closure was destroyed in this era, it will be
645 // represented by a negative count of words in void_total.
647 // To get the count of live words that are void at each
648 // census, just propagate the void_total count forwards:
652 for (t
= 1; t
< era
; t
++) { // note: start at 1, not 0
653 void_total
+= censuses
[t
].void_total
;
654 drag_total
+= censuses
[t
].drag_total
;
655 censuses
[t
].void_total
= void_total
;
656 censuses
[t
].drag_total
= drag_total
;
658 ASSERT( censuses
[t
].void_total
<= censuses
[t
].not_used
);
659 // should be true because: void_total is the count of
660 // live words that are void at this census, which *must*
661 // be less than the number of live words that have not
664 ASSERT( censuses
[t
].drag_total
<= censuses
[t
].used
);
665 // similar reasoning as above.
671 // otherwise... we're doing a heap profile that is restricted to
672 // some combination of lag, drag, void or use. We've kept all the
673 // census info for all censuses so far, but we still need to
674 // aggregate the counters forwards.
677 acc
= allocHashTable();
680 for (t
= 1; t
< era
; t
++) {
682 // first look through all the counters we're aggregating
683 for (c
= ctrs
; c
!= NULL
; c
= c
->next
) {
684 // if one of the totals is non-zero, then this closure
685 // type must be present in the heap at this census time...
686 d
= lookupHashTable(censuses
[t
].hash
, (StgWord
)c
->identity
);
689 // if this closure identity isn't present in the
690 // census for this time period, then our running
691 // totals *must* be zero.
692 ASSERT(c
->c
.ldv
.void_total
== 0 && c
->c
.ldv
.drag_total
== 0);
694 // debugCCS(c->identity);
695 // debugBelch(" census=%d void_total=%d drag_total=%d\n",
696 // t, c->c.ldv.void_total, c->c.ldv.drag_total);
698 d
->c
.ldv
.void_total
+= c
->c
.ldv
.void_total
;
699 d
->c
.ldv
.drag_total
+= c
->c
.ldv
.drag_total
;
700 c
->c
.ldv
.void_total
= d
->c
.ldv
.void_total
;
701 c
->c
.ldv
.drag_total
= d
->c
.ldv
.drag_total
;
703 ASSERT( c
->c
.ldv
.void_total
>= 0 );
704 ASSERT( c
->c
.ldv
.drag_total
>= 0 );
708 // now look through the counters in this census to find new ones
709 for (c
= censuses
[t
].ctrs
; c
!= NULL
; c
= c
->next
) {
710 d
= lookupHashTable(acc
, (StgWord
)c
->identity
);
712 d
= arenaAlloc( arena
, sizeof(counter
) );
714 insertHashTable( acc
, (StgWord
)c
->identity
, d
);
715 d
->identity
= c
->identity
;
718 d
->c
.ldv
.void_total
= c
->c
.ldv
.void_total
;
719 d
->c
.ldv
.drag_total
= c
->c
.ldv
.drag_total
;
721 ASSERT( c
->c
.ldv
.void_total
>= 0 );
722 ASSERT( c
->c
.ldv
.drag_total
>= 0 );
726 freeHashTable(acc
, NULL
);
731 /* -----------------------------------------------------------------------------
732 * Print out the results of a heap census.
733 * -------------------------------------------------------------------------- */
735 dumpCensus( Census
*census
)
740 printSample(rtsTrue
, census
->time
);
743 if (RtsFlags
.ProfFlags
.doHeapProfile
== HEAP_BY_LDV
) {
744 fprintf(hp_file
, "VOID\t%lu\n", (unsigned long)(census
->void_total
) * sizeof(W_
));
745 fprintf(hp_file
, "LAG\t%lu\n",
746 (unsigned long)(census
->not_used
- census
->void_total
) * sizeof(W_
));
747 fprintf(hp_file
, "USE\t%lu\n",
748 (unsigned long)(census
->used
- census
->drag_total
) * sizeof(W_
));
749 fprintf(hp_file
, "INHERENT_USE\t%lu\n",
750 (unsigned long)(census
->prim
) * sizeof(W_
));
751 fprintf(hp_file
, "DRAG\t%lu\n",
752 (unsigned long)(census
->drag_total
) * sizeof(W_
));
753 printSample(rtsFalse
, census
->time
);
758 for (ctr
= census
->ctrs
; ctr
!= NULL
; ctr
= ctr
->next
) {
761 if (RtsFlags
.ProfFlags
.bioSelector
!= NULL
) {
763 if (strMatchesSelector("lag", RtsFlags
.ProfFlags
.bioSelector
))
764 count
+= ctr
->c
.ldv
.not_used
- ctr
->c
.ldv
.void_total
;
765 if (strMatchesSelector("drag", RtsFlags
.ProfFlags
.bioSelector
))
766 count
+= ctr
->c
.ldv
.drag_total
;
767 if (strMatchesSelector("void", RtsFlags
.ProfFlags
.bioSelector
))
768 count
+= ctr
->c
.ldv
.void_total
;
769 if (strMatchesSelector("use", RtsFlags
.ProfFlags
.bioSelector
))
770 count
+= ctr
->c
.ldv
.used
- ctr
->c
.ldv
.drag_total
;
774 count
= ctr
->c
.resid
;
777 ASSERT( count
>= 0 );
779 if (count
== 0) continue;
781 #if !defined(PROFILING)
782 switch (RtsFlags
.ProfFlags
.doHeapProfile
) {
783 case HEAP_BY_CLOSURE_TYPE
:
784 fprintf(hp_file
, "%s", (char *)ctr
->identity
);
790 switch (RtsFlags
.ProfFlags
.doHeapProfile
) {
792 fprint_ccs(hp_file
, (CostCentreStack
*)ctr
->identity
, RtsFlags
.ProfFlags
.ccsLength
);
797 fprintf(hp_file
, "%s", (char *)ctr
->identity
);
799 case HEAP_BY_RETAINER
:
801 RetainerSet
*rs
= (RetainerSet
*)ctr
->identity
;
803 // it might be the distinguished retainer set rs_MANY:
804 if (rs
== &rs_MANY
) {
805 fprintf(hp_file
, "MANY");
809 // Mark this retainer set by negating its id, because it
810 // has appeared in at least one census. We print the
811 // values of all such retainer sets into the log file at
812 // the end. A retainer set may exist but not feature in
813 // any censuses if it arose as the intermediate retainer
814 // set for some closure during retainer set calculation.
818 // report in the unit of bytes: * sizeof(StgWord)
819 printRetainerSetShort(hp_file
, rs
, RtsFlags
.ProfFlags
.ccsLength
);
823 barf("dumpCensus; doHeapProfile");
827 fprintf(hp_file
, "\t%" FMT_SizeT
"\n", (W_
)count
* sizeof(W_
));
830 printSample(rtsFalse
, census
->time
);
834 static void heapProfObject(Census
*census
, StgClosure
*p
, nat size
,
848 // subtract the profiling overhead
849 real_size
= size
- sizeofW(StgProfHeader
);
854 if (closureSatisfiesConstraints((StgClosure
*)p
)) {
856 if (RtsFlags
.ProfFlags
.doHeapProfile
== HEAP_BY_LDV
) {
858 census
->prim
+= real_size
;
859 else if ((LDVW(p
) & LDV_STATE_MASK
) == LDV_STATE_CREATE
)
860 census
->not_used
+= real_size
;
862 census
->used
+= real_size
;
866 identity
= closureIdentity((StgClosure
*)p
);
868 if (identity
!= NULL
) {
869 ctr
= lookupHashTable( census
->hash
, (StgWord
)identity
);
872 if (RtsFlags
.ProfFlags
.bioSelector
!= NULL
) {
874 ctr
->c
.ldv
.prim
+= real_size
;
875 else if ((LDVW(p
) & LDV_STATE_MASK
) == LDV_STATE_CREATE
)
876 ctr
->c
.ldv
.not_used
+= real_size
;
878 ctr
->c
.ldv
.used
+= real_size
;
882 ctr
->c
.resid
+= real_size
;
885 ctr
= arenaAlloc( census
->arena
, sizeof(counter
) );
887 insertHashTable( census
->hash
, (StgWord
)identity
, ctr
);
888 ctr
->identity
= identity
;
889 ctr
->next
= census
->ctrs
;
893 if (RtsFlags
.ProfFlags
.bioSelector
!= NULL
) {
895 ctr
->c
.ldv
.prim
= real_size
;
896 else if ((LDVW(p
) & LDV_STATE_MASK
) == LDV_STATE_CREATE
)
897 ctr
->c
.ldv
.not_used
= real_size
;
899 ctr
->c
.ldv
.used
= real_size
;
903 ctr
->c
.resid
= real_size
;
911 /* -----------------------------------------------------------------------------
912 * Code to perform a heap census.
913 * -------------------------------------------------------------------------- */
915 heapCensusChain( Census
*census
, bdescr
*bd
)
922 for (; bd
!= NULL
; bd
= bd
->link
) {
924 // HACK: pretend a pinned block is just one big ARR_WORDS
925 // owned by CCS_PINNED. These blocks can be full of holes due
926 // to alignment constraints so we can't traverse the memory
927 // and do a proper census.
928 if (bd
->flags
& BF_PINNED
) {
930 SET_HDR(&arr
, &stg_ARR_WORDS_info
, CCS_PINNED
);
931 heapProfObject(census
, &arr
, bd
->blocks
* BLOCK_SIZE_W
, rtsTrue
);
936 while (p
< bd
->free
) {
937 info
= get_itbl((StgClosure
*)p
);
940 switch (info
->type
) {
943 size
= thunk_sizeW_fromITBL(info
);
949 size
= sizeofW(StgThunkHeader
) + 2;
955 size
= sizeofW(StgThunkHeader
) + 1;
973 size
= sizeW_fromITBL(info
);
977 // Special case/Delicate Hack: INDs don't normally
978 // appear, since we're doing this heap census right
979 // after GC. However, GarbageCollect() also does
980 // resurrectThreads(), which can update some
981 // blackholes when it calls raiseAsync() on the
982 // resurrected threads. So we know that any IND will
983 // be the size of a BLACKHOLE.
984 size
= BLACKHOLE_sizeW();
989 size
= bco_sizeW((StgBCO
*)p
);
1001 size
= sizeW_fromITBL(info
);
1005 size
= ap_sizeW((StgAP
*)p
);
1009 size
= pap_sizeW((StgPAP
*)p
);
1013 size
= ap_stack_sizeW((StgAP_STACK
*)p
);
1018 size
= arr_words_sizeW((StgArrWords
*)p
);
1021 case MUT_ARR_PTRS_CLEAN
:
1022 case MUT_ARR_PTRS_DIRTY
:
1023 case MUT_ARR_PTRS_FROZEN
:
1024 case MUT_ARR_PTRS_FROZEN0
:
1026 size
= mut_arr_ptrs_sizeW((StgMutArrPtrs
*)p
);
1032 if (RtsFlags
.ProfFlags
.includeTSOs
) {
1033 size
= sizeofW(StgTSO
);
1036 // Skip this TSO and move on to the next object
1037 p
+= sizeofW(StgTSO
);
1041 size
= sizeofW(StgTSO
);
1048 if (RtsFlags
.ProfFlags
.includeTSOs
) {
1049 size
= stack_sizeW((StgStack
*)p
);
1052 // Skip this TSO and move on to the next object
1053 p
+= stack_sizeW((StgStack
*)p
);
1057 size
= stack_sizeW((StgStack
*)p
);
1063 size
= sizeofW(StgTRecChunk
);
1067 barf("heapCensus, unknown object: %d", info
->type
);
1070 heapProfObject(census
,(StgClosure
*)p
,size
,prim
);
1077 void heapCensus (Time t
)
1083 census
= &censuses
[era
];
1084 census
->time
= mut_user_time_until(t
);
1086 // calculate retainer sets if necessary
1088 if (doingRetainerProfiling()) {
1094 stat_startHeapCensus();
1097 // Traverse the heap, collecting the census info
1098 for (g
= 0; g
< RtsFlags
.GcFlags
.generations
; g
++) {
1099 heapCensusChain( census
, generations
[g
].blocks
);
1100 // Are we interested in large objects? might be
1101 // confusing to include the stack in a heap profile.
1102 heapCensusChain( census
, generations
[g
].large_objects
);
1104 for (n
= 0; n
< n_capabilities
; n
++) {
1105 ws
= &gc_threads
[n
]->gens
[g
];
1106 heapCensusChain(census
, ws
->todo_bd
);
1107 heapCensusChain(census
, ws
->part_list
);
1108 heapCensusChain(census
, ws
->scavd_list
);
1112 // dump out the census info
1114 // We can't generate any info for LDV profiling until
1115 // the end of the run...
1116 if (!doingLDVProfiling())
1117 dumpCensus( census
);
1119 dumpCensus( census
);
1123 // free our storage, unless we're keeping all the census info for
1124 // future restriction by biography.
1126 if (RtsFlags
.ProfFlags
.bioSelector
== NULL
)
1128 freeHashTable( census
->hash
, NULL
/* don't free the elements */ );
1129 arenaFree( census
->arena
);
1130 census
->hash
= NULL
;
1131 census
->arena
= NULL
;
1135 // we're into the next time period now
1139 stat_endHeapCensus();