Skip to content

Commit

Permalink
Backport of ocaml#12318 to the 4.14 LTS branch.
Browse files Browse the repository at this point in the history
  • Loading branch information
damiendoligez committed Nov 21, 2023
1 parent 74fe398 commit 4aa224d
Show file tree
Hide file tree
Showing 7 changed files with 84 additions and 42 deletions.
7 changes: 7 additions & 0 deletions Changes
Expand Up @@ -8,6 +8,13 @@ OCaml 4.14 maintenance version

### Bug fixes:

### Runtime system:

- #12322: GC: simplify the meaning of custom_minor_max_size: blocks with
out-of-heap memory above this limit are now allocated directly in
the major heap.
(Damien Doligez, report by Stephen Dolan, review by ?)

OCaml 4.14.1 (20 December 2022)
------------------------------

Expand Down
2 changes: 1 addition & 1 deletion runtime/caml/config.h
Expand Up @@ -264,7 +264,7 @@ typedef uint64_t uintnat;
/* Default setting for maximum size of custom objects counted as garbage
in the minor heap.
Documented in gc.mli */
#define Custom_minor_max_bsz_def 8192
#define Custom_minor_max_bsz_def 70000

/* Default allocation policy. */
#define Allocation_policy_def caml_policy_best_fit
Expand Down
9 changes: 9 additions & 0 deletions runtime/caml/custom.h
Expand Up @@ -55,17 +55,26 @@ extern "C" {
#endif


CAMLextern uintnat caml_custom_major_ratio;

CAMLextern value caml_alloc_custom(struct custom_operations * ops,
uintnat size, /*size in bytes*/
mlsize_t mem, /*resources consumed*/
mlsize_t max /*max resources*/);

/* [caml_alloc_custom_mem] allocates a custom block with dependent memory
(memory outside the heap that will be reclaimed when the block is
finalized). If [mem] is greater than [custom_minor_max_size] (see gc.mli)
the block is allocated directly in the major heap. */
CAMLextern value caml_alloc_custom_mem(struct custom_operations * ops,
uintnat size, /*size in bytes*/
mlsize_t mem /*memory consumed*/);

CAMLextern void caml_register_custom_operations(struct custom_operations * ops);

/* Return the current [max] factor for [caml_alloc_custom_mem] allocations. */
CAMLextern mlsize_t caml_custom_get_max_major (void);

/* Global variable moved to Caml_state in 4.10 */
#define caml_compare_unordered (Caml_state_field(compare_unordered))

Expand Down
1 change: 1 addition & 0 deletions runtime/caml/memory.h
Expand Up @@ -50,6 +50,7 @@ CAMLextern value caml_alloc_shr_no_track_noexc (mlsize_t, tag_t);
CAMLextern value caml_alloc_shr_for_minor_gc (mlsize_t, tag_t, header_t);

CAMLextern void caml_adjust_gc_speed (mlsize_t, mlsize_t);
CAMLextern void caml_adjust_minor_gc_speed (mlsize_t, mlsize_t);
CAMLextern void caml_alloc_dependent_memory (mlsize_t bsz);
CAMLextern void caml_free_dependent_memory (mlsize_t bsz);
CAMLextern void caml_modify (value *, value);
Expand Down
77 changes: 42 additions & 35 deletions runtime/custom.c
Expand Up @@ -30,41 +30,55 @@ uintnat caml_custom_major_ratio = Custom_major_ratio_def;
uintnat caml_custom_minor_ratio = Custom_minor_ratio_def;
uintnat caml_custom_minor_max_bsz = Custom_minor_max_bsz_def;

mlsize_t caml_custom_get_max_major (void)
{
/* The major ratio is a percentage relative to the major heap size.
A complete GC cycle will be done every time 2/3 of that much
memory is allocated for blocks in the major heap. Assuming
constant allocation and deallocation rates, this means there are
at most [M/100 * major-heap-size] bytes of floating garbage at
any time. The reason for a factor of 2/3 (or 1.5) is, roughly
speaking, because the major GC takes 1.5 cycles (previous cycle +
marking phase) before it starts to deallocate dead blocks
allocated during the previous cycle. [heap_size / 150] is really
[heap_size * (2/3) / 100] (but faster). */
return Bsize_wsize (Caml_state->stat_heap_wsz) / 150
* caml_custom_major_ratio;
}

/* [mem] is an amount of out-of-heap resources, in the same units as
[max_major] and [max_minor]. When the cumulated amount of such
resources reaches [max_minor] (for resources held by the minor
heap) we do a minor collection; when it reaches [max_major] (for
resources held by the major heap), we guarantee that a major cycle
is done.
If [max_major] is 0, then [mem] is a number of bytes and the actual
limit is [caml_custom_get_max_major ()] computed at the
time when the custom block is promoted to the major heap.
*/
static value alloc_custom_gen (struct custom_operations * ops,
uintnat bsz,
mlsize_t mem,
mlsize_t max_major,
mlsize_t mem_minor,
mlsize_t max_minor)
{
mlsize_t wosize;
CAMLparam0();
CAMLlocal1(result);

/* [mem] is the total amount of out-of-heap memory, [mem_minor] is how much
of it should be counted against [max_minor]. */
CAMLassert (mem_minor <= mem);

wosize = 1 + (bsz + sizeof(value) - 1) / sizeof(value);
if (wosize <= Max_young_wosize) {
if (wosize <= Max_young_wosize && mem <= caml_custom_minor_max_bsz) {
result = caml_alloc_small(wosize, Custom_tag);
Custom_ops_val(result) = ops;
if (ops->finalize != NULL || mem != 0) {
if (mem > mem_minor) {
caml_adjust_gc_speed (mem - mem_minor, max_major);
}
/* The remaining [mem_minor] will be counted if the block survives a
minor GC */
/* Record the extra resources in case the block gets promoted. */
add_to_custom_table (Caml_state->custom_table, result,
mem_minor, max_major);
mem, max_major);
/* Keep track of extra resources held by custom block in
minor heap. */
if (mem_minor != 0) {
if (max_minor == 0) max_minor = 1;
Caml_state->extra_heap_resources_minor +=
(double) mem_minor / (double) max_minor;
if (Caml_state->extra_heap_resources_minor > 1.0)
caml_minor_collection ();
if (mem != 0) {
caml_adjust_minor_gc_speed (mem, max_minor);
}
}
} else {
Expand All @@ -76,34 +90,27 @@ static value alloc_custom_gen (struct custom_operations * ops,
CAMLreturn(result);
}

Caml_inline mlsize_t get_max_minor (void)
{
return
Bsize_wsize (Caml_state->minor_heap_wsz) / 100 * caml_custom_minor_ratio;
}

CAMLexport value caml_alloc_custom(struct custom_operations * ops,
uintnat bsz,
mlsize_t mem,
mlsize_t max)
{
return alloc_custom_gen (ops, bsz, mem, max, mem, max);
mlsize_t max_major = max;
mlsize_t max_minor = max == 0 ? get_max_minor() : max;
return alloc_custom_gen (ops, bsz, mem, max_major, max_minor);
}

CAMLexport value caml_alloc_custom_mem(struct custom_operations * ops,
uintnat bsz,
mlsize_t mem)
{
mlsize_t mem_minor =
mem < caml_custom_minor_max_bsz ? mem : caml_custom_minor_max_bsz;
mlsize_t max_major =
/* The major ratio is a percentage relative to the major heap size.
A complete GC cycle will be done every time 2/3 of that much memory
is allocated for blocks in the major heap. Assuming constant
allocation and deallocation rates, this means there are at most
[M/100 * major-heap-size] bytes of floating garbage at any time.
The reason for a factor of 2/3 (or 1.5) is, roughly speaking, because
the major GC takes 1.5 cycles (previous cycle + marking phase) before
it starts to deallocate dead blocks allocated during the previous cycle.
[heap_size / 150] is really [heap_size * (2/3) / 100] (but faster). */
Bsize_wsize (Caml_state->stat_heap_wsz) / 150 * caml_custom_major_ratio;
mlsize_t max_minor =
Bsize_wsize (Caml_state->minor_heap_wsz) / 100 * caml_custom_minor_ratio;
value v = alloc_custom_gen (ops, bsz, mem, max_major, mem_minor, max_minor);
value v = alloc_custom_gen (ops, bsz, mem, 0, get_max_minor());
caml_memprof_track_custom(v, mem);
return v;
}
Expand Down
22 changes: 21 additions & 1 deletion runtime/memory.c
Expand Up @@ -21,6 +21,7 @@
#include <stddef.h>
#include "caml/address_class.h"
#include "caml/config.h"
#include "caml/custom.h"
#include "caml/fail.h"
#include "caml/freelist.h"
#include "caml/gc.h"
Expand Down Expand Up @@ -573,10 +574,16 @@ CAMLexport void caml_free_dependent_memory (mlsize_t nbytes)
this time.
Note that only [res/max] is relevant. The units (and kind of
resource) can change between calls to [caml_adjust_gc_speed].
If [max] = 0, then we use a number proportional to the major heap
size and [caml_custom_major_ratio]. In this case, [mem] should
be a number of bytes and the trade-off between GC work and space
overhead is under the control of the user through
[caml_custom_major_ratio].
*/
CAMLexport void caml_adjust_gc_speed (mlsize_t res, mlsize_t max)
{
if (max == 0) max = 1;
if (max == 0) max = caml_custom_get_max_major ();
if (res > max) res = max;
caml_extra_heap_resources += (double) res / (double) max;
if (caml_extra_heap_resources > 1.0){
Expand All @@ -586,6 +593,19 @@ CAMLexport void caml_adjust_gc_speed (mlsize_t res, mlsize_t max)
}
}

/* This function is analogous to [caml_adjust_gc_speed]. When the
accumulated sum of [res/max] values reaches 1, a minor GC is
triggered.
*/
CAMLexport void caml_adjust_minor_gc_speed (mlsize_t res, mlsize_t max)
{
if (max == 0) max = 1;
Caml_state->extra_heap_resources_minor += (double) res / (double) max;
if (Caml_state->extra_heap_resources_minor > 1.0) {
caml_minor_collection ();
}
}

/* You must use [caml_initialize] to store the initial value in a field of
a shared block, unless you are sure the value is not a young block.
A block value [v] is a shared block if and only if [Is_in_heap (v)]
Expand Down
8 changes: 3 additions & 5 deletions stdlib/gc.mli
Expand Up @@ -232,13 +232,11 @@ type control =

custom_minor_max_size : int;
(** Maximum amount of out-of-heap memory for each custom value
allocated in the minor heap. When a custom value is allocated
on the minor heap and holds more than this many bytes, only
this value is counted against [custom_minor_ratio] and the
rest is directly counted against [custom_major_ratio].
allocated in the minor heap. Custom values that hold more
than this many bytes are allocated on the major heap.
Note: this only applies to values allocated with
[caml_alloc_custom_mem] (e.g. bigarrays).
Default: 8192 bytes.
Default: 70000 bytes.
@since 4.08.0 *)
}
(** The GC parameters are given as a [control] record. Note that
Expand Down

0 comments on commit 4aa224d

Please sign in to comment.