Add caml_alloc_custom_mem (#1738)

* add caml_alloc_custom_mem and corresponding GC parameters
* fix a bug in tests/misc/ephetest2.ml
master
Damien Doligez 2018-11-06 13:42:48 +01:00 committed by GitHub
parent 0d968e357b
commit 17b64ac2b2
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
19 changed files with 275 additions and 31 deletions

View File

@ -261,6 +261,12 @@ Working version
### Runtime system:
- MPR#7750, GPR#1738: add a function (caml_custom_alloc_mem) and three
GC parameters to give the user better control of the out-of-heap
memory retained by custom values; use the function to allocate
bigarrays and I/O channels.
(Damien Doligez, review by Alain Frisch)
- GPR#1793: add the -m and -M command-line options to ocamlrun.
(Sébastien Hinderer, review by Xavier Clerc and Damien Doligez)

View File

@ -125,6 +125,7 @@ last six correspond to the fields of the
record documented in
.IR "The OCaml user's manual",
chapter "Standard Library", section "Gc".
\" FIXME missing: c, H, t, w, W see MPR#7870
.TP
.B b
Trigger the printing of a stack backtrace
@ -168,6 +169,42 @@ The heap compaction trigger setting.
.BR l \ (stack_limit)
The limit (in words) of the stack size.
.TP
.BR M \ (custom_major_ratio)
Target ratio of floating garbage to
major heap size for out-of-heap memory held by custom values
located in the major heap. The GC speed is adjusted
to try to use this much memory for dead values that are not yet
collected. Expressed as a percentage of major heap size.
The default value keeps the out-of-heap floating garbage about the
same size as the in-heap overhead.
Note: this only applies to values allocated with
.B caml_alloc_custom_mem
(e.g. bigarrays).
Default: 44.
.TP
.BR m \ (custom_minor_ratio)
Bound on floating garbage for out-of-heap memory
held by custom values in the minor heap. A minor GC is triggered
when this much memory is held by custom values located in the minor
heap. Expressed as a percentage of minor heap size.
Note: this only applies to values allocated with
.B caml_alloc_custom_mem
(e.g. bigarrays).
Default: 100.
.TP
.BR n \ (custom_minor_max_size)
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
.B custom_minor_ratio
and the rest is directly counted against
.BR custom_major_ratio .
Note: this only applies to values allocated with
.B caml_alloc_custom_mem
(e.g. bigarrays).
Default: 8192 bytes.
.TP
.BR v \ (verbose)
What GC messages to print to stderr. This is a sum of values selected
from the following:

View File

@ -1864,7 +1864,8 @@ functions, and do not use "CAMLreturn" to return the result.
\subsection{Allocating custom blocks}
Custom blocks must be allocated via the "caml_alloc_custom" function:
Custom blocks must be allocated via "caml_alloc_custom" or
"caml_alloc_custom_mem":
\begin{center}
"caml_alloc_custom("\var{ops}", "\var{size}", "\var{used}", "\var{max}")"
\end{center}
@ -1916,6 +1917,18 @@ $\var{used} = 0$ and $\var{max} = 1$. But if you later find that the
finalization functions are not called ``often enough'', consider
increasing the $\var{used} / \var{max}$ ratio.
\begin{center}
"caml_alloc_custom_mem("\var{ops}", "\var{size}", "\var{used}")"
\end{center}
Use this function when your custom block holds only out-of-heap memory
(memory allocated with "malloc" or "caml_stat_alloc") and no other
resources. "used" should be the number of bytes of out-of-heap
memory that are held by your custom block. This function works like
"caml_alloc_custom" except that the "max" parameter is under the
control of the user (via the "custom_major_ratio",
"custom_minor_ratio", and "custom_minor_max_size" parameters) and
proportional to the heap sizes.
\subsection{Accessing custom blocks}
The data part of a custom block \var{v} can be

View File

@ -157,6 +157,28 @@ The following environment variables are also consulted:
"caml_shutdown" in section~\ref{s:embedded-code}). The option also enables
pooling (as in "caml_startup_pooled"). This mode can be used to detect
leaks with a third-party memory debugger.
% FIXME missing: H, t, w, W see MPR#7870
\item[M] ("custom_major_ratio") Target ratio of floating garbage to
major heap size for out-of-heap memory held by custom values
(e.g. bigarrays) located in the major heap. The GC speed is adjusted
to try to use this much memory for dead values that are not yet
collected. Expressed as a percentage of major heap size. Default:
44. Note: this only applies to values allocated with
"caml_alloc_custom_mem".
\item[m] ("custom_minor_ratio") Bound on floating garbage for
out-of-heap memory
held by custom values in the minor heap. A minor GC is triggered
when this much memory is held by custom values located in the minor
heap. Expressed as a percentage of minor heap size. Default:
100. Note: this only applies to values allocated with
"caml_alloc_custom_mem".
\item[n] ("custom_minor_max_size") 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".
Default: 8192 bytes. Note:
this only applies to values allocated with "caml_alloc_custom_mem".
\end{options}
The multiplier is "k", "M", or "G", for multiplication by $2^{10}$,
$2^{20}$, and $2^{30}$ respectively.

View File

@ -79,10 +79,6 @@ CAMLexport struct custom_operations caml_ba_ops = {
/* Allocation of a big array */
#define CAML_BA_MAX_MEMORY (1024*1024*1024)
/* 1 Gb -- after allocating that much, it's probably worth speeding
up the major GC */
/* [caml_ba_alloc] will allocate a new bigarray object in the heap.
If [data] is NULL, the memory for the contents is also allocated
(with [malloc]) by [caml_ba_alloc].
@ -117,7 +113,7 @@ caml_ba_alloc(int flags, int num_dims, void * data, intnat * dim)
flags |= CAML_BA_MANAGED;
}
asize = SIZEOF_BA_ARRAY + num_dims * sizeof(intnat);
res = caml_alloc_custom(&caml_ba_ops, asize, size, CAML_BA_MAX_MEMORY);
res = caml_alloc_custom_mem(&caml_ba_ops, asize, size);
b = Caml_ba_array_val(res);
b->data = data;
b->num_dims = num_dims;

View File

@ -222,4 +222,17 @@ typedef uint64_t uintnat;
/* Maximum size of the major GC slice smoothing window. */
#define Max_major_window 50
/* Default setting for the ratio of custom garbage to major heap size.
Documented in gc.mli */
#define Custom_major_ratio_def 44
/* Default setting for the ratio of custom garbage to minor heap size.
Documented in gc.mli */
#define Custom_minor_ratio_def 100
/* 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
#endif /* CAML_CONFIG_H */

View File

@ -60,6 +60,10 @@ CAMLextern value caml_alloc_custom(struct custom_operations * ops,
mlsize_t mem, /*resources consumed*/
mlsize_t max /*max resources*/);
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);
CAMLextern int caml_compare_unordered;

View File

@ -42,9 +42,13 @@ uintnat caml_normalize_heap_increment (uintnat);
percent_fr: cf. space_overhead in gc.mli
percent_m : cf. max_overhead in gc.mli
window : cf. window_size in gc.mli
custom_maj: cf. custom_major_ratio in gc.mli
custom_min: cf. custom_minor_ratio in gc.mli
custom_sz : cf. custom_minor_max_size in gc.mli
*/
void caml_init_gc (uintnat minor_size, uintnat major_size, uintnat major_incr,
uintnat percent_fr, uintnat percent_m, uintnat window);
uintnat percent_fr, uintnat percent_m, uintnat window,
uintnat custom_maj, uintnat custom_min, uintnat custom_bsz);
CAMLextern value caml_gc_stat(value v);

View File

@ -32,6 +32,9 @@ extern uintnat caml_init_heap_chunk_sz;
extern uintnat caml_init_heap_wsz;
extern uintnat caml_init_max_stack_wsz;
extern uintnat caml_init_major_window;
extern uintnat caml_init_custom_major_ratio;
extern uintnat caml_init_custom_minor_ratio;
extern uintnat caml_init_custom_minor_max_bsz;
extern uintnat caml_trace_level;
extern int caml_cleanup_on_exit;

View File

@ -20,32 +20,47 @@
#include "caml/alloc.h"
#include "caml/custom.h"
#include "caml/fail.h"
#include "caml/gc_ctrl.h"
#include "caml/memory.h"
#include "caml/mlvalues.h"
#include "caml/signals.h"
/* [size] is a number of bytes */
CAMLexport value caml_alloc_custom(struct custom_operations * ops,
uintnat size,
mlsize_t mem,
mlsize_t max)
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;
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);
wosize = 1 + (size + sizeof(value) - 1) / sizeof(value);
/* [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) {
result = caml_alloc_small(wosize, Custom_tag);
Custom_ops_val(result) = ops;
if (ops->finalize != NULL || mem != 0) {
/* Remember that the block needs processing after minor GC. */
add_to_custom_table (&caml_custom_table, result, mem, max);
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 */
add_to_custom_table (&caml_custom_table, result, mem_minor, max_major);
/* Keep track of extra resources held by custom block in
minor heap. */
if (mem != 0) {
if (max == 0) max = 1;
caml_extra_heap_resources_minor += (double) mem / (double) max;
if (mem_minor != 0) {
if (max_minor == 0) max_minor = 1;
caml_extra_heap_resources_minor +=
(double) mem_minor / (double) max_minor;
if (caml_extra_heap_resources_minor > 1.0) {
caml_request_minor_gc ();
caml_gc_dispatch ();
@ -55,12 +70,34 @@ CAMLexport value caml_alloc_custom(struct custom_operations * ops,
} else {
result = caml_alloc_shr(wosize, Custom_tag);
Custom_ops_val(result) = ops;
caml_adjust_gc_speed(mem, max);
caml_adjust_gc_speed(mem, max_major);
result = caml_check_urgent_gc(result);
}
CAMLreturn(result);
}
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);
}
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;
return alloc_custom_gen (ops, bsz, mem,
Bsize_wsize (caml_stat_heap_wsz) / 150
* caml_custom_major_ratio,
mem_minor,
Bsize_wsize (caml_minor_heap_wsz) / 100
* caml_custom_major_ratio);
}
struct custom_operations_list {
struct custom_operations * ops;
struct custom_operations_list * next;

View File

@ -56,6 +56,9 @@ extern uintnat caml_major_heap_increment; /* percent or words; see major_gc.c */
extern uintnat caml_percent_free; /* see major_gc.c */
extern uintnat caml_percent_max; /* see compact.c */
extern uintnat caml_allocation_policy; /* see freelist.c */
extern uintnat caml_custom_major_ratio; /* see custom.c */
extern uintnat caml_custom_minor_ratio; /* see custom.c */
extern uintnat caml_custom_minor_max_bsz; /* see custom.c */
#define Next(hp) ((hp) + Whsize_hp (hp))
@ -356,7 +359,7 @@ CAMLprim value caml_gc_get(value v)
CAMLparam0 (); /* v is ignored */
CAMLlocal1 (res);
res = caml_alloc_tuple (8);
res = caml_alloc_tuple (11);
Store_field (res, 0, Val_long (caml_minor_heap_wsz)); /* s */
Store_field (res, 1, Val_long (caml_major_heap_increment)); /* i */
Store_field (res, 2, Val_long (caml_percent_free)); /* o */
@ -369,6 +372,9 @@ CAMLprim value caml_gc_get(value v)
#endif
Store_field (res, 6, Val_long (caml_allocation_policy)); /* a */
Store_field (res, 7, Val_long (caml_major_window)); /* w */
Store_field (res, 8, Val_long (caml_custom_major_ratio)); /* M */
Store_field (res, 9, Val_long (caml_custom_minor_ratio)); /* m */
Store_field (res, 10, Val_long (caml_custom_minor_max_bsz)); /* n */
CAMLreturn (res);
}
@ -398,12 +404,23 @@ static uintnat norm_window (intnat w)
return w;
}
static uintnat norm_custom_maj (uintnat p)
{
return Max (p, 1);
}
static uintnat norm_custom_min (uintnat p)
{
return Max (p, 1);
}
CAMLprim value caml_gc_set(value v)
{
uintnat newpf, newpm;
asize_t newheapincr;
asize_t newminwsz;
uintnat oldpolicy;
uintnat new_custom_maj, new_custom_min, new_custom_sz;
CAML_INSTR_SETUP (tmr, "");
caml_verb_gc = Long_val (Field (v, 3));
@ -456,6 +473,31 @@ CAMLprim value caml_gc_set(value v)
}
}
/* These fields were added in 4.08.0. */
if (Wosize_val (v) >= 11){
new_custom_maj = norm_custom_maj (Field (v, 8));
if (new_custom_maj != caml_custom_major_ratio){
caml_custom_major_ratio = new_custom_maj;
caml_gc_message (0x20, "New custom major ratio: %"
ARCH_INTNAT_PRINTF_FORMAT "u%%\n",
caml_custom_major_ratio);
}
new_custom_min = norm_custom_min (Field (v, 9));
if (new_custom_min != caml_custom_minor_ratio){
caml_custom_minor_ratio = new_custom_min;
caml_gc_message (0x20, "New custom minor ratio: %"
ARCH_INTNAT_PRINTF_FORMAT "u%%\n",
caml_custom_minor_ratio);
}
new_custom_sz = Field (v, 10);
if (new_custom_sz != caml_custom_minor_max_bsz){
caml_custom_minor_max_bsz = new_custom_sz;
caml_gc_message (0x20, "New custom minor size limit: %"
ARCH_INTNAT_PRINTF_FORMAT "u%%\n",
caml_custom_minor_max_bsz);
}
}
/* Minor heap size comes last because it will trigger a minor collection
(thus invalidating [v]) and it can raise [Out_of_memory]. */
newminwsz = norm_minsize (Long_val (Field (v, 0)));
@ -584,7 +626,9 @@ uintnat caml_normalize_heap_increment (uintnat i)
[major_incr] is either a percentage or a number of words */
void caml_init_gc (uintnat minor_size, uintnat major_size,
uintnat major_incr, uintnat percent_fr,
uintnat percent_m, uintnat window)
uintnat percent_m, uintnat window,
uintnat custom_maj, uintnat custom_min,
uintnat custom_bsz)
{
uintnat major_heap_size =
Bsize_wsize (caml_normalize_heap_increment (major_size));
@ -602,6 +646,9 @@ void caml_init_gc (uintnat minor_size, uintnat major_size,
caml_percent_max = norm_pmax (percent_m);
caml_init_major_heap (major_heap_size);
caml_major_window = norm_window (window);
caml_custom_major_ratio = norm_custom_maj (custom_maj);
caml_custom_minor_ratio = norm_custom_min (custom_min);
caml_custom_minor_max_bsz = custom_bsz;
caml_gc_message (0x20, "Initial minor heap size: %"
ARCH_SIZET_PRINTF_FORMAT "uk words\n",
caml_minor_heap_wsz / 1024);

View File

@ -461,8 +461,8 @@ CAMLexport value caml_alloc_channel(struct channel *chan)
{
value res;
chan->refcount++; /* prevent finalization during next alloc */
res = caml_alloc_custom(&channel_operations, sizeof(struct channel *),
1, 1000);
res = caml_alloc_custom_mem(&channel_operations, sizeof(struct channel *),
sizeof(struct channel));
Channel(res) = chan;
return res;
}

View File

@ -64,6 +64,7 @@ uintnat caml_fl_wsz_at_phase_change = 0;
extern char *caml_fl_merge; /* Defined in freelist.c. */
static char *markhp, *chunk, *limit;
static double p_backlog = 0.0; /* backlog for the gc speedup parameter */
int caml_gc_subphase; /* Subphase_{mark_roots,mark_main,mark_final} */
@ -694,7 +695,12 @@ void caml_major_collection_slice (intnat howmuch)
}
if (p < dp) p = dp;
if (p < caml_extra_heap_resources) p = caml_extra_heap_resources;
if (p > 0.3) p = 0.3;
p += p_backlog;
p_backlog = 0.0;
if (p > 0.3){
p_backlog = p - 0.3;
p = 0.3;
}
CAML_INSTR_INT ("major/work/extra#",
(uintnat) (caml_extra_heap_resources * 1000000));
@ -709,6 +715,9 @@ void caml_major_collection_slice (intnat howmuch)
caml_gc_message (0x40, "raw work-to-do = %"
ARCH_INTNAT_PRINTF_FORMAT "du\n",
(intnat) (p * 1000000));
caml_gc_message (0x40, "work backlog = %"
ARCH_INTNAT_PRINTF_FORMAT "du\n",
(intnat) (p_backlog * 1000000));
for (i = 0; i < caml_major_window; i++){
caml_major_ring[i] += p / caml_major_window;
@ -829,7 +838,10 @@ void caml_major_collection_slice (intnat howmuch)
*/
void caml_finish_major_cycle (void)
{
if (caml_gc_phase == Phase_idle) start_cycle ();
if (caml_gc_phase == Phase_idle){
p_backlog = 0.0; /* full major GC cycle, the backlog becomes irrelevant */
start_cycle ();
}
while (caml_gc_phase == Phase_mark) mark_slice (LONG_MAX);
while (caml_gc_phase == Phase_clean) clean_slice (LONG_MAX);
CAMLassert (caml_gc_phase == Phase_sweep);

View File

@ -59,6 +59,9 @@ uintnat caml_init_heap_chunk_sz = Heap_chunk_def;
uintnat caml_init_heap_wsz = Init_heap_def;
uintnat caml_init_max_stack_wsz = Max_stack_def;
uintnat caml_init_major_window = Major_window_def;
uintnat caml_init_custom_major_ratio = Custom_major_ratio_def;
uintnat caml_init_custom_minor_ratio = Custom_minor_ratio_def;
uintnat caml_init_custom_minor_max_bsz = Custom_minor_max_bsz_def;
extern int caml_parser_trace;
uintnat caml_trace_level = 0;
int caml_cleanup_on_exit = 0;
@ -96,6 +99,9 @@ void caml_parse_ocamlrunparam(void)
case _T('H'): scanmult (opt, &caml_use_huge_pages); break;
case _T('i'): scanmult (opt, &caml_init_heap_chunk_sz); break;
case _T('l'): scanmult (opt, &caml_init_max_stack_wsz); break;
case _T('M'): scanmult (opt, &caml_init_custom_major_ratio); break;
case _T('m'): scanmult (opt, &caml_init_custom_minor_ratio); break;
case _T('n'): scanmult (opt, &caml_init_custom_minor_max_bsz); break;
case _T('o'): scanmult (opt, &caml_init_percent_free); break;
case _T('O'): scanmult (opt, &caml_init_max_percent_free); break;
case _T('p'): scanmult (opt, &p); caml_parser_trace = (p != 0); break;

View File

@ -404,7 +404,9 @@ CAMLexport void caml_main(char_os **argv)
/* Initialize the abstract machine */
caml_init_gc (caml_init_minor_heap_wsz, caml_init_heap_wsz,
caml_init_heap_chunk_sz, caml_init_percent_free,
caml_init_max_percent_free, caml_init_major_window);
caml_init_max_percent_free, caml_init_major_window,
caml_init_custom_major_ratio, caml_init_custom_minor_ratio,
caml_init_custom_minor_max_bsz);
caml_init_stack (caml_init_max_stack_wsz);
caml_init_atom_table();
caml_init_backtrace();
@ -496,7 +498,9 @@ CAMLexport value caml_startup_code_exn(
/* Initialize the abstract machine */
caml_init_gc (caml_init_minor_heap_wsz, caml_init_heap_wsz,
caml_init_heap_chunk_sz, caml_init_percent_free,
caml_init_max_percent_free, caml_init_major_window);
caml_init_max_percent_free, caml_init_major_window,
caml_init_custom_major_ratio, caml_init_custom_minor_ratio,
caml_init_custom_minor_max_bsz);
caml_init_stack (caml_init_max_stack_wsz);
caml_init_atom_table();
caml_init_backtrace();

View File

@ -135,7 +135,9 @@ value caml_startup_common(char_os **argv, int pooling)
caml_top_of_stack = &tos;
caml_init_gc (caml_init_minor_heap_wsz, caml_init_heap_wsz,
caml_init_heap_chunk_sz, caml_init_percent_free,
caml_init_max_percent_free, caml_init_major_window);
caml_init_max_percent_free, caml_init_major_window,
caml_init_custom_major_ratio, caml_init_custom_minor_ratio,
caml_init_custom_minor_max_bsz);
init_static();
caml_init_signals();
#ifdef _WIN32

View File

@ -41,6 +41,9 @@ type control = {
mutable stack_limit : int;
mutable allocation_policy : int;
window_size : int;
custom_major_ratio : int;
custom_minor_ratio : int;
custom_minor_max_size : int;
}
external stat : unit -> stat = "caml_gc_stat"

View File

@ -149,7 +149,41 @@ type control =
out variations in its workload. This is an integer between
1 and 50.
Default: 1. @since 4.03.0 *)
}
custom_major_ratio : int;
(** Target ratio of floating garbage to major heap size for
out-of-heap memory held by custom values located in the major
heap. The GC speed is adjusted to try to use this much memory
for dead values that are not yet collected. Expressed as a
percentage of major heap size. The default value keeps the
out-of-heap floating garbage about the same size as the
in-heap overhead.
Note: this only applies to values allocated with
[caml_alloc_custom_mem] (e.g. bigarrays).
Default: 44.
@since 4.08.0 *)
custom_minor_ratio : int;
(** Bound on floating garbage for out-of-heap memory held by
custom values in the minor heap. A minor GC is triggered when
this much memory is held by custom values located in the minor
heap. Expressed as a percentage of minor heap size.
Note: this only applies to values allocated with
[caml_alloc_custom_mem] (e.g. bigarrays).
Default: 100.
@since 4.08.0 *)
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].
Note: this only applies to values allocated with
[caml_alloc_custom_mem] (e.g. bigarrays).
Default: 8192 bytes.
@since 4.08.0 *)
}
(** The GC parameters are given as a [control] record. Note that
these parameters can also be initialised by setting the
OCAMLRUNPARAM environment variable. See the documentation of

View File

@ -144,9 +144,10 @@ let run test init =
Stack.clear env.varephe_false;
Gc.full_major ();
let res = Hashtbl.fold (fun _ v acc -> acc && check_var v) env.vars true in
is_true test "check" res
is_true test "check" res;
env (* Keep env.varephe_true alive. *)
let () =
for i = 0 to nb_test do
run ("test"^(string_of_int i)) i;
ignore (run ("test"^(string_of_int i)) i);
done