Skip to content

Commit

Permalink
refactored atom, export, and global_literals
Browse files Browse the repository at this point in the history
  • Loading branch information
lucioleKi committed Jul 2, 2024
1 parent 9fb0b05 commit 8932419
Show file tree
Hide file tree
Showing 15 changed files with 206 additions and 231 deletions.
127 changes: 56 additions & 71 deletions erts/emulator/beam/atom.c
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@
#include "global.h"
#include "hash.h"
#include "atom.h"
#include "erl_global_literals.h"


#define ATOM_SIZE 3000
Expand All @@ -48,19 +49,19 @@ static erts_rwmtx_t atom_table_lock;
static erts_atomic_t atom_put_ops;
#endif

/* Functions for allocating space for the ext of atoms. We do not
* use malloc for each atom to prevent excessive memory fragmentation
*/
// /* Functions for allocating space for the ext of atoms. We do not
// * use malloc for each atom to prevent excessive memory fragmentation
// */

typedef struct _atom_text {
struct _atom_text* next;
unsigned char text[ATOM_TEXT_SIZE];
} AtomText;
// typedef struct _atom_text {
// struct _atom_text* next;
// unsigned char text[ATOM_TEXT_SIZE];
// } AtomText;

static AtomText* text_list; /* List of text buffers */
static byte *atom_text_pos;
static byte *atom_text_end;
static Uint reserved_atom_space; /* Total amount of atom text space */
// static AtomText* text_list; /* List of text buffers */
// static byte *atom_text_pos;
// static byte *atom_text_end;
// static Uint reserved_atom_space; /* Total amount of atom text space */
static Uint atom_space; /* Amount of atom text space used */

/*
Expand All @@ -81,44 +82,8 @@ void atom_info(fmtfn_t to, void *to_arg)
atom_read_unlock();
}

/*
* Allocate an atom text segment.
*/
static void
more_atom_space(void)
{
AtomText* ptr;

ptr = (AtomText*) erts_alloc(ERTS_ALC_T_ATOM_TXT, sizeof(AtomText));

ptr->next = text_list;
text_list = ptr;

atom_text_pos = ptr->text;
atom_text_end = atom_text_pos + ATOM_TEXT_SIZE;
reserved_atom_space += sizeof(AtomText);

VERBOSE(DEBUG_SYSTEM,("Allocated %d atom space\n",ATOM_TEXT_SIZE));
}

/*
* Allocate string space within an atom text segment.
*/

static byte*
atom_text_alloc(int bytes)
{
byte *res;

ASSERT(bytes <= MAX_ATOM_SZ_LIMIT);
if (atom_text_pos + bytes >= atom_text_end) {
more_atom_space();
}
res = atom_text_pos;
atom_text_pos += bytes;
atom_space += bytes;
return res;
}

/*
* Calculate atom hash value (using the hash algorithm
Expand All @@ -128,7 +93,7 @@ atom_text_alloc(int bytes)
static HashValue
atom_hash(Atom* obj)
{
byte* p = obj->name;
byte* p = obj->u.name;
int len = obj->len;
HashValue h = 0, g;
byte v;
Expand All @@ -150,12 +115,22 @@ atom_hash(Atom* obj)
return h;
}

byte *erts_atom_get_name(Atom *atom)
{
byte *name;
Uint size;
Uint offset;
ERTS_GET_BITSTRING(atom->u.bin, name, size, offset);
(void) size;
(void) offset;
return name;
}

static int
atom_cmp(Atom* tmpl, Atom* obj)
{
if (tmpl->len == obj->len &&
sys_memcmp(tmpl->name, obj->name, tmpl->len) == 0)
sys_memcmp(tmpl->u.name, erts_atom_get_name(obj), tmpl->len) == 0)
return 0;
return 1;
}
Expand All @@ -164,13 +139,29 @@ atom_cmp(Atom* tmpl, Atom* obj)
static Atom*
atom_alloc(Atom* tmpl)
{
Eterm* bin_ptr;
Uint size = 0;
ErtsHeapFactory factory;
ErlOffHeap oh;
struct erl_off_heap_header **literal_ohp;
Atom* obj = (Atom*) erts_alloc(ERTS_ALC_T_ATOM, sizeof(Atom));

obj->name = atom_text_alloc(tmpl->len);
sys_memcpy(obj->name, tmpl->name, tmpl->len);
if (tmpl->len <= ERL_ONHEAP_BINARY_LIMIT) {
size = heap_bits_size(NBITS(tmpl->len));
} else {
size = ERL_REFC_BITS_SIZE;
}
bin_ptr = erts_global_literal_allocate(size, &literal_ohp);
ERTS_INIT_OFF_HEAP(&oh);
oh.first = *literal_ohp;
erts_factory_static_init(&factory, bin_ptr, size, &oh);
*literal_ohp = oh.first;
obj->u.bin = erts_hfact_new_binary_from_data(&factory, 0, tmpl->len, tmpl->u.name);
erts_global_literal_register(&obj->u.bin, bin_ptr, size);
obj->len = tmpl->len;
obj->latin1_chars = tmpl->latin1_chars;
obj->slot.index = -1;
atom_space += tmpl->len;


/*
* Precompute ordinal value of first 3 bytes + 7 bits.
Expand All @@ -186,7 +177,7 @@ atom_alloc(Atom* tmpl)

j = (tmpl->len < 4) ? tmpl->len : 4;
for(i = 0; i < j; ++i)
c[i] = tmpl->name[i];
c[i] = tmpl->u.name[i];
for(; i < 4; ++i)
c[i] = '\0';
obj->ord0 = (c[0] << 23) + (c[1] << 15) + (c[2] << 7) + (c[3] >> 1);
Expand Down Expand Up @@ -293,7 +284,7 @@ erts_atom_put_index(const byte *name, Sint len, ErtsAtomEncoding enc, int trunc)
}

a.len = tlen;
a.name = (byte *) text;
a.u.name = (byte *) text;
atom_read_lock();
aix = index_get(&erts_atom_table, (void*) &a);
atom_read_unlock();
Expand Down Expand Up @@ -333,7 +324,7 @@ erts_atom_put_index(const byte *name, Sint len, ErtsAtomEncoding enc, int trunc)

a.len = tlen;
a.latin1_chars = (Sint16) no_latin1_chars;
a.name = (byte *) text;
a.u.name = (byte *) text;
atom_write_lock();
aix = index_put(&erts_atom_table, (void*) &a);
atom_write_unlock();
Expand Down Expand Up @@ -400,7 +391,7 @@ erts_atom_get(const char *name, Uint len, Eterm* ap, ErtsAtomEncoding enc)

latin1_to_utf8(utf8_copy, sizeof(utf8_copy), (const byte**)&name, &len);

a.name = (byte*)name;
a.u.name = (byte*)name;
a.len = (Sint16)len;
break;
case ERTS_ATOM_ENC_7BIT_ASCII:
Expand All @@ -415,7 +406,7 @@ erts_atom_get(const char *name, Uint len, Eterm* ap, ErtsAtomEncoding enc)
}

a.len = (Sint16)len;
a.name = (byte*)name;
a.u.name = (byte*)name;
break;
case ERTS_ATOM_ENC_UTF8:
if (len > MAX_ATOM_SZ_LIMIT) {
Expand All @@ -427,7 +418,7 @@ erts_atom_get(const char *name, Uint len, Eterm* ap, ErtsAtomEncoding enc)
* name will fail. */

a.len = (Sint16)len;
a.name = (byte*)name;
a.u.name = (byte*)name;
break;
}

Expand All @@ -446,7 +437,7 @@ erts_atom_get_text_space_sizes(Uint *reserved, Uint *used)
if (lock)
atom_read_lock();
if (reserved)
*reserved = reserved_atom_space;
*reserved = atom_space;
if (used)
*used = atom_space;
if (lock)
Expand Down Expand Up @@ -479,33 +470,27 @@ init_atom_table(void)
f.meta_free = (HMFREE_FUN) erts_free;
f.meta_print = (HMPRINT_FUN) erts_print;

atom_text_pos = NULL;
atom_text_end = NULL;
reserved_atom_space = 0;
atom_space = 0;
text_list = NULL;

erts_index_init(ERTS_ALC_T_ATOM_TABLE, &erts_atom_table,
"atom_tab", ATOM_SIZE, erts_atom_table_size, f);
more_atom_space();

/* Ordinary atoms */
for (i = 0; erl_atom_names[i] != 0; i++) {
int ix;
a.len = sys_strlen(erl_atom_names[i]);
a.latin1_chars = a.len;
a.name = (byte*)erl_atom_names[i];
a.u.name = (byte*)erl_atom_names[i];
a.slot.index = i;


#ifdef DEBUG
/* Verify 7-bit ascii */
for (ix = 0; ix < a.len; ix++) {
ASSERT((a.name[ix] & 0x80) == 0);
ASSERT((a.u.name[ix] & 0x80) == 0);
}
#endif
ix = index_put(&erts_atom_table, (void*) &a);
atom_text_pos -= a.len;
atom_space -= a.len;
atom_tab(ix)->name = (byte*)erl_atom_names[i];
(void) ix;
ASSERT(erts_atom_get_name(atom_tab(ix)));
}

}
Expand Down
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
Loading

0 comments on commit 8932419

Please sign in to comment.