Skip to content

Commit

Permalink
Merge 'sverker/erts/valgrind-cuddle' into maint
Browse files Browse the repository at this point in the history
  • Loading branch information
sverker committed Oct 14, 2024
2 parents 0e968fb + 25caf1c commit 39d5282
Show file tree
Hide file tree
Showing 10 changed files with 30 additions and 20 deletions.
4 changes: 2 additions & 2 deletions erts/emulator/beam/dist.c
Original file line number Diff line number Diff line change
Expand Up @@ -2172,10 +2172,10 @@ int erts_net_message(Port *prt,
goto decode_error;
}

/* Fill the unused part of the hfrag with a bignum header */
/* Fill the unused part of the hfrag */
if (ede_hfrag && ede_hfrag->mem + ede_hfrag->used_size > factory.hp) {
Uint slot = factory.hp - ede_hfrag->mem;
ede_hfrag->mem[slot] = make_pos_bignum_header(ede_hfrag->used_size - slot - 1);
erts_write_heap_filler(&ede_hfrag->mem[slot], ede_hfrag->used_size - slot);
}

if (is_not_tuple(arg) ||
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_bif_info.c
Original file line number Diff line number Diff line change
Expand Up @@ -5135,7 +5135,7 @@ BIF_RETTYPE erts_debug_set_internal_state_2(BIF_ALIST_2)
UWord left = HeapWordsLeft(BIF_P);
if (left > 1) {
Eterm* hp = HAlloc(BIF_P, left);
*hp = make_pos_bignum_header(left - 1);
erts_write_heap_filler(hp, left);
}
if (BIF_ARG_2 == am_true) {
FLAGS(BIF_P) |= F_NEED_FULLSWEEP;
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_gc.c
Original file line number Diff line number Diff line change
Expand Up @@ -567,7 +567,7 @@ delay_garbage_collection(Process *p, int need, int fcalls)
else {
/* Do not leave a hole in the abandoned heap... */
if (orig_htop < orig_hend) {
*orig_htop = make_pos_bignum_header(orig_hend-orig_htop-1);
erts_write_heap_filler(orig_htop, orig_hend-orig_htop);
if (orig_htop + 1 < orig_hend) {
orig_hend[-1] = (Uint) (orig_htop - orig_heap);
p->flags |= F_ABANDONED_HEAP_USE;
Expand Down
10 changes: 5 additions & 5 deletions erts/emulator/beam/erl_map.c
Original file line number Diff line number Diff line change
Expand Up @@ -457,11 +457,11 @@ static Eterm flatmap_from_validated_list(Process *p, Eterm list, Eterm fill_valu

if (unused_size) {
/* the key tuple is embedded in the heap
* write a bignum to clear it.
* write a heap filler to clear it.
*/
/* release values as normal since they are on the top of the heap */

ks[size] = make_pos_bignum_header(unused_size - 1);
erts_write_heap_filler(ks + size, unused_size);
HRelease(p, vs + size + unused_size, vs + size);
}

Expand Down Expand Up @@ -1384,8 +1384,8 @@ static Eterm flatmap_merge(Process *p, Eterm map1, Eterm map2) {
hp_release = thp - unused_size;
}
else {
/* Unused values are embedded in the heap, write bignum to clear them */
*vs = make_pos_bignum_header(unused_size - 1);
/* Unused values are embedded in the heap, write filler to clear them */
erts_write_heap_filler(vs, unused_size);
/* Release unused keys */
hp_release = ks;
}
Expand Down Expand Up @@ -2220,7 +2220,7 @@ Eterm erts_maps_put(Process *p, Eterm key, Eterm value, Eterm map) {
* this will work out fine once we get the size word
* in the header.
*/
*shp = make_pos_bignum_header(0);
erts_write_heap_filler(shp, 1);
return res;

found_key:
Expand Down
8 changes: 8 additions & 0 deletions erts/emulator/beam/erl_term.h
Original file line number Diff line number Diff line change
Expand Up @@ -1463,8 +1463,16 @@ do { \
#define ET_ASSERT(expr,file,line) do { } while(0)
#endif

ERTS_GLB_INLINE void erts_write_heap_filler(Eterm *hp, size_t sz);

#if ERTS_GLB_INLINE_INCL_FUNC_DEF

ERTS_GLB_INLINE void erts_write_heap_filler(Eterm *hp, size_t sz)
{
ASSERT(sz > 0);
*hp = make_pos_bignum_header(sz - 1);
}

#if ET_DEBUG
ERTS_GLB_INLINE unsigned tag_val_def(Eterm x, const char *file, unsigned line)
#else
Expand Down
7 changes: 6 additions & 1 deletion erts/emulator/beam/jit/beam_jit_metadata.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -467,7 +467,12 @@ class JitPerfMap {
public:
bool init() {
char name[MAXPATHLEN];
snprintf(name, sizeof(name), "/tmp/perf-%i.map", getpid());
size_t namesz = sizeof(name);

if (erts_sys_explicit_host_getenv("ERL_SYM_MAP_FILE", name, &namesz) !=
1) {
snprintf(name, sizeof(name), "/tmp/perf-%i.map", getpid());
}
file = fopen(name, "w");
if (!file) {
int saved_errno = errno;
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/sys.h
Original file line number Diff line number Diff line change
Expand Up @@ -863,7 +863,7 @@ int erts_sys_explicit_8bit_putenv(char *key, char *value);

/* This is identical to erts_sys_explicit_8bit_getenv but falls down to the
* host OS implementation instead of erts_osenv. */
int erts_sys_explicit_host_getenv(char *key, char *value, size_t *size);
int erts_sys_explicit_host_getenv(const char *key, char *value, size_t *size);

const erts_osenv_t *erts_sys_rlock_global_osenv(void);
void erts_sys_runlock_global_osenv(void);
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/sys/unix/sys_env.c
Original file line number Diff line number Diff line change
Expand Up @@ -87,7 +87,7 @@ int erts_sys_explicit_8bit_getenv(char *key, char *value, size_t *size) {
return result;
}

int erts_sys_explicit_host_getenv(char *key, char *value, size_t *size) {
int erts_sys_explicit_host_getenv(const char *key, char *value, size_t *size) {
char *orig_value;
size_t length;

Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/sys/win32/sys_env.c
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ void erts_sys_rwunlock_global_osenv() {
erts_rwmtx_rwunlock(&sysenv_rwmtx);
}

int erts_sys_explicit_host_getenv(char *key, char *value, size_t *size) {
int erts_sys_explicit_host_getenv(const char *key, char *value, size_t *size) {
size_t new_size = GetEnvironmentVariableA(key, value, (DWORD)*size);

if(new_size == 0 && GetLastError() == ERROR_ENVVAR_NOT_FOUND) {
Expand Down
11 changes: 4 additions & 7 deletions erts/etc/unix/cerl.src
Original file line number Diff line number Diff line change
Expand Up @@ -387,14 +387,11 @@ if [ "x$GDB" = "x" ]; then
if [ $EMU_NAME = "beam.valgrind.smp" ] && [ "x${VALGRIND_LOG_DIR}" != "x" ]; then
# Always enable `perf` support as we use the same symbol map
emu_xargs="$emu_xargs -JPperf true "
set -m
$taskset1 valgrind $valgrind_xml $valgrind_log $vgflags $BINDIR/$EMU_NAME $sched_arg $emu_xargs "$@" &
VG_PID=$!
fg
export ERL_SYM_MAP_FILE="/tmp/cerl.valgrind.$$.map"
$taskset1 valgrind $valgrind_xml $valgrind_log $vgflags $BINDIR/$EMU_NAME $sched_arg $emu_xargs "$@"
VG_EXIT=$?
set +m
if [ -f /tmp/perf-$VG_PID.map ]; then
$ERL_TOP/scripts/valgrind_beamasm_update.escript $valgrind_log_file /tmp/perf-$VG_PID.map
if [ -f $ERL_SYM_MAP_FILE ]; then
$ERL_TOP/scripts/valgrind_beamasm_update.escript $valgrind_log_file $ERL_SYM_MAP_FILE
fi
exit $VG_EXIT
else
Expand Down

0 comments on commit 39d5282

Please sign in to comment.