Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
16 changes: 16 additions & 0 deletions erts/emulator/beam/atom.h
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,7 @@ extern IndexTable erts_atom_table;
ERTS_GLB_INLINE Atom* atom_tab(Uint i);
ERTS_GLB_INLINE int erts_is_atom_utf8_bytes(byte *text, size_t len, Eterm term);
ERTS_GLB_INLINE int erts_is_atom_str(const char *str, Eterm term, int is_latin1);
ERTS_GLB_INLINE int erts_is_atom_index_ok(Uint ix);

const byte *erts_atom_get_name(const Atom *atom);

Expand Down Expand Up @@ -119,6 +120,21 @@ ERTS_GLB_INLINE int erts_is_atom_str(const char *str, Eterm term, int is_latin1)
return *s == '\0';
}

ERTS_GLB_INLINE int erts_is_atom_index_ok(Uint ix)
{
/*
* This is technincally a thread-unsafe read, but we assume
* + the hardware will get us a constistent integer value even during
* concurrent writes.
* + the tested 'ix' (if ok) comes from an earlier read of 'entries'
* and 'entries' is never decremented.
*
* So we don't care if we race and miss some unrelated increments.
*/
return ix < (Uint)erts_atom_table.entries;
}


#endif

typedef enum {
Expand Down
13 changes: 6 additions & 7 deletions erts/emulator/beam/bif.c
Original file line number Diff line number Diff line change
Expand Up @@ -480,7 +480,6 @@ demonitor(Process *c_p, Eterm ref, Eterm *multip)
}
case ERTS_ML_STATE_ALIAS_ONCE:
case ERTS_ML_STATE_ALIAS_DEMONITOR:
/* fall through... */
default:
erts_monitor_tree_delete(&ERTS_P_MONITORS(c_p), mon);
if (mon->flags & ERTS_ML_FLG_PRIO_ML)
Expand Down Expand Up @@ -641,8 +640,7 @@ BIF_RETTYPE demonitor_2(BIF_ALIST_2)
BIF_TRAP3(flush_monitor_messages_trap, BIF_P,
BIF_ARG_1, multi, res);
}
/* Fall through... */

ERTS_FALLTHROUGH();
case am_true:
if (multi == am_true && flush)
goto flush_messages;
Expand Down Expand Up @@ -1136,12 +1134,13 @@ BIF_RETTYPE erts_internal_spawn_request_4(BIF_ALIST_4)

badarg:
BIF_RET(am_badarg);

system_limit:
error = am_system_limit;
goto send_error;

badopt:
error = am_badopt;
/* fall through... */
send_error: {
Eterm ref = erts_make_ref(BIF_P);
if (!(so.flags & SPO_NO_EMSG))
Expand Down Expand Up @@ -2208,7 +2207,7 @@ BIF_RETTYPE process_flag_2(BIF_ALIST_2)
BIF_RET(old_value);
}
}
/* Fall through and try process_flag_aux() ... */
/* Continue and try process_flag_aux() ... */
}

old_value = process_flag_aux(BIF_P, NULL, BIF_ARG_1, BIF_ARG_2);
Expand Down Expand Up @@ -2397,7 +2396,7 @@ static Sint remote_send(Process *p, DistEntry *dep,
res = 0;
break;
}
/* Fall through... */
ERTS_FALLTHROUGH();
case ERTS_DSIG_PREP_PENDING: {

code = erts_dsig_send_msg(&ctx, to, full_to, msg, prio);
Expand Down Expand Up @@ -2571,7 +2570,7 @@ do_send(Process *p, Eterm to, Eterm msg, Eterm return_term, Eterm *refp,
ret_val = SEND_YIELD_RETURN;
break;
}
/* Fall through */
ERTS_FALLTHROUGH();
case ERTS_PORT_OP_SCHEDULED:
if (is_not_nil(*refp)) {
ASSERT(is_internal_ordinary_ref(*refp));
Expand Down
5 changes: 2 additions & 3 deletions erts/emulator/beam/copy.c
Original file line number Diff line number Diff line change
Expand Up @@ -705,7 +705,6 @@ Eterm copy_struct_x(Eterm obj, Uint sz, Eterm** hpp, ErlOffHeap* off_heap,
break;
}
argp = hp++;
/* Fall through */

L_copy_list:
tailp = argp;
Expand Down Expand Up @@ -916,7 +915,7 @@ Eterm copy_struct_x(Eterm obj, Uint sz, Eterm** hpp, ErlOffHeap* off_heap,
erts_refc_inc(&mreft->mb->intern.refc, 2);
goto L_off_heap_node_container_common;
}
/* Fall through... */
ERTS_FALLTHROUGH();
default:
i = thing_arityval(hdr)+1;
hbot -= i;
Expand Down Expand Up @@ -1723,7 +1722,7 @@ Uint copy_shared_perform_x(Eterm obj, Uint size, erts_shcopy_t *info,
erts_refc_inc(&mreft->mb->intern.refc, 2);
goto off_heap_node_container_common;
}
/* Fall through... */
ERTS_FALLTHROUGH();
default:
sz = thing_arityval(hdr);
*resp = make_boxed(hp);
Expand Down
11 changes: 5 additions & 6 deletions erts/emulator/beam/dist.c
Original file line number Diff line number Diff line change
Expand Up @@ -2131,7 +2131,7 @@ int erts_net_message(Port *prt,
}
}

/* fall through, the first fragment in the sequence was the last fragment */
/* The first fragment in the sequence was also the last fragment */
ERTS_FALLTHROUGH();
case ERTS_PREP_DIST_EXT_FRAG_CONT: {
DistSeqNode *seq;
Expand Down Expand Up @@ -2461,8 +2461,7 @@ int erts_net_message(Port *prt,
if (tuple_arity != 5) {
goto invalid_message;
}

/* Fall through ... */
ERTS_FALLTHROUGH();
case DOP_REG_SEND:
/* {DOP_REG_SEND, From, Cookie, ToName} -- Message */
/* {DOP_REG_SEND_TT, From, Cookie, ToName, TraceToken} -- Message */
Expand Down Expand Up @@ -6091,7 +6090,7 @@ BIF_RETTYPE erts_internal_dist_spawn_request_4(BIF_ALIST_4)
erts_de_runlock(dep);
goto notsup;
}
/* Fall through... */
ERTS_FALLTHROUGH();
case ERTS_DSIG_PREP_PENDING: {
int inserted;
ErtsMonitorData *mdp;
Expand Down Expand Up @@ -6200,9 +6199,9 @@ BIF_RETTYPE erts_internal_dist_spawn_request_4(BIF_ALIST_4)
notsup:
error = am_notsup;
goto send_error;

badopt:
error = am_badopt;
/* fall through... */
send_error:
ASSERT(is_value(ok_result));
if (!(monitor_oflags & ERTS_ML_FLG_SPAWN_NO_EMSG))
Expand Down Expand Up @@ -6578,7 +6577,7 @@ monitor_node(Process* p, Eterm Node, Eterm Bool, Eterm Options)
erts_de_runlock(dep);
goto do_trap;
}
/*fall through*/
ERTS_FALLTHROUGH();
case ERTS_DSIG_PREP_CONNECTED: {
ErtsMonitor *mon;
ErtsMonitorDataExtended *mdep;
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/emu/emu_load.c
Original file line number Diff line number Diff line change
Expand Up @@ -948,7 +948,7 @@ int beam_load_emit_op(LoaderState *stp, BeamOp *tmp_op) {
break;
case TAG_n:
ASSERT(tmp_op->a[arg].val == NIL);
/* ! Fall through ! */
ERTS_FALLTHROUGH();
case TAG_a:
code[ci++] = tmp_op->a[arg].val;
break;
Expand Down
9 changes: 4 additions & 5 deletions erts/emulator/beam/erl_arith.c
Original file line number Diff line number Diff line change
Expand Up @@ -260,7 +260,6 @@ erts_shift(Process* p, Eterm arg1, Eterm arg2, int right)
}
BIF_ERROR(p, SYSTEM_LIMIT);
}
/* Fall through if the left argument is not an integer. */
}
}
BIF_ERROR(p, BADARITH);
Expand Down Expand Up @@ -888,7 +887,7 @@ erts_mul_add(Process* p, Eterm arg1, Eterm arg2, Eterm arg3, Eterm* pp)
break;
}
big_arg1 = small_to_big(signed_val(big_arg1), tmp_big1);
/* Fall through */
ERTS_FALLTHROUGH();
case TAG_PRIMARY_BOXED:
hdr = *boxed_val(big_arg1);
switch ((hdr & _TAG_HEADER_MASK) >> _TAG_PRIMARY_SIZE) {
Expand All @@ -900,7 +899,7 @@ erts_mul_add(Process* p, Eterm arg1, Eterm arg2, Eterm arg3, Eterm* pp)
break;
}
big_arg2 = small_to_big(signed_val(big_arg2), tmp_big2);
/* Fall through */
ERTS_FALLTHROUGH();
case TAG_PRIMARY_BOXED:
hdr = *boxed_val(big_arg2);
switch ((hdr & _TAG_HEADER_MASK) >> _TAG_PRIMARY_SIZE) {
Expand All @@ -912,7 +911,7 @@ erts_mul_add(Process* p, Eterm arg1, Eterm arg2, Eterm arg3, Eterm* pp)
break;
}
big_arg3 = small_to_big(signed_val(big_arg3), tmp_big3);
/* Fall through */
ERTS_FALLTHROUGH();
case TAG_PRIMARY_BOXED:
hdr = *boxed_val(big_arg3);
switch ((hdr & _TAG_HEADER_MASK) >> _TAG_PRIMARY_SIZE) {
Expand Down Expand Up @@ -1131,7 +1130,7 @@ int erts_int_div_rem(Process* p, Eterm arg1, Eterm arg2, Eterm *q, Eterm *r)
ASSERT(rhs == make_small(-1));
lhs = small_to_big(signed_val(lhs), tmp_big1);

/* ! Fall through ! */
ERTS_FALLTHROUGH();
case BIG_SMALL:
rhs = small_to_big(signed_val(rhs), tmp_big2);
break;
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_bif_lists.c
Original file line number Diff line number Diff line change
Expand Up @@ -519,7 +519,7 @@ static void subtract_ctx_move(ErtsSubtractContext *from,
break;
case SUBTRACT_STAGE_SET_FINISH:
uses_result_cdr = 1;
/* FALL THROUGH */
ERTS_FALLTHROUGH();
case SUBTRACT_STAGE_SET_BUILD:
to->u.rhs_set.alloc_start = from->u.rhs_set.alloc_start;
to->u.rhs_set.alloc = from->u.rhs_set.alloc;
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_bif_port.c
Original file line number Diff line number Diff line change
Expand Up @@ -220,7 +220,7 @@ BIF_RETTYPE erts_internal_port_command_3(BIF_ALIST_3)
break;
case ERTS_PORT_OP_BUSY_SCHEDULED:
ASSERT(!(flags & ERTS_PORT_SIG_FLG_FORCE));
/* Fall through... */
ERTS_FALLTHROUGH();
case ERTS_PORT_OP_SCHEDULED:
ASSERT(is_internal_ordinary_ref(ref));
/* Signal order preserved by reply... */
Expand Down
2 changes: 0 additions & 2 deletions erts/emulator/beam/erl_bif_re.c
Original file line number Diff line number Diff line change
Expand Up @@ -1767,7 +1767,6 @@ re_run(Process *p, Eterm arg1, Eterm arg2, Eterm arg3, bool first)
case PCRE2_ERROR_UTF8_ERR20:
case PCRE2_ERROR_UTF8_ERR21:
BUMP_ALL_REDS(p); /* Unknown amount of work done... */
/* Fall through for badarg... */
ERTS_FALLTHROUGH();

case PCRE2_ERROR_BADOFFSET:
Expand Down Expand Up @@ -1886,7 +1885,6 @@ static BIF_RETTYPE re_match_trap(BIF_ALIST_3)
case PCRE2_ERROR_UTF8_ERR20:
case PCRE2_ERROR_UTF8_ERR21:
BUMP_ALL_REDS(BIF_P); /* Unknown amount of work done... */
/* Fall through for badarg... */
ERTS_FALLTHROUGH();

case PCRE2_ERROR_BADOFFSET:
Expand Down
4 changes: 2 additions & 2 deletions erts/emulator/beam/erl_bif_trace.c
Original file line number Diff line number Diff line change
Expand Up @@ -2666,7 +2666,7 @@ erts_finish_breakpointing(void)
}
/* Neither local or global set for event tracing */
}
/* Nothing to do here. Fall through to next stage. */
/* Nothing to do here. Continue to next stage. */
finish_bp.current++;
ERTS_FALLTHROUGH();
case 1:
Expand Down Expand Up @@ -2703,7 +2703,7 @@ erts_finish_breakpointing(void)
if (finish_bp.local || finish_bp.global) {
return 1;
}
/* Nothing done here. Fall through to next stage. */
/* Nothing done here. Continue to next stage. */
finish_bp.current++;
ERTS_FALLTHROUGH();
case 3:
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_db.c
Original file line number Diff line number Diff line change
Expand Up @@ -1493,7 +1493,7 @@ do_update_counter(Process *p, DbTable* tb,
else if (is_not_small(warp)) {
goto finalize;
}
/* Fall through */
ERTS_FALLTHROUGH();
case 2:
if (!is_small(tpl[1])) {
goto finalize;
Expand Down
8 changes: 4 additions & 4 deletions erts/emulator/beam/erl_db_util.c
Original file line number Diff line number Diff line change
Expand Up @@ -2050,7 +2050,7 @@ Binary *db_match_compile(Eterm *matchexpr,
#endif

/*
* Fall through to cleanup code, but context.save should not be free'd
* Continue to cleanup code, but context.save should not be free'd
*/
context.save = NULL;
error: /* Here is were we land when compilation failed. */
Expand Down Expand Up @@ -5606,8 +5606,8 @@ static DMCRet dmc_expr(DMCContext *context,
!= retOk)
return ret;
break;
}
/* Fall through */
}
ERTS_FALLTHROUGH();
default:
simple_term:
*constant = true;
Expand Down Expand Up @@ -5861,7 +5861,7 @@ static Uint my_size_object(Eterm t, bool is_hashmap_node)
}
break;
}
/* fall through */
ERTS_FALLTHROUGH();
default:
sum += size_object(t);
break;
Expand Down
Loading
Loading