1 /* -----------------------------------------------------------------------------
2 *
3 * (c) The GHC Team 2001-2008
4 *
5 * Compacting garbage collector
6 *
7 * Documentation on the architecture of the Garbage Collector can be
8 * found in the online commentary:
9 *
10 * https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/gc
11 *
12 * ---------------------------------------------------------------------------*/
13
14 #include "PosixSource.h"
15 #include "Rts.h"
16
17 #include "GCThread.h"
18 #include "Storage.h"
19 #include "RtsUtils.h"
20 #include "BlockAlloc.h"
21 #include "GC.h"
22 #include "Compact.h"
23 #include "Schedule.h"
24 #include "Apply.h"
25 #include "Trace.h"
26 #include "Weak.h"
27 #include "MarkWeak.h"
28 #include "StablePtr.h"
29 #include "StableName.h"
30
31 // Turn off inlining when debugging - it obfuscates things
32 #if defined(DEBUG)
33 # undef STATIC_INLINE
34 # define STATIC_INLINE static
35 #endif
36
37 /* ----------------------------------------------------------------------------
38 Threading / unthreading pointers.
39
40 The basic idea here is to chain together all the fields pointing at a
41 particular object, with the root of the chain in the object's info table
42 field. The original contents of the info pointer goes at the end of the
43 chain.
44
45 Adding a new field to the chain is a matter of swapping the contents of the
46 field with the contents of the object's info table field:
47
48 *field, **field = **field, field
49
50 To unthread the chain, we walk down it updating all the fields on the chain
51 with the new location of the object. We stop when we reach the info pointer
52 at the end.
53
54 The main difficulty here is that not all pointers to the same object are
55 tagged: pointers from roots (e.g. mut_lists) are not tagged, but pointers
56 from mutators are. So when unthreading a chain we need to distinguish a field
57 that had a tagged pointer from a field that had an untagged pointer.
58
59 Our solution is as follows: when chaining a field, if the field is NOT
60 tagged then we tag the pointer to the field with 1. I.e.
61
62 *field, **field = **field, field + 1
63
64 If the field is tagged then we tag to the pointer to it with 2.
65
66 When unchaining we look at the tag in the pointer to the field, if it's 1
67 then we write an untagged pointer to "free" to it, otherwise we tag the
68 pointer.
69 ------------------------------------------------------------------------- */
70
71 STATIC_INLINE W_
UNTAG_PTR(W_ p)72 UNTAG_PTR(W_ p)
73 {
74 return p & ~TAG_MASK;
75 }
76
77 STATIC_INLINE W_
GET_PTR_TAG(W_ p)78 GET_PTR_TAG(W_ p)
79 {
80 return p & TAG_MASK;
81 }
82
83 static W_
get_iptr_tag(StgInfoTable * iptr)84 get_iptr_tag(StgInfoTable *iptr)
85 {
86 const StgInfoTable *info = INFO_PTR_TO_STRUCT(iptr);
87 switch (info->type) {
88 case CONSTR:
89 case CONSTR_1_0:
90 case CONSTR_0_1:
91 case CONSTR_2_0:
92 case CONSTR_1_1:
93 case CONSTR_0_2:
94 case CONSTR_NOCAF:
95 {
96 W_ con_tag = info->srt + 1;
97 if (con_tag > TAG_MASK) {
98 return TAG_MASK;
99 } else {
100 return con_tag;
101 }
102 }
103
104 case FUN:
105 case FUN_1_0:
106 case FUN_0_1:
107 case FUN_2_0:
108 case FUN_1_1:
109 case FUN_0_2:
110 case FUN_STATIC:
111 {
112 const StgFunInfoTable *fun_itbl = FUN_INFO_PTR_TO_STRUCT(iptr);
113 W_ arity = fun_itbl->f.arity;
114 if (arity <= TAG_MASK) {
115 return arity;
116 } else {
117 return 0;
118 }
119 }
120
121 default:
122 return 0;
123 }
124 }
125
126 STATIC_INLINE void
thread(StgClosure ** p)127 thread (StgClosure **p)
128 {
129 StgClosure *q0 = *p;
130 bool q0_tagged = GET_CLOSURE_TAG(q0) != 0;
131 P_ q = (P_)UNTAG_CLOSURE(q0);
132
133 // It doesn't look like a closure at the moment, because the info
134 // ptr is possibly threaded:
135 // ASSERT(LOOKS_LIKE_CLOSURE_PTR(q));
136
137 if (HEAP_ALLOCED(q)) {
138 bdescr *bd = Bdescr(q);
139
140 if (bd->flags & BF_MARKED)
141 {
142 W_ iptr = *q;
143 *p = (StgClosure *)iptr;
144 *q = (W_)p + 1 + (q0_tagged ? 1 : 0);
145 }
146 }
147 }
148
149 static void
thread_root(void * user STG_UNUSED,StgClosure ** p)150 thread_root (void *user STG_UNUSED, StgClosure **p)
151 {
152 thread(p);
153 }
154
155 // This version of thread() takes a (void *), used to circumvent
156 // warnings from gcc about pointer punning and strict aliasing.
thread_(void * p)157 STATIC_INLINE void thread_ (void *p) { thread((StgClosure **)p); }
158
159 STATIC_INLINE void
unthread(const P_ p,W_ free,W_ tag)160 unthread( const P_ p, W_ free, W_ tag )
161 {
162 W_ q = *p;
163 loop:
164 switch (GET_PTR_TAG(q))
165 {
166 case 0:
167 // nothing to do; the chain is length zero
168 *p = q;
169 return;
170 case 1:
171 {
172 P_ q0 = (P_)(q-1);
173 W_ r = *q0;
174 *q0 = free;
175 q = r;
176 goto loop;
177 }
178 case 2:
179 {
180 P_ q0 = (P_)(q-2);
181 W_ r = *q0;
182 *q0 = free + tag;
183 q = r;
184 goto loop;
185 }
186 default:
187 barf("unthread");
188 }
189 }
190
191 // Traverse a threaded chain and pull out the info pointer at the end.
192 // The info pointer is also tagged with the appropriate pointer tag
193 // for this closure, which should be attached to the pointer
194 // subsequently passed to unthread().
195 STATIC_INLINE StgInfoTable*
get_threaded_info(P_ p)196 get_threaded_info( P_ p )
197 {
198 W_ q = (W_)GET_INFO(UNTAG_CLOSURE((StgClosure *)p));
199
200 loop:
201 switch (GET_PTR_TAG(q))
202 {
203 case 0:
204 ASSERT(LOOKS_LIKE_INFO_PTR(q));
205 return (StgInfoTable*)q;
206 case 1:
207 case 2:
208 {
209 q = *(P_)(UNTAG_PTR(q));
210 goto loop;
211 }
212 default:
213 barf("get_threaded_info");
214 }
215 }
216
217 // A word-aligned memmove will be faster for small objects than libc's or gcc's.
218 // Remember, the two regions *might* overlap, but: to <= from.
219 STATIC_INLINE void
move(P_ to,P_ from,W_ size)220 move(P_ to, P_ from, W_ size)
221 {
222 for(; size > 0; --size) {
223 *to++ = *from++;
224 }
225 }
226
227 static void
thread_static(StgClosure * p)228 thread_static( StgClosure* p )
229 {
230 // keep going until we've threaded all the objects on the linked
231 // list...
232 while (p != END_OF_STATIC_OBJECT_LIST) {
233 p = UNTAG_STATIC_LIST_PTR(p);
234 const StgInfoTable *info = get_itbl(p);
235 switch (info->type) {
236
237 case IND_STATIC:
238 thread(&((StgInd *)p)->indirectee);
239 p = *IND_STATIC_LINK(p);
240 continue;
241
242 case THUNK_STATIC:
243 p = *THUNK_STATIC_LINK(p);
244 continue;
245 case FUN_STATIC:
246 p = *STATIC_LINK(info,p);
247 continue;
248 case CONSTR:
249 case CONSTR_NOCAF:
250 case CONSTR_1_0:
251 case CONSTR_0_1:
252 case CONSTR_2_0:
253 case CONSTR_1_1:
254 case CONSTR_0_2:
255 p = *STATIC_LINK(info,p);
256 continue;
257
258 default:
259 barf("thread_static: strange closure %d", (int)(info->type));
260 }
261
262 }
263 }
264
265 STATIC_INLINE void
thread_large_bitmap(P_ p,StgLargeBitmap * large_bitmap,W_ size)266 thread_large_bitmap( P_ p, StgLargeBitmap *large_bitmap, W_ size )
267 {
268 W_ b = 0;
269 W_ bitmap = large_bitmap->bitmap[b];
270 for (W_ i = 0; i < size; ) {
271 if ((bitmap & 1) == 0) {
272 thread((StgClosure **)p);
273 }
274 i++;
275 p++;
276 if (i % BITS_IN(W_) == 0) {
277 b++;
278 bitmap = large_bitmap->bitmap[b];
279 } else {
280 bitmap = bitmap >> 1;
281 }
282 }
283 }
284
285 STATIC_INLINE P_
thread_small_bitmap(P_ p,W_ size,W_ bitmap)286 thread_small_bitmap (P_ p, W_ size, W_ bitmap)
287 {
288 while (size > 0) {
289 if ((bitmap & 1) == 0) {
290 thread((StgClosure **)p);
291 }
292 p++;
293 bitmap = bitmap >> 1;
294 size--;
295 }
296 return p;
297 }
298
299 STATIC_INLINE P_
thread_arg_block(StgFunInfoTable * fun_info,StgClosure ** args)300 thread_arg_block (StgFunInfoTable *fun_info, StgClosure **args)
301 {
302 W_ bitmap;
303 W_ size;
304
305 P_ p = (P_)args;
306 switch (fun_info->f.fun_type) {
307 case ARG_GEN:
308 bitmap = BITMAP_BITS(fun_info->f.b.bitmap);
309 size = BITMAP_SIZE(fun_info->f.b.bitmap);
310 goto small_bitmap;
311 case ARG_GEN_BIG:
312 size = GET_FUN_LARGE_BITMAP(fun_info)->size;
313 thread_large_bitmap(p, GET_FUN_LARGE_BITMAP(fun_info), size);
314 p += size;
315 break;
316 default:
317 bitmap = BITMAP_BITS(stg_arg_bitmaps[fun_info->f.fun_type]);
318 size = BITMAP_SIZE(stg_arg_bitmaps[fun_info->f.fun_type]);
319 small_bitmap:
320 p = thread_small_bitmap(p, size, bitmap);
321 break;
322 }
323 return p;
324 }
325
326 static void
thread_stack(P_ p,P_ stack_end)327 thread_stack(P_ p, P_ stack_end)
328 {
329 // highly similar to scavenge_stack, but we do pointer threading here.
330
331 while (p < stack_end) {
332
333 // *p must be the info pointer of an activation
334 // record. All activation records have 'bitmap' style layout
335 // info.
336 //
337 const StgRetInfoTable *info = get_ret_itbl((StgClosure *)p);
338
339 switch (info->i.type) {
340
341 // small bitmap (<= 32 entries, or 64 on a 64-bit machine)
342 case CATCH_RETRY_FRAME:
343 case CATCH_STM_FRAME:
344 case ATOMICALLY_FRAME:
345 case UPDATE_FRAME:
346 case UNDERFLOW_FRAME:
347 case STOP_FRAME:
348 case CATCH_FRAME:
349 case RET_SMALL:
350 {
351 W_ bitmap = BITMAP_BITS(info->i.layout.bitmap);
352 W_ size = BITMAP_SIZE(info->i.layout.bitmap);
353 p++;
354 // NOTE: the payload starts immediately after the info-ptr, we
355 // don't have an StgHeader in the same sense as a heap closure.
356 p = thread_small_bitmap(p, size, bitmap);
357 continue;
358 }
359
360 case RET_BCO: {
361 p++;
362 StgBCO *bco = (StgBCO *)*p;
363 thread((StgClosure **)p);
364 p++;
365 W_ size = BCO_BITMAP_SIZE(bco);
366 thread_large_bitmap(p, BCO_BITMAP(bco), size);
367 p += size;
368 continue;
369 }
370
371 // large bitmap (> 32 entries, or 64 on a 64-bit machine)
372 case RET_BIG:
373 p++;
374 W_ size = GET_LARGE_BITMAP(&info->i)->size;
375 thread_large_bitmap(p, GET_LARGE_BITMAP(&info->i), size);
376 p += size;
377 continue;
378
379 case RET_FUN:
380 {
381 StgRetFun *ret_fun = (StgRetFun *)p;
382 StgFunInfoTable *fun_info =
383 FUN_INFO_PTR_TO_STRUCT(get_threaded_info((P_)ret_fun->fun));
384 // *before* threading it!
385 thread(&ret_fun->fun);
386 p = thread_arg_block(fun_info, ret_fun->payload);
387 continue;
388 }
389
390 default:
391 barf("thread_stack: weird activation record found on stack: %d",
392 (int)(info->i.type));
393 }
394 }
395 }
396
397 STATIC_INLINE P_
thread_PAP_payload(StgClosure * fun,StgClosure ** payload,W_ size)398 thread_PAP_payload (StgClosure *fun, StgClosure **payload, W_ size)
399 {
400 StgFunInfoTable *fun_info =
401 FUN_INFO_PTR_TO_STRUCT(get_threaded_info((P_)fun));
402 ASSERT(fun_info->i.type != PAP);
403
404 P_ p = (P_)payload;
405
406 W_ bitmap;
407 switch (fun_info->f.fun_type) {
408 case ARG_GEN:
409 bitmap = BITMAP_BITS(fun_info->f.b.bitmap);
410 goto small_bitmap;
411 case ARG_GEN_BIG:
412 thread_large_bitmap(p, GET_FUN_LARGE_BITMAP(fun_info), size);
413 p += size;
414 break;
415 case ARG_BCO:
416 thread_large_bitmap((P_)payload, BCO_BITMAP(fun), size);
417 p += size;
418 break;
419 default:
420 bitmap = BITMAP_BITS(stg_arg_bitmaps[fun_info->f.fun_type]);
421 small_bitmap:
422 p = thread_small_bitmap(p, size, bitmap);
423 break;
424 }
425
426 return p;
427 }
428
429 STATIC_INLINE P_
thread_PAP(StgPAP * pap)430 thread_PAP (StgPAP *pap)
431 {
432 P_ p = thread_PAP_payload(pap->fun, pap->payload, pap->n_args);
433 thread(&pap->fun);
434 return p;
435 }
436
437 STATIC_INLINE P_
thread_AP(StgAP * ap)438 thread_AP (StgAP *ap)
439 {
440 P_ p = thread_PAP_payload(ap->fun, ap->payload, ap->n_args);
441 thread(&ap->fun);
442 return p;
443 }
444
445 STATIC_INLINE P_
thread_AP_STACK(StgAP_STACK * ap)446 thread_AP_STACK (StgAP_STACK *ap)
447 {
448 thread(&ap->fun);
449 thread_stack((P_)ap->payload, (P_)ap->payload + ap->size);
450 return (P_)ap + sizeofW(StgAP_STACK) + ap->size;
451 }
452
453 static P_
thread_TSO(StgTSO * tso)454 thread_TSO (StgTSO *tso)
455 {
456 thread_(&tso->_link);
457 thread_(&tso->global_link);
458
459 if ( tso->why_blocked == BlockedOnMVar
460 || tso->why_blocked == BlockedOnMVarRead
461 || tso->why_blocked == BlockedOnBlackHole
462 || tso->why_blocked == BlockedOnMsgThrowTo
463 || tso->why_blocked == NotBlocked
464 ) {
465 thread_(&tso->block_info.closure);
466 }
467 thread_(&tso->blocked_exceptions);
468 thread_(&tso->bq);
469
470 thread_(&tso->trec);
471
472 thread_(&tso->stackobj);
473 return (P_)tso + sizeofW(StgTSO);
474 }
475
476
477 static void
update_fwd_large(bdescr * bd)478 update_fwd_large( bdescr *bd )
479 {
480 for (; bd != NULL; bd = bd->link) {
481
482 // nothing to do in a pinned block; it might not even have an object
483 // at the beginning.
484 if (bd->flags & BF_PINNED) continue;
485
486 P_ p = bd->start;
487 const StgInfoTable *info = get_itbl((StgClosure *)p);
488
489 switch (info->type) {
490
491 case ARR_WORDS:
492 case COMPACT_NFDATA:
493 // nothing to follow
494 continue;
495
496 case MUT_ARR_PTRS_CLEAN:
497 case MUT_ARR_PTRS_DIRTY:
498 case MUT_ARR_PTRS_FROZEN_CLEAN:
499 case MUT_ARR_PTRS_FROZEN_DIRTY:
500 // follow everything
501 {
502 StgMutArrPtrs *a;
503
504 a = (StgMutArrPtrs*)p;
505 for (p = (P_)a->payload; p < (P_)&a->payload[a->ptrs]; p++) {
506 thread((StgClosure **)p);
507 }
508 continue;
509 }
510
511 case SMALL_MUT_ARR_PTRS_CLEAN:
512 case SMALL_MUT_ARR_PTRS_DIRTY:
513 case SMALL_MUT_ARR_PTRS_FROZEN_CLEAN:
514 case SMALL_MUT_ARR_PTRS_FROZEN_DIRTY:
515 // follow everything
516 {
517 StgSmallMutArrPtrs *a = (StgSmallMutArrPtrs*)p;
518 for (p = (P_)a->payload; p < (P_)&a->payload[a->ptrs]; p++) {
519 thread((StgClosure **)p);
520 }
521 continue;
522 }
523
524 case STACK:
525 {
526 StgStack *stack = (StgStack*)p;
527 thread_stack(stack->sp, stack->stack + stack->stack_size);
528 continue;
529 }
530
531 case AP_STACK:
532 thread_AP_STACK((StgAP_STACK *)p);
533 continue;
534
535 case PAP:
536 thread_PAP((StgPAP *)p);
537 continue;
538
539 case TREC_CHUNK:
540 {
541 StgTRecChunk *tc = (StgTRecChunk *)p;
542 TRecEntry *e = &(tc -> entries[0]);
543 thread_(&tc->prev_chunk);
544 for (W_ i = 0; i < tc -> next_entry_idx; i ++, e++ ) {
545 thread_(&e->tvar);
546 thread(&e->expected_value);
547 thread(&e->new_value);
548 }
549 continue;
550 }
551
552 default:
553 barf("update_fwd_large: unknown/strange object %d", (int)(info->type));
554 }
555 }
556 }
557
558 // ToDo: too big to inline
559 static /* STATIC_INLINE */ P_
thread_obj(const StgInfoTable * info,P_ p)560 thread_obj (const StgInfoTable *info, P_ p)
561 {
562 switch (info->type) {
563 case THUNK_0_1:
564 return p + sizeofW(StgThunk) + 1;
565
566 case FUN_0_1:
567 case CONSTR_0_1:
568 return p + sizeofW(StgHeader) + 1;
569
570 case FUN_1_0:
571 case CONSTR_1_0:
572 thread(&((StgClosure *)p)->payload[0]);
573 return p + sizeofW(StgHeader) + 1;
574
575 case THUNK_1_0:
576 thread(&((StgThunk *)p)->payload[0]);
577 return p + sizeofW(StgThunk) + 1;
578
579 case THUNK_0_2:
580 return p + sizeofW(StgThunk) + 2;
581
582 case FUN_0_2:
583 case CONSTR_0_2:
584 return p + sizeofW(StgHeader) + 2;
585
586 case THUNK_1_1:
587 thread(&((StgThunk *)p)->payload[0]);
588 return p + sizeofW(StgThunk) + 2;
589
590 case FUN_1_1:
591 case CONSTR_1_1:
592 thread(&((StgClosure *)p)->payload[0]);
593 return p + sizeofW(StgHeader) + 2;
594
595 case THUNK_2_0:
596 thread(&((StgThunk *)p)->payload[0]);
597 thread(&((StgThunk *)p)->payload[1]);
598 return p + sizeofW(StgThunk) + 2;
599
600 case FUN_2_0:
601 case CONSTR_2_0:
602 thread(&((StgClosure *)p)->payload[0]);
603 thread(&((StgClosure *)p)->payload[1]);
604 return p + sizeofW(StgHeader) + 2;
605
606 case BCO: {
607 StgBCO *bco = (StgBCO *)p;
608 thread_(&bco->instrs);
609 thread_(&bco->literals);
610 thread_(&bco->ptrs);
611 return p + bco_sizeW(bco);
612 }
613
614 case THUNK:
615 {
616 P_ end = (P_)((StgThunk *)p)->payload + info->layout.payload.ptrs;
617 for (p = (P_)((StgThunk *)p)->payload; p < end; p++) {
618 thread((StgClosure **)p);
619 }
620 return p + info->layout.payload.nptrs;
621 }
622
623 case FUN:
624 case CONSTR:
625 case CONSTR_NOCAF:
626 case PRIM:
627 case MUT_PRIM:
628 case MUT_VAR_CLEAN:
629 case MUT_VAR_DIRTY:
630 case TVAR:
631 case BLACKHOLE:
632 case BLOCKING_QUEUE:
633 {
634 P_ end = (P_)((StgClosure *)p)->payload + info->layout.payload.ptrs;
635 for (p = (P_)((StgClosure *)p)->payload; p < end; p++) {
636 thread((StgClosure **)p);
637 }
638 return p + info->layout.payload.nptrs;
639 }
640
641 case WEAK:
642 {
643 StgWeak *w = (StgWeak *)p;
644 thread(&w->cfinalizers);
645 thread(&w->key);
646 thread(&w->value);
647 thread(&w->finalizer);
648 if (w->link != NULL) {
649 thread_(&w->link);
650 }
651 return p + sizeofW(StgWeak);
652 }
653
654 case MVAR_CLEAN:
655 case MVAR_DIRTY:
656 {
657 StgMVar *mvar = (StgMVar *)p;
658 thread_(&mvar->head);
659 thread_(&mvar->tail);
660 thread(&mvar->value);
661 return p + sizeofW(StgMVar);
662 }
663
664 case IND:
665 thread(&((StgInd *)p)->indirectee);
666 return p + sizeofW(StgInd);
667
668 case THUNK_SELECTOR:
669 {
670 StgSelector *s = (StgSelector *)p;
671 thread(&s->selectee);
672 return p + THUNK_SELECTOR_sizeW();
673 }
674
675 case AP_STACK:
676 return thread_AP_STACK((StgAP_STACK *)p);
677
678 case PAP:
679 return thread_PAP((StgPAP *)p);
680
681 case AP:
682 return thread_AP((StgAP *)p);
683
684 case ARR_WORDS:
685 return p + arr_words_sizeW((StgArrBytes *)p);
686
687 case MUT_ARR_PTRS_CLEAN:
688 case MUT_ARR_PTRS_DIRTY:
689 case MUT_ARR_PTRS_FROZEN_CLEAN:
690 case MUT_ARR_PTRS_FROZEN_DIRTY:
691 // follow everything
692 {
693 StgMutArrPtrs *a = (StgMutArrPtrs *)p;
694 for (p = (P_)a->payload; p < (P_)&a->payload[a->ptrs]; p++) {
695 thread((StgClosure **)p);
696 }
697
698 return (P_)a + mut_arr_ptrs_sizeW(a);
699 }
700
701 case SMALL_MUT_ARR_PTRS_CLEAN:
702 case SMALL_MUT_ARR_PTRS_DIRTY:
703 case SMALL_MUT_ARR_PTRS_FROZEN_CLEAN:
704 case SMALL_MUT_ARR_PTRS_FROZEN_DIRTY:
705 // follow everything
706 {
707 StgSmallMutArrPtrs *a = (StgSmallMutArrPtrs *)p;
708 for (p = (P_)a->payload; p < (P_)&a->payload[a->ptrs]; p++) {
709 thread((StgClosure **)p);
710 }
711
712 return (P_)a + small_mut_arr_ptrs_sizeW(a);
713 }
714
715 case TSO:
716 return thread_TSO((StgTSO *)p);
717
718 case STACK:
719 {
720 StgStack *stack = (StgStack*)p;
721 thread_stack(stack->sp, stack->stack + stack->stack_size);
722 return p + stack_sizeW(stack);
723 }
724
725 case TREC_CHUNK:
726 {
727 StgTRecChunk *tc = (StgTRecChunk *)p;
728 TRecEntry *e = &(tc -> entries[0]);
729 thread_(&tc->prev_chunk);
730 for (W_ i = 0; i < tc -> next_entry_idx; i ++, e++ ) {
731 thread_(&e->tvar);
732 thread(&e->expected_value);
733 thread(&e->new_value);
734 }
735 return p + sizeofW(StgTRecChunk);
736 }
737
738 default:
739 barf("update_fwd: unknown/strange object %d", (int)(info->type));
740 return NULL;
741 }
742 }
743
744 static void
update_fwd(bdescr * blocks)745 update_fwd( bdescr *blocks )
746 {
747 bdescr *bd = blocks;
748
749 // cycle through all the blocks in the step
750 for (; bd != NULL; bd = bd->link) {
751 P_ p = bd->start;
752
753 // linearly scan the objects in this block
754 while (p < bd->free) {
755 ASSERT(LOOKS_LIKE_CLOSURE_PTR(p));
756 const StgInfoTable *info = get_itbl((StgClosure *)p);
757 p = thread_obj(info, p);
758 }
759 }
760 }
761
762 static void
update_fwd_compact(bdescr * blocks)763 update_fwd_compact( bdescr *blocks )
764 {
765 bdescr *bd = blocks;
766 bdescr *free_bd = blocks;
767 P_ free = free_bd->start;
768
769 // cycle through all the blocks in the step
770 for (; bd != NULL; bd = bd->link) {
771 P_ p = bd->start;
772
773 while (p < bd->free ) {
774
775 while ( p < bd->free && !is_marked(p,bd) ) {
776 p++;
777 }
778 if (p >= bd->free) {
779 break;
780 }
781
782 // Problem: we need to know the destination for this cell
783 // in order to unthread its info pointer. But we can't
784 // know the destination without the size, because we may
785 // spill into the next block. So we have to run down the
786 // threaded list and get the info ptr first.
787 //
788 // ToDo: one possible avenue of attack is to use the fact
789 // that if (p&BLOCK_MASK) >= (free&BLOCK_MASK), then we
790 // definitely have enough room. Also see bug #1147.
791 StgInfoTable *iptr = get_threaded_info(p);
792 StgInfoTable *info = INFO_PTR_TO_STRUCT(iptr);
793
794 P_ q = p;
795
796 p = thread_obj(info, p);
797
798 W_ size = p - q;
799 if (free + size > free_bd->start + BLOCK_SIZE_W) {
800 // set the next bit in the bitmap to indicate that this object
801 // needs to be pushed into the next block. This saves us having
802 // to run down the threaded info pointer list twice during the
803 // next pass. See Note [Mark bits in mark-compact collector] in
804 // Compact.h.
805 mark(q+1,bd);
806 free_bd = free_bd->link;
807 free = free_bd->start;
808 } else {
809 ASSERT(!is_marked(q+1,bd));
810 }
811
812 StgWord iptr_tag = get_iptr_tag(iptr);
813 unthread(q, (W_)free, iptr_tag);
814 free += size;
815 }
816 }
817 }
818
819 static W_
update_bkwd_compact(generation * gen)820 update_bkwd_compact( generation *gen )
821 {
822 bdescr *bd, *free_bd;
823 bd = free_bd = gen->old_blocks;
824
825 P_ free = free_bd->start;
826 W_ free_blocks = 1;
827
828 // cycle through all the blocks in the step
829 for (; bd != NULL; bd = bd->link) {
830 P_ p = bd->start;
831
832 while (p < bd->free ) {
833
834 while ( p < bd->free && !is_marked(p,bd) ) {
835 p++;
836 }
837 if (p >= bd->free) {
838 break;
839 }
840
841 if (is_marked(p+1,bd)) {
842 // don't forget to update the free ptr in the block desc.
843 free_bd->free = free;
844 free_bd = free_bd->link;
845 free = free_bd->start;
846 free_blocks++;
847 }
848
849 StgInfoTable *iptr = get_threaded_info(p);
850 StgWord iptr_tag = get_iptr_tag(iptr);
851 unthread(p, (W_)free, iptr_tag);
852 ASSERT(LOOKS_LIKE_INFO_PTR((W_)((StgClosure *)p)->header.info));
853 const StgInfoTable *info = get_itbl((StgClosure *)p);
854 W_ size = closure_sizeW_((StgClosure *)p,info);
855
856 if (free != p) {
857 move(free,p,size);
858 }
859
860 // relocate TSOs
861 if (info->type == STACK) {
862 move_STACK((StgStack *)p, (StgStack *)free);
863 }
864
865 free += size;
866 p += size;
867 }
868 }
869
870 // free the remaining blocks and count what's left.
871 free_bd->free = free;
872 if (free_bd->link != NULL) {
873 freeChain(free_bd->link);
874 free_bd->link = NULL;
875 }
876
877 return free_blocks;
878 }
879
880 void
compact(StgClosure * static_objects,StgWeak ** dead_weak_ptr_list,StgTSO ** resurrected_threads)881 compact(StgClosure *static_objects,
882 StgWeak **dead_weak_ptr_list,
883 StgTSO **resurrected_threads)
884 {
885 // 1. thread the roots
886 markCapabilities((evac_fn)thread_root, NULL);
887
888 markScheduler((evac_fn)thread_root, NULL);
889
890 // the weak pointer lists...
891 for (W_ g = 0; g < RtsFlags.GcFlags.generations; g++) {
892 if (generations[g].weak_ptr_list != NULL) {
893 thread((void *)&generations[g].weak_ptr_list);
894 }
895 }
896
897 if (dead_weak_ptr_list != NULL) {
898 thread((void *)dead_weak_ptr_list); // tmp
899 }
900
901 // mutable lists
902 for (W_ g = 1; g < RtsFlags.GcFlags.generations; g++) {
903 for (W_ n = 0; n < n_capabilities; n++) {
904 for (bdescr *bd = capabilities[n]->mut_lists[g];
905 bd != NULL; bd = bd->link) {
906 for (P_ p = bd->start; p < bd->free; p++) {
907 thread((StgClosure **)p);
908 }
909 }
910 }
911 }
912
913 // the global thread list
914 for (W_ g = 0; g < RtsFlags.GcFlags.generations; g++) {
915 thread((void *)&generations[g].threads);
916 }
917
918 // any threads resurrected during this GC
919 thread((void *)resurrected_threads);
920
921 // the task list
922 for (Task *task = all_tasks; task != NULL; task = task->all_next) {
923 for (InCall *incall = task->incall; incall != NULL;
924 incall = incall->prev_stack) {
925 if (incall->tso) {
926 thread_(&incall->tso);
927 }
928 }
929 }
930
931 // the static objects
932 thread_static(static_objects /* ToDo: ok? */);
933
934 // the stable pointer table
935 threadStablePtrTable((evac_fn)thread_root, NULL);
936
937 // the stable name table
938 threadStableNameTable((evac_fn)thread_root, NULL);
939
940 // the CAF list (used by GHCi)
941 markCAFs((evac_fn)thread_root, NULL);
942
943 // 2. update forward ptrs
944 for (W_ g = 0; g < RtsFlags.GcFlags.generations; g++) {
945 generation *gen = &generations[g];
946 debugTrace(DEBUG_gc, "update_fwd: %d", g);
947
948 update_fwd(gen->blocks);
949 for (W_ n = 0; n < n_capabilities; n++) {
950 update_fwd(gc_threads[n]->gens[g].todo_bd);
951 update_fwd(gc_threads[n]->gens[g].part_list);
952 }
953 update_fwd_large(gen->scavenged_large_objects);
954 if (g == RtsFlags.GcFlags.generations-1 && gen->old_blocks != NULL) {
955 debugTrace(DEBUG_gc, "update_fwd: %d (compact)", g);
956 update_fwd_compact(gen->old_blocks);
957 }
958 }
959
960 // 3. update backward ptrs
961 generation *gen = oldest_gen;
962 if (gen->old_blocks != NULL) {
963 W_ blocks = update_bkwd_compact(gen);
964 debugTrace(DEBUG_gc,
965 "update_bkwd: %d (compact, old: %d blocks, now %d blocks)",
966 gen->no, gen->n_old_blocks, blocks);
967 gen->n_old_blocks = blocks;
968 }
969 }
970