Skip to content

Commit

Permalink
erts: Organize limits as its own group
Browse files Browse the repository at this point in the history
  • Loading branch information
psyeugenic committed Jan 11, 2012
1 parent 39cb752 commit c737c3a
Show file tree
Hide file tree
Showing 7 changed files with 61 additions and 26 deletions.
1 change: 1 addition & 0 deletions erts/emulator/beam/atom.names
Expand Up @@ -290,6 +290,7 @@ atom last_calls
atom latin1
atom Le='=<'
atom lf
atom limits
atom line
atom line_length
atom linked_in_driver
Expand Down
6 changes: 3 additions & 3 deletions erts/emulator/beam/bif.c
Expand Up @@ -1615,11 +1615,11 @@ BIF_RETTYPE process_flag_2(BIF_ALIST_2)
if (i < H_MIN_SIZE || i > H_DEFAULT_LIMIT_SIZE) {
goto error;
}
old_value = make_small(BIF_P->max_heap_size);
old_value = make_small(LIMIT_HEAP_SIZE(BIF_P));
if (i > H_MAX_SIZE) {
BIF_P->max_heap_size = H_MAX_SIZE;
LIMIT_HEAP_SIZE(BIF_P) = H_MAX_SIZE;
} else {
BIF_P->max_heap_size = erts_next_heap_size(i, 0);
LIMIT_HEAP_SIZE(BIF_P) = erts_next_heap_size(i, 0);
}
BIF_RET(old_value);
}
Expand Down
39 changes: 30 additions & 9 deletions erts/emulator/beam/erl_bif_info.c
Expand Up @@ -568,6 +568,7 @@ static Eterm pi_args[] = {
am_min_bin_vheap_size,
am_current_location,
am_current_stacktrace,
am_limits,
#ifdef HYBRID
am_message_binary
#endif
Expand Down Expand Up @@ -618,8 +619,9 @@ pi_arg2ix(Eterm arg)
case am_min_bin_vheap_size: return 28;
case am_current_location: return 29;
case am_current_stacktrace: return 30;
case am_limits: return 31;
#ifdef HYBRID
case am_message_binary: return 31;
case am_message_binary: return 32;
#endif
default: return -1;
}
Expand All @@ -643,7 +645,8 @@ static Eterm pi_1_keys[] = {
am_stack_size,
am_reductions,
am_garbage_collection,
am_suspending
am_suspending,
am_limits
};

#define ERTS_PI_1_NO_OF_KEYS (sizeof(pi_1_keys)/sizeof(Eterm))
Expand Down Expand Up @@ -1466,11 +1469,21 @@ process_info_aux(Process *BIF_P,
break;
}

case am_limits: {
Eterm t;

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

t = TUPLE2(hp, am_heap_size, make_small(LIMIT_HEAP_SIZE(rp))); hp += 3;
res = CONS(hp, t, NIL); hp += 2;
break;
}

case am_garbage_collection: {
DECL_AM(minor_gcs);
Eterm t;

hp = HAlloc(BIF_P, 3+2 + 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); /* 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,8 +1492,6 @@ 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 Expand Up @@ -2148,18 +2159,28 @@ BIF_RETTYPE system_info_1(BIF_ALIST_1)
ASSERT(is_internal_pid(val) || is_internal_port(val) || val==am_false)
hp = HAlloc(BIF_P, 3);
res = TUPLE2(hp, am_sequential_tracer, val);
BIF_RET(res);
} else if (BIF_ARG_1 == am_limits){
Eterm tup, proc = NIL;
hp = HAlloc(BIF_P, 3+2 /* process tuple and cons */ + 3+2);

/* process limits */
tup = TUPLE2(hp, am_heap_size, make_small(H_MAX_SIZE)); hp += 3;
proc = CONS(hp, tup, NIL); hp += 2;

/* resulting limits */
tup = TUPLE2(hp, am_process, proc); hp += 3;
res = CONS(hp, tup, NIL); hp += 2;

BIF_RET(res);
} else if (BIF_ARG_1 == am_garbage_collection){
Uint val = (Uint) erts_smp_atomic32_read_nob(&erts_max_gen_gcs);
Eterm tup;
hp = HAlloc(BIF_P, 3+2 + 3+2 + 3+2 + 3+2);
hp = HAlloc(BIF_P, 3+2 + 3+2 + 3+2);

tup = TUPLE2(hp, am_fullsweep_after, make_small(val)); hp += 3;
res = CONS(hp, tup, NIL); hp += 2;

tup = TUPLE2(hp, am_max_heap_size, make_small(H_MAX_SIZE)); hp += 3;
res = CONS(hp, tup, res); hp += 2;

tup = TUPLE2(hp, am_min_heap_size, make_small(H_MIN_SIZE)); hp += 3;
res = CONS(hp, tup, res); hp += 2;

Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_gc.c
Expand Up @@ -415,7 +415,7 @@ erts_garbage_collect(Process* p, int need, Eterm* objv, int nobj)
monitor_large_heap(p);
}

if ( (HEAP_SIZE(p) + OLD_HEAP(p) ? OLD_HEND(p) - OLD_HEAP(p) : 0) > MAX_HEAP_SIZE(p)) {
if ( (HEAP_SIZE(p) + OLD_HEAP(p) ? OLD_HEND(p) - OLD_HEAP(p) : 0) > LIMIT_HEAP_SIZE(p)) {
ErtsProcLocks locks;

locks = ERTS_PROC_LOCKS_XSIG_SEND;
Expand Down
24 changes: 14 additions & 10 deletions erts/emulator/beam/erl_process.c
Expand Up @@ -6761,17 +6761,21 @@ erl_create_process(Process* parent, /* Parent of process (default group leader).
* noone except us has access to the process.
*/
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;
p->min_heap_size = so->min_heap_size;
p->min_vheap_size = so->min_vheap_size;
p->prio = so->priority;
p->max_gen_gcs = so->max_gen_gcs;

/* limits */
LIMIT_HEAP_SIZE(p) = so->max_heap_size;
} 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);
p->min_heap_size = H_MIN_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);

/* limits */
LIMIT_HEAP_SIZE(p) = H_MAX_SIZE;
}
p->skipped = 0;
ASSERT(p->min_heap_size == erts_next_heap_size(p->min_heap_size, 0));
Expand Down
13 changes: 11 additions & 2 deletions erts/emulator/beam/erl_process.h
Expand Up @@ -474,6 +474,13 @@ extern ErtsAlignedSchedulerData *erts_aligned_scheduler_data;
extern ErtsSchedulerData *erts_scheduler_data;
#endif

/* All limits within a process */

typedef struct {
Uint heap_size;
} ErlProcessLimits;


/*
* Process Specific Data.
*
Expand Down Expand Up @@ -578,14 +585,16 @@ 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
# define BIN_VHEAP_MATURE(p) (p)->bin_vheap_mature
# define BIN_OLD_VHEAP_SZ(p) (p)->bin_old_vheap_sz
# define BIN_OLD_VHEAP(p) (p)->bin_old_vheap

/* Define easy access to process limits */
# define LIMIT_HEAP_SIZE(p) (p)->limits.heap_size

struct process {
/* All fields in the PCB that differs between different heap
* architectures, have been moved to the end of this struct to
Expand All @@ -600,7 +609,6 @@ 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 @@ -716,6 +724,7 @@ struct process {
} u;

ErtsRunQueue *bound_runq;
ErlProcessLimits limits;

#ifdef ERTS_SMP
erts_proc_lock_t lock;
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_vm.h
Expand Up @@ -68,7 +68,7 @@
#define INPUT_REDUCTIONS (2 * CONTEXT_REDS)

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

#ifdef HYBRID
Expand Down

0 comments on commit c737c3a

Please sign in to comment.