Skip to content

Commit

Permalink
erts: Setup limits for process heaps
Browse files Browse the repository at this point in the history
  • Loading branch information
psyeugenic committed Jan 10, 2012
1 parent a69fb32 commit d54854b
Show file tree
Hide file tree
Showing 8 changed files with 87 additions and 3 deletions.
1 change: 1 addition & 0 deletions erts/emulator/beam/atom.names
Original file line number Diff line number Diff line change
Expand Up @@ -319,6 +319,7 @@ atom messages
atom meta
atom meta_match_spec
atom min_heap_size
atom max_heap_size
atom min_bin_vheap_size
atom minor_version
atom Minus='-'
Expand Down
57 changes: 57 additions & 0 deletions erts/emulator/beam/bif.c
Original file line number Diff line number Diff line change
Expand Up @@ -810,6 +810,7 @@ BIF_RETTYPE spawn_opt_1(BIF_ALIST_1)
*/
so.flags = SPO_USE_ARGS;
so.min_heap_size = H_MIN_SIZE;
so.max_heap_size = H_MAX_SIZE;
so.min_vheap_size = BIN_VH_MIN_SIZE;
so.priority = PRIORITY_NORMAL;
so.max_gen_gcs = (Uint16) erts_smp_atomic32_read_nob(&erts_max_gen_gcs);
Expand Down Expand Up @@ -852,6 +853,15 @@ BIF_RETTYPE spawn_opt_1(BIF_ALIST_1)
} else {
so.min_heap_size = erts_next_heap_size(min_heap_size, 0);
}
} else if (arg == am_max_heap_size && is_small(val)) {
Sint max_heap_size = signed_val(val);
if (max_heap_size < 0 || max_heap_size > H_DEFAULT_LIMIT_SIZE) {
goto error;
} else if (max_heap_size > H_MAX_SIZE) {
so.max_heap_size = H_MAX_SIZE;
} else {
so.max_heap_size = erts_next_heap_size(max_heap_size, 0);
}
} else if (arg == am_min_bin_vheap_size && is_small(val)) {
Sint min_vheap_size = signed_val(val);
if (min_vheap_size < 0) {
Expand Down Expand Up @@ -885,6 +895,11 @@ BIF_RETTYPE spawn_opt_1(BIF_ALIST_1)
goto error;
}

/* ensure min heap size is less than max heap size */
if (so.min_heap_size >= so.max_heap_size) {
goto error;
}

/*
* Spawn the process.
*/
Expand Down Expand Up @@ -1591,6 +1606,23 @@ BIF_RETTYPE process_flag_2(BIF_ALIST_2)
}
BIF_RET(old_value);
}
else if (BIF_ARG_1 == am_max_heap_size) {
Sint i;
if (!is_small(BIF_ARG_2)) {
goto error;
}
i = signed_val(BIF_ARG_2);
if (i < H_MIN_SIZE || i > H_DEFAULT_LIMIT_SIZE) {
goto error;
}
old_value = make_small(BIF_P->max_heap_size);
if (i > H_MAX_SIZE) {
BIF_P->max_heap_size = H_MAX_SIZE;
} else {
BIF_P->max_heap_size = erts_next_heap_size(i, 0);
}
BIF_RET(old_value);
}
else if (BIF_ARG_1 == am_min_bin_vheap_size) {
Sint i;
if (!is_small(BIF_ARG_2)) {
Expand Down Expand Up @@ -4084,6 +4116,11 @@ BIF_RETTYPE system_flag_2(BIF_ALIST_2)
goto error;
}

/* egil: Should we calculate erts_next_heap_size before we check? */
if (n >= H_MAX_SIZE) {
goto error;
}

erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
erts_smp_thr_progress_block();

Expand All @@ -4092,6 +4129,26 @@ BIF_RETTYPE system_flag_2(BIF_ALIST_2)
erts_smp_thr_progress_unblock();
erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);

BIF_RET(make_small(oval));
} else if (BIF_ARG_1 == am_max_heap_size) {
int oval = H_MAX_SIZE;

if (!is_small(BIF_ARG_2) || (n = signed_val(BIF_ARG_2)) < 0) {
goto error;
}

/* egil: Should we calculate erts_next_heap_size before we check? */
if (n <= H_MIN_SIZE) {
goto error;
}
erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
erts_smp_thr_progress_block();

H_MAX_SIZE = erts_next_heap_size(n, 0);

erts_smp_thr_progress_unblock();
erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);

BIF_RET(make_small(oval));
} else if (BIF_ARG_1 == am_min_bin_vheap_size) {
int oval = BIN_VH_MIN_SIZE;
Expand Down
4 changes: 3 additions & 1 deletion erts/emulator/beam/erl_bif_info.c
Original file line number Diff line number Diff line change
Expand Up @@ -1470,7 +1470,7 @@ process_info_aux(Process *BIF_P,
DECL_AM(minor_gcs);
Eterm t;

hp = HAlloc(BIF_P, 3+2 + 3+2 + 3+2 + 3+2 + 3); /* last "3" is for outside tuple */
hp = HAlloc(BIF_P, 3+2 + 3+2 + 3+2 + 3+2 + 3+2 + 3); /* last "3" is for outside tuple */

t = TUPLE2(hp, AM_minor_gcs, make_small(GEN_GCS(rp))); hp += 3;
res = CONS(hp, t, NIL); hp += 2;
Expand All @@ -1479,6 +1479,8 @@ process_info_aux(Process *BIF_P,

t = TUPLE2(hp, am_min_heap_size, make_small(MIN_HEAP_SIZE(rp))); hp += 3;
res = CONS(hp, t, res); hp += 2;
t = TUPLE2(hp, am_max_heap_size, make_small(MAX_HEAP_SIZE(rp))); hp += 3;
res = CONS(hp, t, res); hp += 2;
t = TUPLE2(hp, am_min_bin_vheap_size, make_small(MIN_VHEAP_SIZE(rp))); hp += 3;
res = CONS(hp, t, res); hp += 2;
break;
Expand Down
16 changes: 16 additions & 0 deletions erts/emulator/beam/erl_init.c
Original file line number Diff line number Diff line change
Expand Up @@ -93,6 +93,7 @@ int erts_use_sender_punish;

Uint display_items; /* no of items to display in traces etc */
int H_MIN_SIZE; /* The minimum heap grain */
int H_MAX_SIZE; /* The maximum heap grain */
int BIN_VH_MIN_SIZE; /* The minimum binary virtual*/

Uint32 erts_debug_flags; /* Debug flags. */
Expand Down Expand Up @@ -490,6 +491,8 @@ void erts_usage(void)

erts_fprintf(stderr, "-hms size set minimum heap size in words (default %d)\n",
H_DEFAULT_SIZE);
erts_fprintf(stderr, "-hls size set maximum (limit) heap size in words (default %d)\n",
H_DEFAULT_LIMIT_SIZE);
erts_fprintf(stderr, "-hmbs size set minimum binary virtual heap size in words (default %d)\n",
VH_DEFAULT_SIZE);

Expand Down Expand Up @@ -618,6 +621,7 @@ early_init(int *argc, char **argv) /*
erts_async_max_threads = 0;
erts_async_thread_suggested_stack_size = ERTS_ASYNC_THREAD_MIN_STACK_SIZE;
H_MIN_SIZE = H_DEFAULT_SIZE;
H_MAX_SIZE = H_DEFAULT_LIMIT_SIZE;
BIN_VH_MIN_SIZE = VH_DEFAULT_SIZE;

erts_initialized = 0;
Expand Down Expand Up @@ -1075,6 +1079,13 @@ erl_start(int argc, char **argv)
erts_usage();
}
VERBOSE(DEBUG_SYSTEM, ("using minimum heap size %d\n", H_MIN_SIZE));
} else if (has_prefix("ls", sub_param)) {
arg = get_arg(sub_param+2, argv[i+1], &i);
if ((H_MAX_SIZE = atoi(arg)) <= 0) {
erts_fprintf(stderr, "bad heap size %s\n", arg);
erts_usage();
}
VERBOSE(DEBUG_SYSTEM, ("using maximum (limit) heap size %d\n", H_MAX_SIZE));
} else {
/* backward compatibility */
arg = get_arg(argv[i]+2, argv[i+1], &i);
Expand Down Expand Up @@ -1438,6 +1449,11 @@ erl_start(int argc, char **argv)
i++;
}

/* make sure min heap size is less than max heap size */
if (H_MAX_SIZE <= H_MIN_SIZE) {
erts_fprintf(stderr, "bad heap size, min heap %d >= max heap %d\n", H_MIN_SIZE, H_MAX_SIZE);
erts_usage();
}
/* Delayed check of +P flag */
if (erts_max_processes < ERTS_MIN_PROCESSES
|| erts_max_processes > ERTS_MAX_PROCESSES
Expand Down
2 changes: 2 additions & 0 deletions erts/emulator/beam/erl_process.c
Original file line number Diff line number Diff line change
Expand Up @@ -6762,11 +6762,13 @@ erl_create_process(Process* parent, /* Parent of process (default group leader).
*/
if (so->flags & SPO_USE_ARGS) {
p->min_heap_size = so->min_heap_size;
p->max_heap_size = so->max_heap_size;
p->min_vheap_size = so->min_vheap_size;
p->prio = so->priority;
p->max_gen_gcs = so->max_gen_gcs;
} else {
p->min_heap_size = H_MIN_SIZE;
p->max_heap_size = H_MAX_SIZE;
p->min_vheap_size = BIN_VH_MIN_SIZE;
p->prio = PRIORITY_NORMAL;
p->max_gen_gcs = (Uint16) erts_smp_atomic32_read_nob(&erts_max_gen_gcs);
Expand Down
3 changes: 3 additions & 0 deletions erts/emulator/beam/erl_process.h
Original file line number Diff line number Diff line change
Expand Up @@ -578,6 +578,7 @@ struct ErtsPendingSuspend_ {
# define MBUF_SIZE(p) (p)->mbuf_sz
# define MSO(p) (p)->off_heap
# define MIN_HEAP_SIZE(p) (p)->min_heap_size
# define MAX_HEAP_SIZE(p) (p)->max_heap_size

# define MIN_VHEAP_SIZE(p) (p)->min_vheap_size
# define BIN_VHEAP_SZ(p) (p)->bin_vheap_sz
Expand All @@ -599,6 +600,7 @@ struct process {
Eterm* hend; /* Heap end */
Uint heap_sz; /* Size of heap in words */
Uint min_heap_size; /* Minimum size of heap (in words). */
Uint max_heap_size; /* Max size of heap (in words). */
Uint min_vheap_size; /* Minimum size of virtual heap (in words). */

#if !defined(NO_FPE_SIGNALS) || defined(HIPE)
Expand Down Expand Up @@ -838,6 +840,7 @@ typedef struct {
*/
Uint min_heap_size; /* Minimum heap size (must be a valued returned
* from next_heap_size()). */
Uint max_heap_size; /* Max heap size */
Uint min_vheap_size; /* Minimum virtual heap size */
int priority; /* Priority for process. */
Uint16 max_gen_gcs; /* Maximum number of gen GCs before fullsweep. */
Expand Down
6 changes: 4 additions & 2 deletions erts/emulator/beam/erl_vm.h
Original file line number Diff line number Diff line change
Expand Up @@ -67,8 +67,9 @@

#define INPUT_REDUCTIONS (2 * CONTEXT_REDS)

#define H_DEFAULT_SIZE 233 /* default (heap + stack) min size */
#define VH_DEFAULT_SIZE 32768 /* default virtual (bin) heap min size (words) */
#define H_DEFAULT_SIZE 233 /* default (heap + stack) min size */
#define H_DEFAULT_LIMIT_SIZE 536870912 /* default (heap + stack) min size */
#define VH_DEFAULT_SIZE 32768 /* default virtual (bin) heap min size (words) */

#ifdef HYBRID
# define SH_DEFAULT_SIZE 2629425 /* default message area min size */
Expand Down Expand Up @@ -191,6 +192,7 @@ extern int num_instructions; /* Number of instruction in opc[]. */
#define MAX_PORT_LINK 8 /* Maximum number of links to a port */

extern int H_MIN_SIZE; /* minimum (heap + stack) */
extern int H_MAX_SIZE; /* maximum (heap + stack) */
extern int BIN_VH_MIN_SIZE; /* minimum virtual (bin) heap */

extern int erts_atom_table_size;/* Atom table size */
Expand Down
1 change: 1 addition & 0 deletions erts/etc/common/erlexec.c
Original file line number Diff line number Diff line change
Expand Up @@ -130,6 +130,7 @@ static char *pluss_val_switches[] = {
/* +h arguments with values */
static char *plush_val_switches[] = {
"ms",
"ls",
"mbs",
"",
NULL
Expand Down

0 comments on commit d54854b

Please sign in to comment.