Skip to content

Commit

Permalink
Merge pull request ocaml#13299 from stedolan/remove-memprof-global-param
Browse files Browse the repository at this point in the history
Simplify memprof internals by removing "global" param
  • Loading branch information
gasche authored Jul 24, 2024
2 parents 7c79323 + b45a0b8 commit 3941ce0
Show file tree
Hide file tree
Showing 5 changed files with 39 additions and 46 deletions.
24 changes: 6 additions & 18 deletions runtime/caml/memprof.h
Original file line number Diff line number Diff line change
Expand Up @@ -64,35 +64,23 @@ extern void caml_memprof_update_suspended(_Bool);
* point to minor heaps (the `SCANNING_ONLY_YOUNG_VALUES` flag).
*
* If `weak` is false then only scan strong roots. If `weak`
* is true then also scan weak roots.
*
* If `global` is false then only scan roots for `state`. If `global`
* is true then also scan roots shared between all domains. */
* is true then also scan weak roots. */

extern void caml_memprof_scan_roots(scanning_action f,
scanning_action_flags fflags,
void* fdata,
caml_domain_state *state,
_Bool weak,
_Bool global);
_Bool weak);

/* Update memprof data structures for the domain `state`, to reflect
* survival and promotion, after a minor GC is completed.
*
* If `global` is false then only update structures for `state`. If
* `global` is true then also update structures shared between all
* domains. */
* survival and promotion, after a minor GC is completed. */

extern void caml_memprof_after_minor_gc(caml_domain_state *state, _Bool global);
extern void caml_memprof_after_minor_gc(caml_domain_state *state);

/* Update memprof data structures for the domain `state`, to reflect
* survival, after a minor GC is completed.
*
* If `global` is false then only update structures for `state`. If
* `global` is true then also update structures shared between all
* domains. */
* survival, after a minor GC is completed. */

extern void caml_memprof_after_major_gc(caml_domain_state *state, _Bool global);
extern void caml_memprof_after_major_gc(caml_domain_state *state);

/* Freshly computes state->memprof_young_trigger. *Does not* set the
* young limit. */
Expand Down
4 changes: 2 additions & 2 deletions runtime/major_gc.c
Original file line number Diff line number Diff line change
Expand Up @@ -1408,7 +1408,7 @@ static void stw_cycle_all_domains(
* mysteriously put all domains back into mark/sweep.
*/
CAML_EV_BEGIN(EV_MAJOR_MEMPROF_CLEAN);
caml_memprof_after_major_gc(domain, domain == participating[0]);
caml_memprof_after_major_gc(domain);
CAML_EV_END(EV_MAJOR_MEMPROF_CLEAN);

CAML_EV_BEGIN(EV_MAJOR_GC_CYCLE_DOMAINS);
Expand Down Expand Up @@ -1487,7 +1487,7 @@ static void stw_cycle_all_domains(

CAML_EV_BEGIN(EV_MAJOR_MEMPROF_ROOTS);
caml_memprof_scan_roots(caml_darken, darken_scanning_flags, domain,
domain, false, participating[0] == Caml_state);
domain, false);
CAML_EV_END(EV_MAJOR_MEMPROF_ROOTS);

if (domain->mark_stack->count == 0 &&
Expand Down
51 changes: 28 additions & 23 deletions runtime/memprof.c
Original file line number Diff line number Diff line change
Expand Up @@ -626,9 +626,12 @@ struct memprof_orphan_table_s {
/* List of orphaned entry tables not yet adopted by any domain. */
static memprof_orphan_table_t orphans = NULL;

/* lock controlling access to `orphans` variable */
/* lock controlling access to `orphans` and writes to `orphans_present` */
static caml_plat_mutex orphans_lock = CAML_PLAT_MUTEX_INITIALIZER;

/* Flag indicating non-NULL orphans. Only modified when holding orphans_lock. */
static atomic_uintnat orphans_present;

/**** Initializing and clearing entries tables ****/

static void entries_init(entries_t es, size_t min_capacity, value config)
Expand Down Expand Up @@ -965,6 +968,7 @@ static void orphans_abandon(memprof_domain_t domain)
caml_plat_lock_blocking(&orphans_lock);
ot->next = orphans;
orphans = domain->orphans;
atomic_store_release(&orphans_present, 1);
caml_plat_unlock(&orphans_lock);
domain->orphans = NULL;
}
Expand All @@ -973,15 +977,21 @@ static void orphans_abandon(memprof_domain_t domain)

static void orphans_adopt(memprof_domain_t domain)
{
if (!atomic_load_acquire(&orphans_present))
return; /* No orphans to adopt */

/* Find the end of the domain's orphans list */
memprof_orphan_table_t *p = &domain->orphans;
while(*p) {
p = &(*p)->next;
}

caml_plat_lock_blocking(&orphans_lock);
*p = orphans;
orphans = NULL;
if (orphans) {
*p = orphans;
orphans = NULL;
atomic_store_release(&orphans_present, 0);
}
caml_plat_unlock(&orphans_lock);
}

Expand Down Expand Up @@ -1463,15 +1473,13 @@ void caml_memprof_scan_roots(scanning_action f,
scanning_action_flags fflags,
void* fdata,
caml_domain_state *state,
bool weak,
bool global)
bool weak)
{
memprof_domain_t domain = state->memprof;
CAMLassert(domain);
if (global) {
/* Adopt all global orphans into this domain. */
orphans_adopt(domain);
}

/* Adopt all global orphans into this domain. */
orphans_adopt(domain);

bool young = (fflags & SCANNING_ONLY_YOUNG_VALUES);
struct scan_closure closure = {f, fflags, fdata, weak};
Expand Down Expand Up @@ -1515,17 +1523,15 @@ static void entries_update_after_minor_gc(entries_t entries,
}

/* Update all memprof structures for a given domain, at the end of a
* minor GC. If `global` is set, also ensure shared structures are
* updated (we do this by adopting orphans into this domain). */
* minor GC. */

void caml_memprof_after_minor_gc(caml_domain_state *state, bool global)
void caml_memprof_after_minor_gc(caml_domain_state *state)
{
memprof_domain_t domain = state->memprof;
CAMLassert(domain);
if (global) {
/* Adopt all global orphans into this domain. */
orphans_adopt(domain);
}

/* Adopt all global orphans into this domain. */
orphans_adopt(domain);

domain_apply_actions(domain, true, entry_update_after_minor_gc,
NULL, entries_update_after_minor_gc);
Expand Down Expand Up @@ -1558,17 +1564,16 @@ static bool entry_update_after_major_gc(entry_t e, void *data)
* is no "entries_update_after_major_gc" function. */

/* Update all memprof structures for a given domain, at the end of a
* major GC. If `global` is set, also update shared structures (we do
* this by adopting orphans into this domain). */
* major GC. */

void caml_memprof_after_major_gc(caml_domain_state *state, bool global)
void caml_memprof_after_major_gc(caml_domain_state *state)
{
memprof_domain_t domain = state->memprof;
CAMLassert(domain);
if (global) {
/* Adopt all global orphans into this domain. */
orphans_adopt(domain);
}

/* Adopt all global orphans into this domain. */
orphans_adopt(domain);

domain_apply_actions(domain, false, entry_update_after_major_gc,
NULL, NULL);
orphans_update_pending(domain);
Expand Down
4 changes: 2 additions & 2 deletions runtime/minor_gc.c
Original file line number Diff line number Diff line change
Expand Up @@ -596,7 +596,7 @@ void caml_empty_minor_heap_promote(caml_domain_state* domain,

CAML_EV_BEGIN(EV_MINOR_MEMPROF_ROOTS);
caml_memprof_scan_roots(&oldify_one, oldify_scanning_flags, &st,
domain, false, participating[0] == domain);
domain, false);
CAML_EV_END(EV_MINOR_MEMPROF_ROOTS);

CAML_EV_BEGIN(EV_MINOR_REMEMBERED_SET_PROMOTE);
Expand Down Expand Up @@ -633,7 +633,7 @@ void caml_empty_minor_heap_promote(caml_domain_state* domain,
CAML_EV_END(EV_MINOR_LOCAL_ROOTS);

CAML_EV_BEGIN(EV_MINOR_MEMPROF_CLEAN);
caml_memprof_after_minor_gc(domain, participating[0] == domain);
caml_memprof_after_minor_gc(domain);
CAML_EV_END(EV_MINOR_MEMPROF_CLEAN);

domain->young_ptr = domain->young_end;
Expand Down
2 changes: 1 addition & 1 deletion runtime/shared_heap.c
Original file line number Diff line number Diff line change
Expand Up @@ -1223,7 +1223,7 @@ void caml_compact_heap(caml_domain_state* domain_state,

/* Memprof roots and "weak" pointers to tracked blocks */
caml_memprof_scan_roots(&compact_update_value, 0, NULL,
Caml_state, true, participants[0] == Caml_state);
Caml_state, true);

/* Next, one domain does the global roots */
if (participants[0] == Caml_state) {
Expand Down

0 comments on commit 3941ce0

Please sign in to comment.