Skip to content

Commit

Permalink
erts: Introduce global literals
Browse files Browse the repository at this point in the history
`erl_global_literals` has been redesigned to be more dynamic, allowing any global literal to be created, rather than a small set of literals. Lambdas for exports will now use this interface. The next commit will change atoms to also do that.
  • Loading branch information
lucioleKi committed Jul 12, 2024
1 parent c35ac05 commit e927b0b
Show file tree
Hide file tree
Showing 16 changed files with 224 additions and 167 deletions.
8 changes: 5 additions & 3 deletions erts/emulator/beam/beam_file.c
Original file line number Diff line number Diff line change
Expand Up @@ -522,7 +522,7 @@ static int parse_line_chunk(BeamFile *beam, IFF_Chunk *chunk) {
Eterm name, suffix;
Eterm *hp;

suffix = erts_get_global_literal(ERTS_LIT_ERL_FILE_SUFFIX);
suffix = ERTS_GLOBAL_LIT_ERL_FILE_SUFFIX;

hp = name_heap;
name = erts_atom_to_string(&hp, beam->module, suffix);
Expand Down Expand Up @@ -1312,11 +1312,13 @@ int iff_read_chunk(IFF_File *iff, Uint id, IFF_Chunk *chunk)
void beamfile_init(void) {
Eterm suffix;
Eterm *hp;
struct erl_off_heap_header **ohp;

hp = erts_alloc_global_literal(ERTS_LIT_ERL_FILE_SUFFIX, 8);
hp = erts_global_literal_allocate(8, &ohp);
suffix = erts_bin_bytes_to_list(NIL, hp, (byte*)".erl", 4, 0);

erts_register_global_literal(ERTS_LIT_ERL_FILE_SUFFIX, suffix);
erts_global_literal_register(&suffix, hp, 8);
ERTS_GLOBAL_LIT_ERL_FILE_SUFFIX = suffix;
}

/* * * * * * * */
Expand Down
8 changes: 5 additions & 3 deletions erts/emulator/beam/dist.c
Original file line number Diff line number Diff line change
Expand Up @@ -1146,6 +1146,7 @@ void init_dist(void)
Eterm *hp_start, *hp, **hpp = NULL, tuple;
Uint sz = 0, *szp = &sz;
while (1) {
struct erl_off_heap_header **ohp;
/*
* Sync with dist_util.erl:
*
Expand All @@ -1162,10 +1163,11 @@ void init_dist(void)
if (hpp) {
ASSERT(is_value(tuple));
ASSERT(hp == hp_start + sz);
erts_register_global_literal(ERTS_LIT_DFLAGS_RECORD, tuple);
erts_global_literal_register(&tuple, hp, sz);
ERTS_GLOBAL_LIT_DFLAGS_RECORD = tuple;
break;
}
hp = hp_start = erts_alloc_global_literal(ERTS_LIT_DFLAGS_RECORD, sz);
hp = hp_start = erts_global_literal_allocate(sz, &ohp);
hpp = &hp;
szp = NULL;
}
Expand Down Expand Up @@ -5423,7 +5425,7 @@ BIF_RETTYPE erts_internal_get_dflags_0(BIF_ALIST_0)
szp = NULL;
}
}
return erts_get_global_literal(ERTS_LIT_DFLAGS_RECORD);
return ERTS_GLOBAL_LIT_DFLAGS_RECORD;
}

BIF_RETTYPE erts_internal_get_creation_0(BIF_ALIST_0)
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/emu/generators.tab
Original file line number Diff line number Diff line change
Expand Up @@ -563,7 +563,7 @@ gen.new_small_map_lit(Dst, Live, Size, Rest) {

tmp = thp = erts_alloc(ERTS_ALC_T_LOADER_TMP, ((size == 0 ? 0 : 1) + size/2) * sizeof(*tmp));
if (size == 0) {
keys = erts_get_global_literal(ERTS_LIT_EMPTY_TUPLE);
keys = ERTS_GLOBAL_LIT_EMPTY_TUPLE;
} else {
keys = make_tuple(thp);
*thp++ = make_arityval(size/2);
Expand Down
4 changes: 2 additions & 2 deletions erts/emulator/beam/erl_alloc_util.c
Original file line number Diff line number Diff line change
Expand Up @@ -7744,7 +7744,7 @@ static int gather_ahist_append_result(hist_tree_t *node, void *arg, Sint reds)

hp = erts_produce_heap(&state->msg_factory, heap_size, 0);
if (state->hist_slot_count == 0) {
histogram_tuple = erts_get_global_literal(ERTS_LIT_EMPTY_TUPLE);
histogram_tuple = ERTS_GLOBAL_LIT_EMPTY_TUPLE;
} else {
hp[0] = make_arityval(state->hist_slot_count);

Expand Down Expand Up @@ -8088,7 +8088,7 @@ static void gather_cinfo_append_result(gather_cinfo_t *state,
}
}
if (state->hist_slot_count == 0) {
histogram_tuple = erts_get_global_literal(ERTS_LIT_EMPTY_TUPLE);
histogram_tuple = ERTS_GLOBAL_LIT_EMPTY_TUPLE;
} else {
hp[0] = make_arityval(state->hist_slot_count);
for (ix = 0; ix < state->hist_slot_count; ix++) {
Expand Down
16 changes: 10 additions & 6 deletions erts/emulator/beam/erl_bif_info.c
Original file line number Diff line number Diff line change
Expand Up @@ -2985,7 +2985,7 @@ BIF_RETTYPE system_info_1(BIF_ALIST_1)
NIL));
}
else if (BIF_ARG_1 == am_os_type) {
BIF_RET(erts_get_global_literal(ERTS_LIT_OS_TYPE));
BIF_RET(ERTS_GLOBAL_LIT_OS_TYPE);
}
else if (BIF_ARG_1 == am_allocator) {
BIF_RET(erts_allocator_options((void *) BIF_P));
Expand All @@ -3001,7 +3001,7 @@ BIF_RETTYPE system_info_1(BIF_ALIST_1)
BIF_RET(erts_alloc_util_allocators((void *) BIF_P));
}
else if (BIF_ARG_1 == am_os_version) {
BIF_RET(erts_get_global_literal(ERTS_LIT_OS_VERSION));
BIF_RET(ERTS_GLOBAL_LIT_OS_VERSION);
}
else if (BIF_ARG_1 == am_version) {
int n = sys_strlen(ERLANG_VERSION);
Expand Down Expand Up @@ -6265,21 +6265,25 @@ static void os_info_init(void)
char* buf = erts_alloc(ERTS_ALC_T_TMP, 1024); /* More than enough */
Eterm* hp;
Eterm tuple;
struct erl_off_heap_header **ohp;

os_flavor(buf, 1024);
flav = erts_atom_put((byte *) buf, sys_strlen(buf), ERTS_ATOM_ENC_LATIN1, 1);
erts_free(ERTS_ALC_T_TMP, (void *) buf);
hp = erts_alloc_global_literal(ERTS_LIT_OS_TYPE, 3);

hp = erts_global_literal_allocate(3, &ohp);
tuple = TUPLE2(hp, type, flav);
erts_register_global_literal(ERTS_LIT_OS_TYPE, tuple);
erts_global_literal_register(&tuple, hp, 3);
ERTS_GLOBAL_LIT_OS_TYPE = tuple;

hp = erts_alloc_global_literal(ERTS_LIT_OS_VERSION, 4);
hp = erts_global_literal_allocate(4, &ohp);
os_version(&major, &minor, &build);
tuple = TUPLE3(hp,
make_small(major),
make_small(minor),
make_small(build));
erts_register_global_literal(ERTS_LIT_OS_VERSION, tuple);
erts_global_literal_register(&tuple, hp, 4);
ERTS_GLOBAL_LIT_OS_VERSION = tuple;
}

void
Expand Down
160 changes: 131 additions & 29 deletions erts/emulator/beam/erl_global_literals.c
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
/*
* %CopyrightBegin%
*
* Copyright Ericsson AB 2020-2021. All Rights Reserved.
* Copyright Ericsson AB 2020-2024. All Rights Reserved.
*
* Licensed under the Apache License, Version 2.0 (the "License");
* you may not use this file except in compliance with the License.
Expand All @@ -25,51 +25,153 @@
#include "sys.h"
#include "global.h"
#include "erl_global_literals.h"
#include "erl_mmap.h"

struct literal {
Eterm term;
ErtsLiteralArea* area;
};

static struct literal literals[ERTS_NUM_GLOBAL_LITERALS];
#define GLOBAL_LITERAL_INITIAL_SIZE (1<<16)
#define GLOBAL_LITERAL_EXPAND_SIZE 512


/*
* Global Constant Literals
*/
Eterm ERTS_WRITE_UNLIKELY(ERTS_GLOBAL_LIT_OS_TYPE);
Eterm ERTS_WRITE_UNLIKELY(ERTS_GLOBAL_LIT_OS_VERSION);
Eterm ERTS_WRITE_UNLIKELY(ERTS_GLOBAL_LIT_DFLAGS_RECORD);
Eterm ERTS_WRITE_UNLIKELY(ERTS_GLOBAL_LIT_ERL_FILE_SUFFIX);
Eterm ERTS_WRITE_UNLIKELY(ERTS_GLOBAL_LIT_EMPTY_TUPLE);

/* This lock is taken in the beginning of erts_global_literal_allocate,
* released at the end of erts_global_literal_register. It protects the
* allocated literal chunk, and the heap pointer from concurrent access until
* the literal tag is set.
*/
erts_mtx_t global_literal_lock;

/* Bump allocator for global literal chunks, allocating them in
* reasonably large chunks to simplify crash dumping and avoid fragmenting the
* literal heap too much.
*
* This is protected by the global literal lock. */
struct global_literal_chunk {
struct global_literal_chunk *next;
Eterm *hp;

ErtsLiteralArea area;
} *global_literal_chunk = NULL;



Eterm* erts_alloc_global_literal(Uint index, Uint sz)
ErtsLiteralArea *erts_global_literal_iterate_area(ErtsLiteralArea *prev)
{
ErtsLiteralArea* area;
Uint area_sz;

ASSERT(index < ERTS_NUM_GLOBAL_LITERALS);
area_sz = sizeof(ErtsLiteralArea) + (sz-1)*sizeof(Eterm);
area = erts_alloc(ERTS_ALC_T_LITERAL, area_sz);
area->end = area->start + sz;
literals[index].area = area;
return area->start;
struct global_literal_chunk *next;

ASSERT(ERTS_IS_CRASH_DUMPING);

if (prev != NULL) {
struct global_literal_chunk *chunk = ErtsContainerStruct(prev,
struct global_literal_chunk,
area);
next = chunk->next;

if (next == NULL) {
return NULL;
}
} else {
next = global_literal_chunk;
}

next->area.end = next->hp;
return &next->area;
}

void erts_register_global_literal(Uint index, Eterm term)
static void expand_shared_global_literal_area(Uint heap_size)
{
Eterm* start;
const size_t size = sizeof(struct global_literal_chunk) +
(heap_size - 1) * sizeof(Eterm);
struct global_literal_chunk *chunk;

#ifndef DEBUG
chunk = (struct global_literal_chunk *) erts_alloc(ERTS_ALC_T_LITERAL, size);
#else
/* erts_mem_guard requires the memory area to be page aligned. Overallocate
* and align the address to ensure that is the case. */
UWord address;
address = (UWord) erts_alloc(ERTS_ALC_T_LITERAL, size + sys_page_size * 2);
address = (address + (sys_page_size - 1)) & ~(sys_page_size - 1);
chunk = (struct global_literal_chunk *) address;
#endif

chunk->hp = &chunk->area.start[0];
chunk->area.end = &chunk->hp[heap_size];
chunk->area.off_heap = NULL;
chunk->next = global_literal_chunk;

ASSERT(index < ERTS_NUM_GLOBAL_LITERALS);
start = literals[index].area->start;
erts_set_literal_tag(&term, start, literals[index].area->end - start);
literals[index].term = term;
global_literal_chunk = chunk;
}

Eterm erts_get_global_literal(Uint index)
Eterm *erts_global_literal_allocate(Uint heap_size, struct erl_off_heap_header ***ohp)
{
ASSERT(index < ERTS_NUM_GLOBAL_LITERALS);
return literals[index].term;
Eterm *hp;

erts_mtx_lock(&global_literal_lock);

ASSERT((global_literal_chunk->hp <= global_literal_chunk->area.end &&
global_literal_chunk->hp >= global_literal_chunk->area.start) );
if (global_literal_chunk->area.end - global_literal_chunk->hp <= heap_size) {
expand_shared_global_literal_area(heap_size + GLOBAL_LITERAL_EXPAND_SIZE);
}

*ohp = &global_literal_chunk->area.off_heap;
hp = global_literal_chunk->hp;
global_literal_chunk->hp += heap_size;

#ifdef DEBUG
{
struct global_literal_chunk *chunk = global_literal_chunk;
erts_mem_guard(&chunk->area.start[0],
(chunk->area.end - &chunk->area.start[0]) * sizeof(Eterm),
1,
1);
}
#endif

return hp;
}

ErtsLiteralArea* erts_get_global_literal_area(Uint index)
{
ASSERT(index < ERTS_NUM_GLOBAL_LITERALS);
return literals[index].area;
void erts_global_literal_register(Eterm *variable, Eterm *hp, Uint heap_size) {
erts_set_literal_tag(variable, hp, heap_size);

#ifdef DEBUG
{
struct global_literal_chunk *chunk = global_literal_chunk;
erts_mem_guard(&chunk->area.start[0],
(chunk->area.end - &chunk->area.start[0]) * sizeof(Eterm),
1,
0);
}
#endif

erts_mtx_unlock(&global_literal_lock);
}

static void init_empty_tuple(void) {
struct erl_off_heap_header **ohp;
Eterm* hp = erts_global_literal_allocate(2, &ohp);
Eterm tuple;
hp[0] = make_arityval_zero();
hp[1] = make_arityval_zero();
tuple = make_tuple(hp);
erts_global_literal_register(&tuple, hp, 2);
ERTS_GLOBAL_LIT_EMPTY_TUPLE = tuple;
}

void
init_global_literals(void)
{
erts_mtx_init(&global_literal_lock, "global_literals", NIL,
ERTS_LOCK_FLAGS_PROPERTY_STATIC | ERTS_LOCK_FLAGS_CATEGORY_GENERIC);

expand_shared_global_literal_area(GLOBAL_LITERAL_INITIAL_SIZE);
init_empty_tuple();
}
43 changes: 31 additions & 12 deletions erts/emulator/beam/erl_global_literals.h
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
/*
* %CopyrightBegin%
*
* Copyright Ericsson AB 1996-2021. All Rights Reserved.
* Copyright Ericsson AB 1996-2024. All Rights Reserved.
*
* Licensed under the Apache License, Version 2.0 (the "License");
* you may not use this file except in compliance with the License.
Expand All @@ -18,22 +18,41 @@
* %CopyrightEnd%
*/

/* Global literals are used to store Erlang terms that are never modified or
* deleted. They are commonly-used constants at compile or run-time. This is
* similar in spirit to persistent_term but for internal usage.
*
* Examples include lambdas associated with export entries, the bitstring
* representation of atoms, and certain constants.
*/

#ifndef __ERL_GLOBAL_LITERALS_H__
#define __ERL_GLOBAL_LITERALS_H__

#define ERTS_LIT_OS_TYPE 0
#define ERTS_LIT_OS_VERSION 1
#define ERTS_LIT_DFLAGS_RECORD 2
#define ERTS_LIT_EMPTY_TUPLE 3
#define ERTS_LIT_ERL_FILE_SUFFIX 4
extern Eterm ERTS_GLOBAL_LIT_OS_TYPE;
extern Eterm ERTS_GLOBAL_LIT_OS_VERSION;
extern Eterm ERTS_GLOBAL_LIT_DFLAGS_RECORD;
extern Eterm ERTS_GLOBAL_LIT_ERL_FILE_SUFFIX;
extern Eterm ERTS_GLOBAL_LIT_EMPTY_TUPLE;

#define ERTS_NUM_GLOBAL_LITERALS 5
/* Initializes global literals. Note that the literals terms mentioned in the
* examples above may be created elsewhere, and are only kept here for clarity.
*/
void init_global_literals(void);

extern Eterm ERTS_GLOBAL_LIT_EMPTY_TUPLE;
/* Allocates space for global literals. Users must call erts_global_literal_register
* when done creating the literal.
*/
Eterm *erts_global_literal_allocate(Uint sz, struct erl_off_heap_header ***ohp);

Eterm* erts_alloc_global_literal(Uint index, Uint sz);
void erts_register_global_literal(Uint index, Eterm term);
Eterm erts_get_global_literal(Uint index);
ErtsLiteralArea* erts_get_global_literal_area(Uint index);
/* Registers the pointed-to term as a global literal. Must be called for terms
* allocated using erts_global_literal_allocate.*/
void erts_global_literal_register(Eterm *variable, Eterm *hp, Uint heap_size);

/* Iterates between global literal areas. Can only be used when crash dumping.
* Iteration is started by passing NULL, then successively calling this function
* until it returns NULL.
*/
ErtsLiteralArea *erts_global_literal_iterate_area(ErtsLiteralArea *prev);

#endif
Loading

0 comments on commit e927b0b

Please sign in to comment.