1 /* -----------------------------------------------------------------------------
3 * (c) The GHC Team, 1998-2004
5 * Storage manager front end
7 * ---------------------------------------------------------------------------*/
9 #include "PosixSource.h"
15 #include "BlockAlloc.h"
20 #include "OSThreads.h"
21 #include "Capability.h"
24 #include "RetainerProfile.h" // for counting memory blocks (memInventory)
32 * All these globals require sm_mutex to access in THREADED_RTS mode.
34 StgClosure *caf_list = NULL;
35 StgClosure *revertible_caf_list = NULL;
38 bdescr *small_alloc_list; /* allocate()d small objects */
39 bdescr *pinned_object_block; /* allocate pinned objects into this block */
40 nat alloc_blocks; /* number of allocate()d blocks since GC */
41 nat alloc_blocks_lim; /* approximate limit on alloc_blocks */
43 StgPtr alloc_Hp = NULL; /* next free byte in small_alloc_list */
44 StgPtr alloc_HpLim = NULL; /* end of block at small_alloc_list */
46 generation *generations = NULL; /* all the generations */
47 generation *g0 = NULL; /* generation 0, for convenience */
48 generation *oldest_gen = NULL; /* oldest generation, for convenience */
49 step *g0s0 = NULL; /* generation 0, step 0, for convenience */
51 ullong total_allocated = 0; /* total memory allocated during run */
53 nat n_nurseries = 0; /* == RtsFlags.ParFlags.nNodes, convenience */
54 step *nurseries = NULL; /* array of nurseries, >1 only if THREADED_RTS */
58 * Storage manager mutex: protects all the above state from
59 * simultaneous access by two STG threads.
63 * This mutex is used by atomicModifyMutVar# only
65 Mutex atomic_modify_mutvar_mutex;
72 static void *stgAllocForGMP (size_t size_in_bytes);
73 static void *stgReallocForGMP (void *ptr, size_t old_size, size_t new_size);
74 static void stgDeallocForGMP (void *ptr, size_t size);
77 initStep (step *stp, int g, int s)
82 stp->old_blocks = NULL;
83 stp->n_old_blocks = 0;
84 stp->gen = &generations[g];
90 stp->scavd_hpLim = NULL;
93 stp->large_objects = NULL;
94 stp->n_large_blocks = 0;
95 stp->new_large_objects = NULL;
96 stp->scavenged_large_objects = NULL;
97 stp->n_scavenged_large_blocks = 0;
98 stp->is_compacted = 0;
108 if (generations != NULL) {
109 // multi-init protection
113 /* Sanity check to make sure the LOOKS_LIKE_ macros appear to be
114 * doing something reasonable.
116 ASSERT(LOOKS_LIKE_INFO_PTR(&stg_BLACKHOLE_info));
117 ASSERT(LOOKS_LIKE_CLOSURE_PTR(&stg_dummy_ret_closure));
118 ASSERT(!HEAP_ALLOCED(&stg_dummy_ret_closure));
120 if (RtsFlags.GcFlags.maxHeapSize != 0 &&
121 RtsFlags.GcFlags.heapSizeSuggestion >
122 RtsFlags.GcFlags.maxHeapSize) {
123 RtsFlags.GcFlags.maxHeapSize = RtsFlags.GcFlags.heapSizeSuggestion;
126 if (RtsFlags.GcFlags.maxHeapSize != 0 &&
127 RtsFlags.GcFlags.minAllocAreaSize >
128 RtsFlags.GcFlags.maxHeapSize) {
129 errorBelch("maximum heap size (-M) is smaller than minimum alloc area size (-A)");
130 RtsFlags.GcFlags.minAllocAreaSize = RtsFlags.GcFlags.maxHeapSize;
133 initBlockAllocator();
135 #if defined(THREADED_RTS)
136 initMutex(&sm_mutex);
137 initMutex(&atomic_modify_mutvar_mutex);
142 /* allocate generation info array */
143 generations = (generation *)stgMallocBytes(RtsFlags.GcFlags.generations
144 * sizeof(struct generation_),
145 "initStorage: gens");
147 /* Initialise all generations */
148 for(g = 0; g < RtsFlags.GcFlags.generations; g++) {
149 gen = &generations[g];
151 gen->mut_list = allocBlock();
152 gen->collections = 0;
153 gen->failed_promotions = 0;
157 /* A couple of convenience pointers */
158 g0 = &generations[0];
159 oldest_gen = &generations[RtsFlags.GcFlags.generations-1];
161 /* Allocate step structures in each generation */
162 if (RtsFlags.GcFlags.generations > 1) {
163 /* Only for multiple-generations */
165 /* Oldest generation: one step */
166 oldest_gen->n_steps = 1;
168 stgMallocBytes(1 * sizeof(struct step_), "initStorage: last step");
170 /* set up all except the oldest generation with 2 steps */
171 for(g = 0; g < RtsFlags.GcFlags.generations-1; g++) {
172 generations[g].n_steps = RtsFlags.GcFlags.steps;
173 generations[g].steps =
174 stgMallocBytes (RtsFlags.GcFlags.steps * sizeof(struct step_),
175 "initStorage: steps");
179 /* single generation, i.e. a two-space collector */
181 g0->steps = stgMallocBytes (sizeof(struct step_), "initStorage: steps");
185 n_nurseries = n_capabilities;
186 nurseries = stgMallocBytes (n_nurseries * sizeof(struct step_),
187 "initStorage: nurseries");
190 nurseries = g0->steps; // just share nurseries[0] with g0s0
193 /* Initialise all steps */
194 for (g = 0; g < RtsFlags.GcFlags.generations; g++) {
195 for (s = 0; s < generations[g].n_steps; s++) {
196 initStep(&generations[g].steps[s], g, s);
201 for (s = 0; s < n_nurseries; s++) {
202 initStep(&nurseries[s], 0, s);
206 /* Set up the destination pointers in each younger gen. step */
207 for (g = 0; g < RtsFlags.GcFlags.generations-1; g++) {
208 for (s = 0; s < generations[g].n_steps-1; s++) {
209 generations[g].steps[s].to = &generations[g].steps[s+1];
211 generations[g].steps[s].to = &generations[g+1].steps[0];
213 oldest_gen->steps[0].to = &oldest_gen->steps[0];
216 for (s = 0; s < n_nurseries; s++) {
217 nurseries[s].to = generations[0].steps[0].to;
221 /* The oldest generation has one step. */
222 if (RtsFlags.GcFlags.compact) {
223 if (RtsFlags.GcFlags.generations == 1) {
224 errorBelch("WARNING: compaction is incompatible with -G1; disabled");
226 oldest_gen->steps[0].is_compacted = 1;
231 if (RtsFlags.GcFlags.generations == 1) {
232 errorBelch("-G1 is incompatible with -threaded");
233 stg_exit(EXIT_FAILURE);
237 /* generation 0 is special: that's the nursery */
238 generations[0].max_blocks = 0;
240 /* G0S0: the allocation area. Policy: keep the allocation area
241 * small to begin with, even if we have a large suggested heap
242 * size. Reason: we're going to do a major collection first, and we
243 * don't want it to be a big one. This vague idea is borne out by
244 * rigorous experimental evidence.
246 g0s0 = &generations[0].steps[0];
250 weak_ptr_list = NULL;
252 revertible_caf_list = NULL;
254 /* initialise the allocate() interface */
255 small_alloc_list = NULL;
257 alloc_blocks_lim = RtsFlags.GcFlags.minAllocAreaSize;
259 /* Tell GNU multi-precision pkg about our custom alloc functions */
260 mp_set_memory_functions(stgAllocForGMP, stgReallocForGMP, stgDeallocForGMP);
262 IF_DEBUG(gc, statDescribeGens());
270 stat_exit(calcAllocated());
278 for(g = 0; g < RtsFlags.GcFlags.generations; g++)
279 stgFree(generations[g].steps);
280 stgFree(generations);
282 #if defined(THREADED_RTS)
283 closeMutex(&sm_mutex);
284 closeMutex(&atomic_modify_mutvar_mutex);
288 /* -----------------------------------------------------------------------------
291 The entry code for every CAF does the following:
293 - builds a CAF_BLACKHOLE in the heap
294 - pushes an update frame pointing to the CAF_BLACKHOLE
295 - invokes UPD_CAF(), which:
296 - calls newCaf, below
297 - updates the CAF with a static indirection to the CAF_BLACKHOLE
299 Why do we build a BLACKHOLE in the heap rather than just updating
300 the thunk directly? It's so that we only need one kind of update
301 frame - otherwise we'd need a static version of the update frame too.
303 newCaf() does the following:
305 - it puts the CAF on the oldest generation's mut-once list.
306 This is so that we can treat the CAF as a root when collecting
309 For GHCI, we have additional requirements when dealing with CAFs:
311 - we must *retain* all dynamically-loaded CAFs ever entered,
312 just in case we need them again.
313 - we must be able to *revert* CAFs that have been evaluated, to
314 their pre-evaluated form.
316 To do this, we use an additional CAF list. When newCaf() is
317 called on a dynamically-loaded CAF, we add it to the CAF list
318 instead of the old-generation mutable list, and save away its
319 old info pointer (in caf->saved_info) for later reversion.
321 To revert all the CAFs, we traverse the CAF list and reset the
322 info pointer to caf->saved_info, then throw away the CAF list.
323 (see GC.c:revertCAFs()).
327 -------------------------------------------------------------------------- */
330 newCAF(StgClosure* caf)
337 // If we are in GHCi _and_ we are using dynamic libraries,
338 // then we can't redirect newCAF calls to newDynCAF (see below),
339 // so we make newCAF behave almost like newDynCAF.
340 // The dynamic libraries might be used by both the interpreted
341 // program and GHCi itself, so they must not be reverted.
342 // This also means that in GHCi with dynamic libraries, CAFs are not
343 // garbage collected. If this turns out to be a problem, we could
344 // do another hack here and do an address range test on caf to figure
345 // out whether it is from a dynamic library.
346 ((StgIndStatic *)caf)->saved_info = (StgInfoTable *)caf->header.info;
347 ((StgIndStatic *)caf)->static_link = caf_list;
352 /* Put this CAF on the mutable list for the old generation.
353 * This is a HACK - the IND_STATIC closure doesn't really have
354 * a mut_link field, but we pretend it has - in fact we re-use
355 * the STATIC_LINK field for the time being, because when we
356 * come to do a major GC we won't need the mut_link field
357 * any more and can use it as a STATIC_LINK.
359 ((StgIndStatic *)caf)->saved_info = NULL;
360 recordMutableGen(caf, oldest_gen);
366 /* If we are PAR or DIST then we never forget a CAF */
368 //debugBelch("<##> Globalising CAF %08x %s",caf,info_type(caf));
369 newGA=makeGlobal(caf,rtsTrue); /*given full weight*/
375 // An alternate version of newCaf which is used for dynamically loaded
376 // object code in GHCi. In this case we want to retain *all* CAFs in
377 // the object code, because they might be demanded at any time from an
378 // expression evaluated on the command line.
379 // Also, GHCi might want to revert CAFs, so we add these to the
380 // revertible_caf_list.
382 // The linker hackily arranges that references to newCaf from dynamic
383 // code end up pointing to newDynCAF.
385 newDynCAF(StgClosure *caf)
389 ((StgIndStatic *)caf)->saved_info = (StgInfoTable *)caf->header.info;
390 ((StgIndStatic *)caf)->static_link = revertible_caf_list;
391 revertible_caf_list = caf;
396 /* -----------------------------------------------------------------------------
398 -------------------------------------------------------------------------- */
401 allocNursery (step *stp, bdescr *tail, nat blocks)
406 // Allocate a nursery: we allocate fresh blocks one at a time and
407 // cons them on to the front of the list, not forgetting to update
408 // the back pointer on the tail of the list to point to the new block.
409 for (i=0; i < blocks; i++) {
412 processNursery() in LdvProfile.c assumes that every block group in
413 the nursery contains only a single block. So, if a block group is
414 given multiple blocks, change processNursery() accordingly.
418 // double-link the nursery: we might need to insert blocks
425 bd->free = bd->start;
433 assignNurseriesToCapabilities (void)
438 for (i = 0; i < n_nurseries; i++) {
439 capabilities[i].r.rNursery = &nurseries[i];
440 capabilities[i].r.rCurrentNursery = nurseries[i].blocks;
441 capabilities[i].r.rCurrentAlloc = NULL;
443 #else /* THREADED_RTS */
444 MainCapability.r.rNursery = &nurseries[0];
445 MainCapability.r.rCurrentNursery = nurseries[0].blocks;
446 MainCapability.r.rCurrentAlloc = NULL;
451 allocNurseries( void )
455 for (i = 0; i < n_nurseries; i++) {
456 nurseries[i].blocks =
457 allocNursery(&nurseries[i], NULL,
458 RtsFlags.GcFlags.minAllocAreaSize);
459 nurseries[i].n_blocks = RtsFlags.GcFlags.minAllocAreaSize;
460 nurseries[i].old_blocks = NULL;
461 nurseries[i].n_old_blocks = 0;
462 /* hp, hpLim, hp_bd, to_space etc. aren't used in the nursery */
464 assignNurseriesToCapabilities();
468 resetNurseries( void )
474 for (i = 0; i < n_nurseries; i++) {
476 for (bd = stp->blocks; bd; bd = bd->link) {
477 bd->free = bd->start;
478 ASSERT(bd->gen_no == 0);
479 ASSERT(bd->step == stp);
480 IF_DEBUG(sanity,memset(bd->start, 0xaa, BLOCK_SIZE));
483 assignNurseriesToCapabilities();
487 countNurseryBlocks (void)
492 for (i = 0; i < n_nurseries; i++) {
493 blocks += nurseries[i].n_blocks;
499 resizeNursery ( step *stp, nat blocks )
504 nursery_blocks = stp->n_blocks;
505 if (nursery_blocks == blocks) return;
507 if (nursery_blocks < blocks) {
508 debugTrace(DEBUG_gc, "increasing size of nursery to %d blocks",
510 stp->blocks = allocNursery(stp, stp->blocks, blocks-nursery_blocks);
515 debugTrace(DEBUG_gc, "decreasing size of nursery to %d blocks",
519 while (nursery_blocks > blocks) {
521 next_bd->u.back = NULL;
522 nursery_blocks -= bd->blocks; // might be a large block
527 // might have gone just under, by freeing a large block, so make
528 // up the difference.
529 if (nursery_blocks < blocks) {
530 stp->blocks = allocNursery(stp, stp->blocks, blocks-nursery_blocks);
534 stp->n_blocks = blocks;
535 ASSERT(countBlocks(stp->blocks) == stp->n_blocks);
539 // Resize each of the nurseries to the specified size.
542 resizeNurseriesFixed (nat blocks)
545 for (i = 0; i < n_nurseries; i++) {
546 resizeNursery(&nurseries[i], blocks);
551 // Resize the nurseries to the total specified size.
554 resizeNurseries (nat blocks)
556 // If there are multiple nurseries, then we just divide the number
557 // of available blocks between them.
558 resizeNurseriesFixed(blocks / n_nurseries);
561 /* -----------------------------------------------------------------------------
562 The allocate() interface
564 allocate(n) always succeeds, and returns a chunk of memory n words
565 long. n can be larger than the size of a block if necessary, in
566 which case a contiguous block group will be allocated.
567 -------------------------------------------------------------------------- */
577 TICK_ALLOC_HEAP_NOCTR(n);
580 /* big allocation (>LARGE_OBJECT_THRESHOLD) */
581 /* ToDo: allocate directly into generation 1 */
582 if (n >= LARGE_OBJECT_THRESHOLD/sizeof(W_)) {
583 nat req_blocks = (lnat)BLOCK_ROUND_UP(n*sizeof(W_)) / BLOCK_SIZE;
584 bd = allocGroup(req_blocks);
585 dbl_link_onto(bd, &g0s0->large_objects);
586 g0s0->n_large_blocks += req_blocks;
589 bd->flags = BF_LARGE;
590 bd->free = bd->start + n;
591 alloc_blocks += req_blocks;
595 /* small allocation (<LARGE_OBJECT_THRESHOLD) */
596 } else if (small_alloc_list == NULL || alloc_Hp + n > alloc_HpLim) {
597 if (small_alloc_list) {
598 small_alloc_list->free = alloc_Hp;
601 bd->link = small_alloc_list;
602 small_alloc_list = bd;
606 alloc_Hp = bd->start;
607 alloc_HpLim = bd->start + BLOCK_SIZE_W;
618 allocated_bytes( void )
622 allocated = alloc_blocks * BLOCK_SIZE_W - (alloc_HpLim - alloc_Hp);
623 if (pinned_object_block != NULL) {
624 allocated -= (pinned_object_block->start + BLOCK_SIZE_W) -
625 pinned_object_block->free;
632 tidyAllocateLists (void)
634 if (small_alloc_list != NULL) {
635 ASSERT(alloc_Hp >= small_alloc_list->start &&
636 alloc_Hp <= small_alloc_list->start + BLOCK_SIZE);
637 small_alloc_list->free = alloc_Hp;
641 /* -----------------------------------------------------------------------------
644 This allocates memory in the current thread - it is intended for
645 use primarily from STG-land where we have a Capability. It is
646 better than allocate() because it doesn't require taking the
647 sm_mutex lock in the common case.
649 Memory is allocated directly from the nursery if possible (but not
650 from the current nursery block, so as not to interfere with
652 -------------------------------------------------------------------------- */
655 allocateLocal (Capability *cap, nat n)
660 TICK_ALLOC_HEAP_NOCTR(n);
663 /* big allocation (>LARGE_OBJECT_THRESHOLD) */
664 /* ToDo: allocate directly into generation 1 */
665 if (n >= LARGE_OBJECT_THRESHOLD/sizeof(W_)) {
666 nat req_blocks = (lnat)BLOCK_ROUND_UP(n*sizeof(W_)) / BLOCK_SIZE;
668 bd = allocGroup(req_blocks);
669 dbl_link_onto(bd, &g0s0->large_objects);
670 g0s0->n_large_blocks += req_blocks;
673 bd->flags = BF_LARGE;
674 bd->free = bd->start + n;
675 alloc_blocks += req_blocks;
679 /* small allocation (<LARGE_OBJECT_THRESHOLD) */
682 bd = cap->r.rCurrentAlloc;
683 if (bd == NULL || bd->free + n > bd->start + BLOCK_SIZE_W) {
685 // The CurrentAlloc block is full, we need to find another
686 // one. First, we try taking the next block from the
688 bd = cap->r.rCurrentNursery->link;
690 if (bd == NULL || bd->free + n > bd->start + BLOCK_SIZE_W) {
691 // The nursery is empty, or the next block is already
692 // full: allocate a fresh block (we can't fail here).
695 cap->r.rNursery->n_blocks++;
698 bd->step = cap->r.rNursery;
701 // we have a block in the nursery: take it and put
702 // it at the *front* of the nursery list, and use it
703 // to allocate() from.
704 cap->r.rCurrentNursery->link = bd->link;
705 if (bd->link != NULL) {
706 bd->link->u.back = cap->r.rCurrentNursery;
709 dbl_link_onto(bd, &cap->r.rNursery->blocks);
710 cap->r.rCurrentAlloc = bd;
711 IF_DEBUG(sanity, checkNurserySanity(cap->r.rNursery));
719 /* ---------------------------------------------------------------------------
720 Allocate a fixed/pinned object.
722 We allocate small pinned objects into a single block, allocating a
723 new block when the current one overflows. The block is chained
724 onto the large_object_list of generation 0 step 0.
726 NOTE: The GC can't in general handle pinned objects. This
727 interface is only safe to use for ByteArrays, which have no
728 pointers and don't require scavenging. It works because the
729 block's descriptor has the BF_LARGE flag set, so the block is
730 treated as a large object and chained onto various lists, rather
731 than the individual objects being copied. However, when it comes
732 to scavenge the block, the GC will only scavenge the first object.
733 The reason is that the GC can't linearly scan a block of pinned
734 objects at the moment (doing so would require using the
735 mostly-copying techniques). But since we're restricting ourselves
736 to pinned ByteArrays, not scavenging is ok.
738 This function is called by newPinnedByteArray# which immediately
739 fills the allocated memory with a MutableByteArray#.
740 ------------------------------------------------------------------------- */
743 allocatePinned( nat n )
746 bdescr *bd = pinned_object_block;
748 // If the request is for a large object, then allocate()
749 // will give us a pinned object anyway.
750 if (n >= LARGE_OBJECT_THRESHOLD/sizeof(W_)) {
756 TICK_ALLOC_HEAP_NOCTR(n);
759 // we always return 8-byte aligned memory. bd->free must be
760 // 8-byte aligned to begin with, so we just round up n to
761 // the nearest multiple of 8 bytes.
762 if (sizeof(StgWord) == 4) {
766 // If we don't have a block of pinned objects yet, or the current
767 // one isn't large enough to hold the new object, allocate a new one.
768 if (bd == NULL || (bd->free + n) > (bd->start + BLOCK_SIZE_W)) {
769 pinned_object_block = bd = allocBlock();
770 dbl_link_onto(bd, &g0s0->large_objects);
773 bd->flags = BF_PINNED | BF_LARGE;
774 bd->free = bd->start;
784 /* -----------------------------------------------------------------------------
785 This is the write barrier for MUT_VARs, a.k.a. IORefs. A
786 MUT_VAR_CLEAN object is not on the mutable list; a MUT_VAR_DIRTY
787 is. When written to, a MUT_VAR_CLEAN turns into a MUT_VAR_DIRTY
788 and is put on the mutable list.
789 -------------------------------------------------------------------------- */
792 dirty_MUT_VAR(StgRegTable *reg, StgClosure *p)
794 Capability *cap = regTableToCapability(reg);
796 if (p->header.info == &stg_MUT_VAR_CLEAN_info) {
797 p->header.info = &stg_MUT_VAR_DIRTY_info;
798 bd = Bdescr((StgPtr)p);
799 if (bd->gen_no > 0) recordMutableCap(p,cap,bd->gen_no);
803 /* -----------------------------------------------------------------------------
804 Allocation functions for GMP.
806 These all use the allocate() interface - we can't have any garbage
807 collection going on during a gmp operation, so we use allocate()
808 which always succeeds. The gmp operations which might need to
809 allocate will ask the storage manager (via doYouWantToGC()) whether
810 a garbage collection is required, in case we get into a loop doing
811 only allocate() style allocation.
812 -------------------------------------------------------------------------- */
815 stgAllocForGMP (size_t size_in_bytes)
818 nat data_size_in_words, total_size_in_words;
820 /* round up to a whole number of words */
821 data_size_in_words = (size_in_bytes + sizeof(W_) + 1) / sizeof(W_);
822 total_size_in_words = sizeofW(StgArrWords) + data_size_in_words;
824 /* allocate and fill it in. */
825 #if defined(THREADED_RTS)
826 arr = (StgArrWords *)allocateLocal(myTask()->cap, total_size_in_words);
828 arr = (StgArrWords *)allocateLocal(&MainCapability, total_size_in_words);
830 SET_ARR_HDR(arr, &stg_ARR_WORDS_info, CCCS, data_size_in_words);
832 /* and return a ptr to the goods inside the array */
837 stgReallocForGMP (void *ptr, size_t old_size, size_t new_size)
839 void *new_stuff_ptr = stgAllocForGMP(new_size);
841 char *p = (char *) ptr;
842 char *q = (char *) new_stuff_ptr;
844 for (; i < old_size; i++, p++, q++) {
848 return(new_stuff_ptr);
852 stgDeallocForGMP (void *ptr STG_UNUSED,
853 size_t size STG_UNUSED)
855 /* easy for us: the garbage collector does the dealloc'n */
858 /* -----------------------------------------------------------------------------
860 * -------------------------------------------------------------------------- */
862 /* -----------------------------------------------------------------------------
865 * Approximate how much we've allocated: number of blocks in the
866 * nursery + blocks allocated via allocate() - unused nusery blocks.
867 * This leaves a little slop at the end of each block, and doesn't
868 * take into account large objects (ToDo).
869 * -------------------------------------------------------------------------- */
872 calcAllocated( void )
877 allocated = allocated_bytes();
878 allocated += countNurseryBlocks() * BLOCK_SIZE_W;
883 for (i = 0; i < n_nurseries; i++) {
885 for ( bd = capabilities[i].r.rCurrentNursery->link;
886 bd != NULL; bd = bd->link ) {
887 allocated -= BLOCK_SIZE_W;
889 cap = &capabilities[i];
890 if (cap->r.rCurrentNursery->free <
891 cap->r.rCurrentNursery->start + BLOCK_SIZE_W) {
892 allocated -= (cap->r.rCurrentNursery->start + BLOCK_SIZE_W)
893 - cap->r.rCurrentNursery->free;
897 bdescr *current_nursery = MainCapability.r.rCurrentNursery;
899 for ( bd = current_nursery->link; bd != NULL; bd = bd->link ) {
900 allocated -= BLOCK_SIZE_W;
902 if (current_nursery->free < current_nursery->start + BLOCK_SIZE_W) {
903 allocated -= (current_nursery->start + BLOCK_SIZE_W)
904 - current_nursery->free;
909 total_allocated += allocated;
913 /* Approximate the amount of live data in the heap. To be called just
914 * after garbage collection (see GarbageCollect()).
923 if (RtsFlags.GcFlags.generations == 1) {
924 live = (g0s0->n_blocks - 1) * BLOCK_SIZE_W +
925 ((lnat)g0s0->hp_bd->free - (lnat)g0s0->hp_bd->start) / sizeof(W_);
929 for (g = 0; g < RtsFlags.GcFlags.generations; g++) {
930 for (s = 0; s < generations[g].n_steps; s++) {
931 /* approximate amount of live data (doesn't take into account slop
932 * at end of each block).
934 if (g == 0 && s == 0) {
937 stp = &generations[g].steps[s];
938 live += (stp->n_large_blocks + stp->n_blocks - 1) * BLOCK_SIZE_W;
939 if (stp->hp_bd != NULL) {
940 live += ((lnat)stp->hp_bd->free - (lnat)stp->hp_bd->start)
943 if (stp->scavd_hp != NULL) {
944 live -= (P_)(BLOCK_ROUND_UP(stp->scavd_hp)) - stp->scavd_hp;
951 /* Approximate the number of blocks that will be needed at the next
952 * garbage collection.
954 * Assume: all data currently live will remain live. Steps that will
955 * be collected next time will therefore need twice as many blocks
956 * since all the data will be copied.
965 for (g = 0; g < RtsFlags.GcFlags.generations; g++) {
966 for (s = 0; s < generations[g].n_steps; s++) {
967 if (g == 0 && s == 0) { continue; }
968 stp = &generations[g].steps[s];
969 if (generations[g].steps[0].n_blocks +
970 generations[g].steps[0].n_large_blocks
971 > generations[g].max_blocks
972 && stp->is_compacted == 0) {
973 needed += 2 * stp->n_blocks;
975 needed += stp->n_blocks;
982 /* ----------------------------------------------------------------------------
985 Executable memory must be managed separately from non-executable
986 memory. Most OSs these days require you to jump through hoops to
987 dynamically allocate executable memory, due to various security
990 Here we provide a small memory allocator for executable memory.
991 Memory is managed with a page granularity; we allocate linearly
992 in the page, and when the page is emptied (all objects on the page
993 are free) we free the page again, not forgetting to make it
995 ------------------------------------------------------------------------- */
997 static bdescr *exec_block;
999 void *allocateExec (nat bytes)
1006 // round up to words.
1007 n = (bytes + sizeof(W_) + 1) / sizeof(W_);
1009 if (n+1 > BLOCK_SIZE_W) {
1010 barf("allocateExec: can't handle large objects");
1013 if (exec_block == NULL ||
1014 exec_block->free + n + 1 > exec_block->start + BLOCK_SIZE_W) {
1016 lnat pagesize = getPageSize();
1017 bd = allocGroup(stg_max(1, pagesize / BLOCK_SIZE));
1018 debugTrace(DEBUG_gc, "allocate exec block %p", bd->start);
1020 bd->flags = BF_EXEC;
1021 bd->link = exec_block;
1022 if (exec_block != NULL) {
1023 exec_block->u.back = bd;
1026 setExecutable(bd->start, bd->blocks * BLOCK_SIZE, rtsTrue);
1029 *(exec_block->free) = n; // store the size of this chunk
1030 exec_block->gen_no += n; // gen_no stores the number of words allocated
1031 ret = exec_block->free + 1;
1032 exec_block->free += n + 1;
1038 void freeExec (void *addr)
1040 StgPtr p = (StgPtr)addr - 1;
1041 bdescr *bd = Bdescr((StgPtr)p);
1043 if ((bd->flags & BF_EXEC) == 0) {
1044 barf("freeExec: not executable");
1047 if (*(StgPtr)p == 0) {
1048 barf("freeExec: already free?");
1053 bd->gen_no -= *(StgPtr)p;
1056 // Free the block if it is empty, but not if it is the block at
1057 // the head of the queue.
1058 if (bd->gen_no == 0 && bd != exec_block) {
1059 debugTrace(DEBUG_gc, "free exec block %p", bd->start);
1061 bd->u.back->link = bd->link;
1063 exec_block = bd->link;
1066 bd->link->u.back = bd->u.back;
1068 setExecutable(bd->start, bd->blocks * BLOCK_SIZE, rtsFalse);
1075 /* -----------------------------------------------------------------------------
1078 memInventory() checks for memory leaks by counting up all the
1079 blocks we know about and comparing that to the number of blocks
1080 allegedly floating around in the system.
1081 -------------------------------------------------------------------------- */
1086 stepBlocks (step *stp)
1091 total_blocks = stp->n_blocks;
1092 total_blocks += stp->n_old_blocks;
1093 for (bd = stp->large_objects; bd; bd = bd->link) {
1094 total_blocks += bd->blocks;
1095 /* hack for megablock groups: they have an extra block or two in
1096 the second and subsequent megablocks where the block
1097 descriptors would normally go.
1099 if (bd->blocks > BLOCKS_PER_MBLOCK) {
1100 total_blocks -= (MBLOCK_SIZE / BLOCK_SIZE - BLOCKS_PER_MBLOCK)
1101 * (bd->blocks/(MBLOCK_SIZE/BLOCK_SIZE));
1104 return total_blocks;
1113 lnat total_blocks = 0, free_blocks = 0;
1115 /* count the blocks we current have */
1117 for (g = 0; g < RtsFlags.GcFlags.generations; g++) {
1118 for (i = 0; i < n_capabilities; i++) {
1119 for (bd = capabilities[i].mut_lists[g]; bd != NULL; bd = bd->link) {
1120 total_blocks += bd->blocks;
1123 for (bd = generations[g].mut_list; bd != NULL; bd = bd->link) {
1124 total_blocks += bd->blocks;
1126 for (s = 0; s < generations[g].n_steps; s++) {
1127 if (g==0 && s==0) continue;
1128 stp = &generations[g].steps[s];
1129 total_blocks += stepBlocks(stp);
1133 for (i = 0; i < n_nurseries; i++) {
1134 total_blocks += stepBlocks(&nurseries[i]);
1137 // We put pinned object blocks in g0s0, so better count blocks there too.
1138 total_blocks += stepBlocks(g0s0);
1141 /* any blocks held by allocate() */
1142 for (bd = small_alloc_list; bd; bd = bd->link) {
1143 total_blocks += bd->blocks;
1147 if (RtsFlags.ProfFlags.doHeapProfile == HEAP_BY_RETAINER) {
1148 total_blocks += retainerStackBlocks();
1152 // count the blocks allocated by the arena allocator
1153 total_blocks += arenaBlocks();
1155 // count the blocks containing executable memory
1156 for (bd = exec_block; bd; bd = bd->link) {
1157 total_blocks += bd->blocks;
1160 /* count the blocks on the free list */
1161 free_blocks = countFreeList();
1163 if (total_blocks + free_blocks != mblocks_allocated *
1164 BLOCKS_PER_MBLOCK) {
1165 debugBelch("Blocks: %ld live + %ld free = %ld total (%ld around)\n",
1166 total_blocks, free_blocks, total_blocks + free_blocks,
1167 mblocks_allocated * BLOCKS_PER_MBLOCK);
1170 ASSERT(total_blocks + free_blocks == mblocks_allocated * BLOCKS_PER_MBLOCK);
1175 countBlocks(bdescr *bd)
1178 for (n=0; bd != NULL; bd=bd->link) {
1184 /* Full heap sanity check. */
1190 if (RtsFlags.GcFlags.generations == 1) {
1191 checkHeap(g0s0->blocks);
1192 checkChain(g0s0->large_objects);
1195 for (g = 0; g < RtsFlags.GcFlags.generations; g++) {
1196 for (s = 0; s < generations[g].n_steps; s++) {
1197 if (g == 0 && s == 0) { continue; }
1198 ASSERT(countBlocks(generations[g].steps[s].blocks)
1199 == generations[g].steps[s].n_blocks);
1200 ASSERT(countBlocks(generations[g].steps[s].large_objects)
1201 == generations[g].steps[s].n_large_blocks);
1202 checkHeap(generations[g].steps[s].blocks);
1203 checkChain(generations[g].steps[s].large_objects);
1205 checkMutableList(generations[g].mut_list, g);
1210 for (s = 0; s < n_nurseries; s++) {
1211 ASSERT(countBlocks(nurseries[s].blocks)
1212 == nurseries[s].n_blocks);
1213 ASSERT(countBlocks(nurseries[s].large_objects)
1214 == nurseries[s].n_large_blocks);
1217 checkFreeListSanity();
1221 /* Nursery sanity check */
1223 checkNurserySanity( step *stp )
1229 for (bd = stp->blocks; bd != NULL; bd = bd->link) {
1230 ASSERT(bd->u.back == prev);
1232 blocks += bd->blocks;
1234 ASSERT(blocks == stp->n_blocks);
1237 // handy function for use in gdb, because Bdescr() is inlined.
1238 extern bdescr *_bdescr( StgPtr p );