From 6598a8c5938d3a5ece730d912234dfd6a2fa459c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Mon, 28 Oct 2024 09:32:43 +0100 Subject: [PATCH 01/10] erts: Annotate all switch fallthroughs --- erts/emulator/beam/beam_bp.c | 6 ++++ erts/emulator/beam/bif.c | 5 +++ erts/emulator/beam/break.c | 44 +++++++++++------------ erts/emulator/beam/copy.c | 5 ++- erts/emulator/beam/dist.c | 11 ++++++ erts/emulator/beam/emu/bs_instrs.tab | 14 ++++---- erts/emulator/beam/erl_arith.c | 30 ++++++++++------ erts/emulator/beam/erl_bif_re.c | 3 +- erts/emulator/beam/erl_bif_trace.c | 2 ++ erts/emulator/beam/erl_bits.c | 42 +++++++++++----------- erts/emulator/beam/erl_db_tree.c | 1 + erts/emulator/beam/erl_gc.c | 6 ++-- erts/emulator/beam/erl_init.c | 4 ++- erts/emulator/beam/erl_map.c | 7 ++-- erts/emulator/beam/erl_message.c | 2 +- erts/emulator/beam/erl_monitor_link.c | 3 +- erts/emulator/beam/erl_nif.c | 8 ++--- erts/emulator/beam/erl_process.c | 15 ++++++++ erts/emulator/beam/erl_term_hashing.c | 48 ++++++++++++------------- erts/emulator/beam/erl_trace.c | 2 +- erts/emulator/beam/erl_unicode.c | 2 ++ erts/emulator/beam/external.c | 13 ++++--- erts/emulator/beam/io.c | 1 + erts/emulator/beam/packet_parser.c | 1 + erts/emulator/beam/sys.h | 10 ++++++ erts/emulator/beam/utils.c | 4 ++- erts/emulator/sys/common/erl_check_io.c | 3 +- erts/epmd/src/epmd.c | 4 ++- erts/epmd/src/epmd_int.h | 17 ++++++++- erts/include/internal/ethread.h | 9 +++++ erts/lib_src/common/erl_printf_format.c | 13 +++++++ erts/lib_src/common/ethr_mutex.c | 2 ++ lib/erl_interface/src/misc/ei_format.c | 1 + lib/erl_interface/src/misc/eidef.h | 10 ++++++ lib/erl_interface/src/misc/get_type.c | 2 ++ lib/erl_interface/src/prog/erl_call.c | 40 ++++++++++++++++----- 36 files changed, 274 insertions(+), 116 deletions(-) diff --git a/erts/emulator/beam/beam_bp.c b/erts/emulator/beam/beam_bp.c index 788e4e2bf110..d2481ca93052 100644 --- a/erts/emulator/beam/beam_bp.c +++ b/erts/emulator/beam/beam_bp.c @@ -221,12 +221,15 @@ erts_bp_match_functions(BpFunctions* f, ErtsCodeMFA *mfa, int specified) case 3: if (ci->mfa.arity != mfa->arity) continue; + ERTS_FALLTHROUGH(); case 2: if (ci->mfa.function != mfa->function) continue; + ERTS_FALLTHROUGH(); case 1: if (ci->mfa.module != mfa->module) continue; + ERTS_FALLTHROUGH(); case 0: break; } @@ -259,12 +262,15 @@ erts_bp_match_export(BpFunctions* f, ErtsCodeMFA *mfa, int specified) case 3: if (mfa->arity != ep->info.mfa.arity) continue; + ERTS_FALLTHROUGH(); case 2: if (mfa->function != ep->info.mfa.function) continue; + ERTS_FALLTHROUGH(); case 1: if (mfa->module != ep->info.mfa.module) continue; + ERTS_FALLTHROUGH(); case 0: break; default: diff --git a/erts/emulator/beam/bif.c b/erts/emulator/beam/bif.c index 3c4591fb1c6c..e6d4eaea86aa 100644 --- a/erts/emulator/beam/bif.c +++ b/erts/emulator/beam/bif.c @@ -3295,6 +3295,7 @@ BIF_RETTYPE string_list_to_float_1(BIF_ALIST_1) break; case EXP0: /* example: "2.3e--" */ LOAD_E(i, i_mem, list, list_mem); + ERTS_FALLTHROUGH(); default: /* unexpected - done */ part = END; } @@ -3308,6 +3309,7 @@ BIF_RETTYPE string_list_to_float_1(BIF_ALIST_1) break; case EXP0: /* example: "2.3e++" */ LOAD_E(i, i_mem, list, list_mem); + ERTS_FALLTHROUGH(); default: /* unexpected - done */ part = END; } @@ -3318,8 +3320,10 @@ BIF_RETTYPE string_list_to_float_1(BIF_ALIST_1) break; case EXP_SIGN: /* example: "2.3e." */ LOAD_E(i, i_mem, list, list_mem); + ERTS_FALLTHROUGH(); case EXP0: /* example: "2.3e+." */ LOAD_E(i, i_mem, list, list_mem); + ERTS_FALLTHROUGH(); default: /* unexpected - done */ part = END; } @@ -3336,6 +3340,7 @@ BIF_RETTYPE string_list_to_float_1(BIF_ALIST_1) case EXP0: /* example: "2.3e+e" */ case EXP_SIGN: /* example: "2.3ee" */ LOAD_E(i, i_mem, list, list_mem); + ERTS_FALLTHROUGH(); case INT: /* would like this to be ok, example "2e2", but it's not compatible with list_to_float */ default: /* unexpected - done */ diff --git a/erts/emulator/beam/break.c b/erts/emulator/beam/break.c index 9d9cfdf4dc3a..561d1d147cfb 100644 --- a/erts/emulator/beam/break.c +++ b/erts/emulator/beam/break.c @@ -127,32 +127,28 @@ process_killer(void) for (i = max-1; i >= 0; i--) { rp = erts_pix2proc(i); if (rp && rp->i != ENULL) { - int br; print_process_info(ERTS_PRINT_STDOUT, NULL, rp, 0); erts_printf("(k)ill (n)ext (r)eturn:\n"); - while(1) { - if ((j = sys_get_key(0)) <= 0) - erts_exit(0, ""); - switch(j) { - case 'k': - { - Process *init_proc; - - ASSERT(erts_init_process_id != ERTS_INVALID_PID); - init_proc = erts_proc_lookup_raw(erts_init_process_id); - - /* Send a 'kill' exit signal from init process */ - erts_proc_sig_send_exit(&init_proc->common, - erts_init_process_id, - rp->common.id, - am_kill, NIL, 0); - } - case 'n': br = 1; break; - case 'r': return; - default: return; - } - if (br == 1) break; - } + if ((j = sys_get_key(0)) <= 0) + erts_exit(0, ""); + switch(j) { + case 'k': + { + Process *init_proc; + + ASSERT(erts_init_process_id != ERTS_INVALID_PID); + init_proc = erts_proc_lookup_raw(erts_init_process_id); + + /* Send a 'kill' exit signal from init process */ + erts_proc_sig_send_exit(&init_proc->common, + erts_init_process_id, + rp->common.id, + am_kill, NIL, 0); + break; + } + case 'n': break; + default: return; + } } } } diff --git a/erts/emulator/beam/copy.c b/erts/emulator/beam/copy.c index 7ae1e7210423..df6b37c8762e 100644 --- a/erts/emulator/beam/copy.c +++ b/erts/emulator/beam/copy.c @@ -898,6 +898,7 @@ Eterm copy_struct_x(Eterm obj, Uint sz, Eterm** hpp, ErlOffHeap* off_heap, case MAP_HEADER_TAG_HAMT_HEAD_BITMAP : case MAP_HEADER_TAG_HAMT_HEAD_ARRAY : *htop++ = *objp++; + ERTS_FALLTHROUGH(); case MAP_HEADER_TAG_HAMT_NODE_BITMAP : i = 1 + hashmap_bitcount(MAP_HEADER_VAL(hdr)); while (i--) { *htop++ = *objp++; } @@ -1601,6 +1602,7 @@ Uint copy_shared_perform_x(Eterm obj, Uint size, erts_shcopy_t *info, case MAP_HEADER_TAG_HAMT_HEAD_BITMAP : case MAP_HEADER_TAG_HAMT_HEAD_ARRAY : *hp++ = *++ptr; /* total map size */ + ERTS_FALLTHROUGH(); case MAP_HEADER_TAG_HAMT_NODE_BITMAP : { Uint n = hashmap_bitcount(MAP_HEADER_VAL(hdr)); while (n--) { @@ -1987,7 +1989,7 @@ Eterm* copy_shallow_x(Eterm *ERTS_RESTRICT ptr, Uint sz, Eterm **hpp, erts_refc_inc(&mreft->mb->intern.refc, 2); goto off_heap_common; } - /* Fall through... */ + ERTS_FALLTHROUGH(); } default: { @@ -2101,6 +2103,7 @@ move_one_frag(Eterm** hpp, ErlHeapFragment* frag, ErlOffHeap* off_heap, int lite if (!is_magic_ref_thing(hdr)) { break; } + ERTS_FALLTHROUGH(); case BIN_REF_SUBTAG: case EXTERNAL_PID_SUBTAG: case EXTERNAL_PORT_SUBTAG: diff --git a/erts/emulator/beam/dist.c b/erts/emulator/beam/dist.c index 906ea8de5932..c1670f8b2fb9 100644 --- a/erts/emulator/beam/dist.c +++ b/erts/emulator/beam/dist.c @@ -383,6 +383,7 @@ con_monitor_link_seq_cleanup(void *vcmlcp) ASSERT(!cmlcp->yield_state); cmlcp->state = ERTS_CML_CLEANUP_STATE_MONITORS; + ERTS_FALLTHROUGH(); case ERTS_CML_CLEANUP_STATE_MONITORS: reds = erts_monitor_list_foreach_delete_yielding(&dist->monitors, monitor_connection_down, @@ -393,6 +394,7 @@ con_monitor_link_seq_cleanup(void *vcmlcp) ASSERT(!cmlcp->yield_state); cmlcp->state = ERTS_CML_CLEANUP_STATE_ONAME_MONITORS; + ERTS_FALLTHROUGH(); case ERTS_CML_CLEANUP_STATE_ONAME_MONITORS: reds = erts_monitor_tree_foreach_delete_yielding(&dist->orig_name_monitors, monitor_connection_down, @@ -403,6 +405,7 @@ con_monitor_link_seq_cleanup(void *vcmlcp) ASSERT(!cmlcp->yield_state); cmlcp->state = ERTS_CML_CLEANUP_STATE_PEND_SPAWN_EXIT_MONITORS; + ERTS_FALLTHROUGH(); case ERTS_CML_CLEANUP_STATE_PEND_SPAWN_EXIT_MONITORS: reds = erts_monitor_tree_foreach_delete_yielding(&dist->dist_pend_spawn_exit, dist_pend_spawn_exit_connection_down, @@ -416,6 +419,7 @@ con_monitor_link_seq_cleanup(void *vcmlcp) ASSERT(!cmlcp->yield_state); cmlcp->state = ERTS_CML_CLEANUP_STATE_SEQUENCES; + ERTS_FALLTHROUGH(); case ERTS_CML_CLEANUP_STATE_SEQUENCES: reds = erts_dist_seq_tree_foreach_delete_yielding(&cmlcp->seq, &cmlcp->yield_state, @@ -425,6 +429,7 @@ con_monitor_link_seq_cleanup(void *vcmlcp) ASSERT(!cmlcp->yield_state); cmlcp->state = ERTS_CML_CLEANUP_STATE_NODE_MONITORS; + ERTS_FALLTHROUGH(); case ERTS_CML_CLEANUP_STATE_NODE_MONITORS: if (cmlcp->trigger_node_monitors) { Process* waiter; @@ -2114,6 +2119,7 @@ int erts_net_message(Port *prt, } /* fall through, the first fragment in the sequence was the last fragment */ + ERTS_FALLTHROUGH(); case ERTS_PREP_DIST_EXT_FRAG_CONT: { DistSeqNode *seq; erts_de_rlock(dep); @@ -3274,6 +3280,7 @@ erts_dsig_send(ErtsDSigSendContext *ctx) } ctx->phase = ERTS_DSIG_SEND_PHASE_MSG_SIZE; + ERTS_FALLTHROUGH(); case ERTS_DSIG_SEND_PHASE_MSG_SIZE: { Sint reds, *redsp; if (!ctx->no_trap) @@ -3311,6 +3318,7 @@ erts_dsig_send(ErtsDSigSendContext *ctx) } ctx->phase = ERTS_DSIG_SEND_PHASE_ALLOC; + ERTS_FALLTHROUGH(); } case ERTS_DSIG_SEND_PHASE_ALLOC: { @@ -3356,6 +3364,7 @@ erts_dsig_send(ErtsDSigSendContext *ctx) } ctx->phase = ERTS_DSIG_SEND_PHASE_MSG_ENCODE; + ERTS_FALLTHROUGH(); } case ERTS_DSIG_SEND_PHASE_MSG_ENCODE: { Sint reds, *redsp; @@ -3387,6 +3396,7 @@ erts_dsig_send(ErtsDSigSendContext *ctx) } ctx->phase = ERTS_DSIG_SEND_PHASE_FIN; + ERTS_FALLTHROUGH(); } case ERTS_DSIG_SEND_PHASE_FIN: { Uint fid = ctx->fragments; @@ -3456,6 +3466,7 @@ erts_dsig_send(ErtsDSigSendContext *ctx) retval = ERTS_DSIG_SEND_CONTINUE; goto done; } + ERTS_FALLTHROUGH(); } case ERTS_DSIG_SEND_PHASE_SEND: { /* diff --git a/erts/emulator/beam/emu/bs_instrs.tab b/erts/emulator/beam/emu/bs_instrs.tab index 1c41b5b3ccb7..7e95d4e790a1 100644 --- a/erts/emulator/beam/emu/bs_instrs.tab +++ b/erts/emulator/beam/emu/bs_instrs.tab @@ -1343,22 +1343,22 @@ i_bs_read_bits.execute() { #ifdef ARCH_64 case 9: case 8: - bitdata = bitdata << 8 | *byte_ptr++; + bitdata = bitdata << 8 | *byte_ptr++; ERTS_FALLTHROUGH(); case 7: - bitdata = bitdata << 8 | *byte_ptr++; + bitdata = bitdata << 8 | *byte_ptr++; ERTS_FALLTHROUGH(); case 6: - bitdata = bitdata << 8 | *byte_ptr++; + bitdata = bitdata << 8 | *byte_ptr++; ERTS_FALLTHROUGH(); case 5: - bitdata = bitdata << 8 | *byte_ptr++; + bitdata = bitdata << 8 | *byte_ptr++; ERTS_FALLTHROUGH(); #else case 5: #endif case 4: - bitdata = bitdata << 8 | *byte_ptr++; + bitdata = bitdata << 8 | *byte_ptr++; ERTS_FALLTHROUGH(); case 3: - bitdata = bitdata << 8 | *byte_ptr++; + bitdata = bitdata << 8 | *byte_ptr++; ERTS_FALLTHROUGH(); case 2: - bitdata = bitdata << 8 | *byte_ptr++; + bitdata = bitdata << 8 | *byte_ptr++; ERTS_FALLTHROUGH(); case 1: bitdata = bitdata << 8 | *byte_ptr++; } diff --git a/erts/emulator/beam/erl_arith.c b/erts/emulator/beam/erl_arith.c index b608df2b4fc0..e394a3a9416c 100644 --- a/erts/emulator/beam/erl_arith.c +++ b/erts/emulator/beam/erl_arith.c @@ -370,7 +370,7 @@ erts_mixed_plus(Process* p, Eterm arg1, Eterm arg2) case (_TAG_HEADER_POS_BIG >> _TAG_PRIMARY_SIZE): case (_TAG_HEADER_NEG_BIG >> _TAG_PRIMARY_SIZE): switch (arg2 & _TAG_PRIMARY_MASK) { - case (_TAG_IMMED1_SMALL >> _TAG_PRIMARY_SIZE): + case TAG_PRIMARY_IMMED1: switch ((arg2 & _TAG_IMMED1_MASK) >> _TAG_PRIMARY_SIZE) { case (_TAG_IMMED1_SMALL >> _TAG_PRIMARY_SIZE): if (arg2 == SMALL_ZERO) { @@ -408,7 +408,9 @@ erts_mixed_plus(Process* p, Eterm arg1, Eterm arg2) default: goto badarith; } - } + default: + goto badarith; + } case (_TAG_HEADER_FLOAT >> _TAG_PRIMARY_SIZE): switch (arg2 & _TAG_PRIMARY_MASK) { case TAG_PRIMARY_IMMED1: @@ -576,7 +578,7 @@ erts_mixed_minus(Process* p, Eterm arg1, Eterm arg2) case (_TAG_HEADER_POS_BIG >> _TAG_PRIMARY_SIZE): case (_TAG_HEADER_NEG_BIG >> _TAG_PRIMARY_SIZE): switch (arg2 & _TAG_PRIMARY_MASK) { - case (_TAG_IMMED1_SMALL >> _TAG_PRIMARY_SIZE): + case TAG_PRIMARY_IMMED1: switch ((arg2 & _TAG_IMMED1_MASK) >> _TAG_PRIMARY_SIZE) { case (_TAG_IMMED1_SMALL >> _TAG_PRIMARY_SIZE): if (arg2 == SMALL_ZERO) { @@ -615,6 +617,8 @@ erts_mixed_minus(Process* p, Eterm arg1, Eterm arg2) default: goto badarith; } + default: + goto badarith; } case (_TAG_HEADER_FLOAT >> _TAG_PRIMARY_SIZE): switch (arg2 & _TAG_PRIMARY_MASK) { @@ -744,17 +748,19 @@ erts_mixed_times(Process* p, Eterm arg1, Eterm arg2) default: goto badarith; } - } - default: + default: + goto badarith; + } + default: goto badarith; - } + } case TAG_PRIMARY_BOXED: hdr = *boxed_val(arg1); switch ((hdr & _TAG_HEADER_MASK) >> _TAG_PRIMARY_SIZE) { case (_TAG_HEADER_POS_BIG >> _TAG_PRIMARY_SIZE): case (_TAG_HEADER_NEG_BIG >> _TAG_PRIMARY_SIZE): switch (arg2 & _TAG_PRIMARY_MASK) { - case (_TAG_IMMED1_SMALL >> _TAG_PRIMARY_SIZE): + case TAG_PRIMARY_IMMED1: switch ((arg2 & _TAG_IMMED1_MASK) >> _TAG_PRIMARY_SIZE) { case (_TAG_IMMED1_SMALL >> _TAG_PRIMARY_SIZE): if (arg2 == SMALL_ZERO) @@ -810,7 +816,9 @@ erts_mixed_times(Process* p, Eterm arg1, Eterm arg2) default: goto badarith; } - } + default: + goto badarith; + } case (_TAG_HEADER_FLOAT >> _TAG_PRIMARY_SIZE): switch (arg2 & _TAG_PRIMARY_MASK) { case TAG_PRIMARY_IMMED1: @@ -998,7 +1006,7 @@ erts_mixed_div(Process* p, Eterm arg1, Eterm arg2) case (_TAG_HEADER_POS_BIG >> _TAG_PRIMARY_SIZE): case (_TAG_HEADER_NEG_BIG >> _TAG_PRIMARY_SIZE): switch (arg2 & _TAG_PRIMARY_MASK) { - case (_TAG_IMMED1_SMALL >> _TAG_PRIMARY_SIZE): + case TAG_PRIMARY_IMMED1: switch ((arg2 & _TAG_IMMED1_MASK) >> _TAG_PRIMARY_SIZE) { case (_TAG_IMMED1_SMALL >> _TAG_PRIMARY_SIZE): if (big_to_double(arg1, &f1.fd) < 0) { @@ -1028,7 +1036,9 @@ erts_mixed_div(Process* p, Eterm arg1, Eterm arg2) default: goto badarith; } - } + default: + goto badarith; + } case (_TAG_HEADER_FLOAT >> _TAG_PRIMARY_SIZE): switch (arg2 & _TAG_PRIMARY_MASK) { case TAG_PRIMARY_IMMED1: diff --git a/erts/emulator/beam/erl_bif_re.c b/erts/emulator/beam/erl_bif_re.c index 38072f3fcd73..88433a29389c 100644 --- a/erts/emulator/beam/erl_bif_re.c +++ b/erts/emulator/beam/erl_bif_re.c @@ -1361,7 +1361,8 @@ re_run(Process *p, Eterm arg1, Eterm arg2, Eterm arg3, int first) case PCRE_ERROR_BADUTF8_OFFSET: BUMP_ALL_REDS(p); /* Unknown amount of work done... */ /* Fall through for badarg... */ - + ERTS_FALLTHROUGH(); + /* Bad pre-compiled regexp... */ case PCRE_ERROR_BADMAGIC: case PCRE_ERROR_BADENDIANNESS: diff --git a/erts/emulator/beam/erl_bif_trace.c b/erts/emulator/beam/erl_bif_trace.c index a7614403155e..40b1433c9f6b 100644 --- a/erts/emulator/beam/erl_bif_trace.c +++ b/erts/emulator/beam/erl_bif_trace.c @@ -2666,6 +2666,7 @@ erts_finish_breakpointing(void) } /* Nothing to do here. Fall through to next stage. */ finish_bp.current++; + ERTS_FALLTHROUGH(); case 1: /* * Switch index for the breakpoint data, activating the staged @@ -2702,6 +2703,7 @@ erts_finish_breakpointing(void) } /* Nothing done here. Fall through to next stage. */ finish_bp.current++; + ERTS_FALLTHROUGH(); case 3: /* * Now all breakpoints have either been inserted or removed. diff --git a/erts/emulator/beam/erl_bits.c b/erts/emulator/beam/erl_bits.c index a3858841283a..ef3640e1c289 100644 --- a/erts/emulator/beam/erl_bits.c +++ b/erts/emulator/beam/erl_bits.c @@ -246,13 +246,13 @@ Process *p, Uint num_bits, unsigned flags, ErlSubBits *sb) */ switch (BYTE_OFFSET(n)) { #if defined(ARCH_64) - case 7: w = (w << 8) | *bp++; - case 6: w = (w << 8) | *bp++; - case 5: w = (w << 8) | *bp++; - case 4: w = (w << 8) | *bp++; + case 7: w = (w << 8) | *bp++; ERTS_FALLTHROUGH(); + case 6: w = (w << 8) | *bp++; ERTS_FALLTHROUGH(); + case 5: w = (w << 8) | *bp++; ERTS_FALLTHROUGH(); + case 4: w = (w << 8) | *bp++; ERTS_FALLTHROUGH(); #endif - case 3: w = (w << 8) | *bp++; - case 2: w = (w << 8) | *bp++; + case 3: w = (w << 8) | *bp++; ERTS_FALLTHROUGH(); + case 2: w = (w << 8) | *bp++; ERTS_FALLTHROUGH(); case 1: w = (w << 8) | *bp++; } n = BIT_OFFSET(n); @@ -537,21 +537,21 @@ erts_bs_get_binary_all_2(Process *p, ErlSubBits *sb) * dst and val are updated. */ -#define FMT_COPY_VAL(dst,ddir,val,sz) do { \ - Uint __sz = (sz); \ - while (__sz) { \ - switch(__sz) { \ - default: \ - case 8: *dst = val; dst += ddir; val >>= 8; __sz--; \ - case 7: *dst = val; dst += ddir; val >>= 8; __sz--; \ - case 6: *dst = val; dst += ddir; val >>= 8; __sz--; \ - case 5: *dst = val; dst += ddir; val >>= 8; __sz--; \ - case 4: *dst = val; dst += ddir; val >>= 8; __sz--; \ - case 3: *dst = val; dst += ddir; val >>= 8; __sz--; \ - case 2: *dst = val; dst += ddir; val >>= 8; __sz--; \ - case 1: *dst = val; dst += ddir; val >>= 8; __sz--; \ - } \ - } \ +#define FMT_COPY_VAL(dst,ddir,val,sz) do { \ + Uint __sz = (sz); \ + while (__sz) { \ + switch(__sz) { \ + default: \ + case 8: *dst = val; dst += ddir; val >>= 8; __sz--; ERTS_FALLTHROUGH(); \ + case 7: *dst = val; dst += ddir; val >>= 8; __sz--; ERTS_FALLTHROUGH(); \ + case 6: *dst = val; dst += ddir; val >>= 8; __sz--; ERTS_FALLTHROUGH(); \ + case 5: *dst = val; dst += ddir; val >>= 8; __sz--; ERTS_FALLTHROUGH(); \ + case 4: *dst = val; dst += ddir; val >>= 8; __sz--; ERTS_FALLTHROUGH(); \ + case 3: *dst = val; dst += ddir; val >>= 8; __sz--; ERTS_FALLTHROUGH(); \ + case 2: *dst = val; dst += ddir; val >>= 8; __sz--; ERTS_FALLTHROUGH(); \ + case 1: *dst = val; dst += ddir; val >>= 8; __sz--; \ + } \ + } \ } while(0) static void diff --git a/erts/emulator/beam/erl_db_tree.c b/erts/emulator/beam/erl_db_tree.c index 4660837300b7..9714851ca695 100644 --- a/erts/emulator/beam/erl_db_tree.c +++ b/erts/emulator/beam/erl_db_tree.c @@ -3902,6 +3902,7 @@ static Sint do_cmp_partly_bound(Eterm a, Eterm b, int *done) return 0; } /* Drop through */ + ERTS_FALLTHROUGH(); default: return CMP(a,b); } diff --git a/erts/emulator/beam/erl_gc.c b/erts/emulator/beam/erl_gc.c index 11e8974f8d78..20585d75f78a 100644 --- a/erts/emulator/beam/erl_gc.c +++ b/erts/emulator/beam/erl_gc.c @@ -2562,6 +2562,7 @@ erts_copy_one_frag(Eterm** hpp, ErlOffHeap* off_heap, case REF_SUBTAG: if (!is_magic_ref_thing(fhp - 1)) goto the_default; + ERTS_FALLTHROUGH(); case BIN_REF_SUBTAG: case EXTERNAL_PID_SUBTAG: case EXTERNAL_PORT_SUBTAG: @@ -3058,7 +3059,7 @@ sweep_off_heap(Process *p, int fullsweep) bin_vheap += size / sizeof(Eterm); else p->bin_old_vheap += size / sizeof(Eterm); /* for binary gc (words)*/ - /* fall through... */ + ERTS_FALLTHROUGH(); } default: if (is_external_header(ptr->thing_word)) { @@ -3312,6 +3313,7 @@ offset_heap(Eterm* hp, Uint sz, Sint offs, char* area, Uint area_size) case REF_SUBTAG: if (!is_magic_ref_thing(hp)) break; + ERTS_FALLTHROUGH(); case BIN_REF_SUBTAG: case EXTERNAL_PID_SUBTAG: case EXTERNAL_PORT_SUBTAG: @@ -4023,7 +4025,7 @@ check_all_heap_terms_in_range(int (*check_eterm)(Eterm), if (is_magic_ref_thing(rtp)) { goto off_heap_common; } - /* Fall through... */ + ERTS_FALLTHROUGH(); } default: { diff --git a/erts/emulator/beam/erl_init.c b/erts/emulator/beam/erl_init.c index d8397d31db20..a875fba8958b 100644 --- a/erts/emulator/beam/erl_init.c +++ b/erts/emulator/beam/erl_init.c @@ -528,7 +528,7 @@ load_preloaded(void) } /* be helpful (or maybe downright rude:-) */ -void erts_usage(void) +__decl_noreturn void __noreturn erts_usage(void) { int this_rel = this_rel_num(); erts_fprintf(stderr, "Usage: %s [flags] [ -- [init_args] ]\n", progname(program)); @@ -1033,6 +1033,7 @@ early_init(int *argc, char **argv) /* case 1: onln = tot < dirty_cpu_scheds_online ? tot : dirty_cpu_scheds_online; + ERTS_FALLTHROUGH(); case 2: chk_SDcpu: if (tot > 0) @@ -1103,6 +1104,7 @@ early_init(int *argc, char **argv) /* } case 1: onln = tot < schdlrs_onln ? tot : schdlrs_onln; + ERTS_FALLTHROUGH(); case 2: chk_S: if (tot > 0) diff --git a/erts/emulator/beam/erl_map.c b/erts/emulator/beam/erl_map.c index bdbd10d22234..541d3c1220c2 100644 --- a/erts/emulator/beam/erl_map.c +++ b/erts/emulator/beam/erl_map.c @@ -1656,7 +1656,7 @@ static BIF_RETTYPE hashmap_merge(Process *p, Eterm map_A, Eterm map_B, sp->abm = 0xffff; break; } - case HAMT_SUBTAG_HEAD_BITMAP: sp->srcA++; + case HAMT_SUBTAG_HEAD_BITMAP: sp->srcA++; ERTS_FALLTHROUGH(); case HAMT_SUBTAG_NODE_BITMAP: { ASSERT(ctx->lvl < HAMT_MAX_LEVEL); sp->abm = MAP_HEADER_VAL(hdrA); @@ -1693,7 +1693,7 @@ static BIF_RETTYPE hashmap_merge(Process *p, Eterm map_A, Eterm map_B, sp->bbm = 0xffff; break; } - case HAMT_SUBTAG_HEAD_BITMAP: sp->srcB++; + case HAMT_SUBTAG_HEAD_BITMAP: sp->srcB++; ERTS_FALLTHROUGH(); case HAMT_SUBTAG_NODE_BITMAP: { ASSERT(ctx->lvl < HAMT_MAX_LEVEL); sp->bbm = MAP_HEADER_VAL(hdrB); @@ -2329,6 +2329,7 @@ Uint hashmap_node_size(Eterm hdr, Eterm **nodep) break; case HAMT_SUBTAG_HEAD_BITMAP: if (nodep) ++*nodep; + ERTS_FALLTHROUGH(); case HAMT_SUBTAG_NODE_BITMAP: sz = hashmap_bitcount(MAP_HEADER_VAL(hdr)); ASSERT(sz < 17); @@ -2711,6 +2712,7 @@ Eterm erts_hashmap_insert_up(Eterm *hp, Eterm key, Eterm value, /* subnodes, fake it */ fake = node; node = make_boxed(&fake); + ERTS_FALLTHROUGH(); case TAG_PRIMARY_BOXED: ptr = boxed_val(node); hdr = *ptr; @@ -3442,6 +3444,7 @@ BIF_RETTYPE erts_internal_map_hashmap_children_1(BIF_ALIST_1) { BIF_ERROR(BIF_P, BADARG); case HAMT_SUBTAG_HEAD_BITMAP: ptr++; + ERTS_FALLTHROUGH(); case HAMT_SUBTAG_NODE_BITMAP: ptr++; sz = hashmap_bitcount(MAP_HEADER_VAL(hdr)); diff --git a/erts/emulator/beam/erl_message.c b/erts/emulator/beam/erl_message.c index bb075be5d1c2..3cb6b0a3da16 100644 --- a/erts/emulator/beam/erl_message.c +++ b/erts/emulator/beam/erl_message.c @@ -1509,7 +1509,7 @@ void erts_factory_trim_and_close(ErtsHeapFactory* factory, /*else we don't trim multi fragmented messages for now (off_heap...) */ break; } - /* Fall through... */ + ERTS_FALLTHROUGH(); } case FACTORY_HEAP_FRAGS: bp = factory->heap_frags; diff --git a/erts/emulator/beam/erl_monitor_link.c b/erts/emulator/beam/erl_monitor_link.c index 85d880dda354..59506b10510c 100644 --- a/erts/emulator/beam/erl_monitor_link.c +++ b/erts/emulator/beam/erl_monitor_link.c @@ -894,7 +894,8 @@ erts_monitor_create(Uint16 type, Eterm ref, Eterm orgn, Eterm trgt, Eterm name, mdp->u.target.type = type; erts_atomic32_init_nob(&mdp->refc, 2); break; - } + } /* end of "if (is_nil(name))"" */ + ERTS_FALLTHROUGH(); case ERTS_MON_TYPE_DIST_PROC: case ERTS_MON_TYPE_DIST_PORT: case ERTS_MON_TYPE_RESOURCE: diff --git a/erts/emulator/beam/erl_nif.c b/erts/emulator/beam/erl_nif.c index f5600b7dc607..6c40b8290a8b 100644 --- a/erts/emulator/beam/erl_nif.c +++ b/erts/emulator/beam/erl_nif.c @@ -2707,10 +2707,10 @@ ErlNifResourceType* open_resource_type(ErlNifEnv* env, ort->type = type; sys_memzero(&ort->new_callbacks, sizeof(ErlNifResourceTypeInit)); switch (init_members) { - case 4: ort->new_callbacks.dyncall = init->dyncall; - case 3: ort->new_callbacks.down = init->down; - case 2: ort->new_callbacks.stop = init->stop; - case 1: ort->new_callbacks.dtor = init->dtor; + case 4: ort->new_callbacks.dyncall = init->dyncall; ERTS_FALLTHROUGH(); + case 3: ort->new_callbacks.down = init->down; ERTS_FALLTHROUGH(); + case 2: ort->new_callbacks.stop = init->stop; ERTS_FALLTHROUGH(); + case 1: ort->new_callbacks.dtor = init->dtor; ERTS_FALLTHROUGH(); case 0: break; default: diff --git a/erts/emulator/beam/erl_process.c b/erts/emulator/beam/erl_process.c index ee266a47ddf9..b96a01bc4555 100644 --- a/erts/emulator/beam/erl_process.c +++ b/erts/emulator/beam/erl_process.c @@ -14161,6 +14161,7 @@ erts_continue_exit_process(Process *p) trap_state->phase = ERTS_CONTINUE_EXIT_BLCKD_MSHED; if (reds <= 0) goto yield; + ERTS_FALLTHROUGH(); case ERTS_CONTINUE_EXIT_BLCKD_MSHED: if (p->flags & F_HAVE_BLCKD_MSCHED) { @@ -14181,6 +14182,7 @@ erts_continue_exit_process(Process *p) trap_state->phase = ERTS_CONTINUE_EXIT_BLCKD_NMSHED; if (reds <= 0) goto yield; + ERTS_FALLTHROUGH(); case ERTS_CONTINUE_EXIT_BLCKD_NMSHED: if (p->flags & F_HAVE_BLCKD_NMSCHED) { @@ -14202,6 +14204,7 @@ erts_continue_exit_process(Process *p) trap_state->yield_state = NULL; trap_state->phase = ERTS_CONTINUE_EXIT_USING_DB; if (reds <= 0) goto yield; + ERTS_FALLTHROUGH(); case ERTS_CONTINUE_EXIT_USING_DB: if (p->flags & F_USING_DB) { @@ -14211,6 +14214,7 @@ erts_continue_exit_process(Process *p) } trap_state->phase = ERTS_CONTINUE_EXIT_CLEAN_SYS_TASKS; + ERTS_FALLTHROUGH(); case ERTS_CONTINUE_EXIT_CLEAN_SYS_TASKS: state = erts_atomic32_read_acqb(&p->state); @@ -14246,6 +14250,7 @@ erts_continue_exit_process(Process *p) } trap_state->phase = ERTS_CONTINUE_EXIT_FREE; + ERTS_FALLTHROUGH(); case ERTS_CONTINUE_EXIT_FREE: #ifdef DEBUG @@ -14320,6 +14325,7 @@ erts_continue_exit_process(Process *p) erts_proc_unlock(p, ERTS_PROC_LOCKS_ALL_MINOR); curr_locks = ERTS_PROC_LOCK_MAIN; trap_state->phase = ERTS_CONTINUE_EXIT_CLEAN_SYS_TASKS_AFTER; + ERTS_FALLTHROUGH(); case ERTS_CONTINUE_EXIT_CLEAN_SYS_TASKS_AFTER: /* * It might show up signal prio elevation tasks until we @@ -14383,6 +14389,7 @@ erts_continue_exit_process(Process *p) trap_state->yield_state = NULL; trap_state->phase = ERTS_CONTINUE_EXIT_LINKS; if (reds <= 0) goto yield; + ERTS_FALLTHROUGH(); case ERTS_CONTINUE_EXIT_LINKS: reds = erts_link_tree_foreach_delete_yielding( @@ -14397,6 +14404,7 @@ erts_continue_exit_process(Process *p) ASSERT(!trap_state->links); trap_state->yield_state = NULL; trap_state->phase = ERTS_CONTINUE_EXIT_MONITORS; + ERTS_FALLTHROUGH(); case ERTS_CONTINUE_EXIT_MONITORS: reds = erts_monitor_tree_foreach_delete_yielding( @@ -14411,6 +14419,7 @@ erts_continue_exit_process(Process *p) ASSERT(!trap_state->monitors); trap_state->yield_state = NULL; trap_state->phase = ERTS_CONTINUE_EXIT_LT_MONITORS; + ERTS_FALLTHROUGH(); case ERTS_CONTINUE_EXIT_LT_MONITORS: reds = erts_monitor_list_foreach_delete_yielding( @@ -14424,6 +14433,7 @@ erts_continue_exit_process(Process *p) ASSERT(!trap_state->lt_monitors); trap_state->phase = ERTS_CONTINUE_EXIT_HANDLE_PROC_SIG; + ERTS_FALLTHROUGH(); case ERTS_CONTINUE_EXIT_HANDLE_PROC_SIG: { Sint r = reds; @@ -14434,6 +14444,7 @@ erts_continue_exit_process(Process *p) reds -= r; trap_state->phase = ERTS_CONTINUE_EXIT_DIST_SEND; + ERTS_FALLTHROUGH(); } case ERTS_CONTINUE_EXIT_DIST_SEND: { @@ -14472,6 +14483,7 @@ erts_continue_exit_process(Process *p) } trap_state->phase = ERTS_CONTINUE_EXIT_DIST_LINKS; + ERTS_FALLTHROUGH(); } case ERTS_CONTINUE_EXIT_DIST_LINKS: { @@ -14488,6 +14500,7 @@ erts_continue_exit_process(Process *p) goto yield; trap_state->phase = ERTS_CONTINUE_EXIT_DIST_MONITORS; + ERTS_FALLTHROUGH(); } case ERTS_CONTINUE_EXIT_DIST_MONITORS: { @@ -14504,6 +14517,7 @@ erts_continue_exit_process(Process *p) goto yield; trap_state->phase = ERTS_CONTINUE_EXIT_DIST_PEND_SPAWN_MONITORS; + ERTS_FALLTHROUGH(); } case ERTS_CONTINUE_EXIT_DIST_PEND_SPAWN_MONITORS: { @@ -14529,6 +14543,7 @@ erts_continue_exit_process(Process *p) goto yield; trap_state->phase = ERTS_CONTINUE_EXIT_DONE; + ERTS_FALLTHROUGH(); } case ERTS_CONTINUE_EXIT_DONE: { erts_aint_t state; diff --git a/erts/emulator/beam/erl_term_hashing.c b/erts/emulator/beam/erl_term_hashing.c index a32d47aa914e..3ada7f479c2e 100644 --- a/erts/emulator/beam/erl_term_hashing.c +++ b/erts/emulator/beam/erl_term_hashing.c @@ -462,17 +462,17 @@ Uint32 block_hash_final_bytes(byte *buf, ctx->c += full_length; switch(len) { /* all the case statements fall through */ - case 11: ctx->c+=((Uint32)k[10]<<24); - case 10: ctx->c+=((Uint32)k[9]<<16); - case 9 : ctx->c+=((Uint32)k[8]<<8); + case 11: ctx->c+=((Uint32)k[10]<<24); ERTS_FALLTHROUGH(); + case 10: ctx->c+=((Uint32)k[9]<<16); ERTS_FALLTHROUGH(); + case 9 : ctx->c+=((Uint32)k[8]<<8); ERTS_FALLTHROUGH(); /* the first byte of c is reserved for the length */ - case 8 : ctx->b+=((Uint32)k[7]<<24); - case 7 : ctx->b+=((Uint32)k[6]<<16); - case 6 : ctx->b+=((Uint32)k[5]<<8); - case 5 : ctx->b+=k[4]; - case 4 : ctx->a+=((Uint32)k[3]<<24); - case 3 : ctx->a+=((Uint32)k[2]<<16); - case 2 : ctx->a+=((Uint32)k[1]<<8); + case 8 : ctx->b+=((Uint32)k[7]<<24); ERTS_FALLTHROUGH(); + case 7 : ctx->b+=((Uint32)k[6]<<16); ERTS_FALLTHROUGH(); + case 6 : ctx->b+=((Uint32)k[5]<<8); ERTS_FALLTHROUGH(); + case 5 : ctx->b+=k[4]; ERTS_FALLTHROUGH(); + case 4 : ctx->a+=((Uint32)k[3]<<24); ERTS_FALLTHROUGH(); + case 3 : ctx->a+=((Uint32)k[2]<<16); ERTS_FALLTHROUGH(); + case 2 : ctx->a+=((Uint32)k[1]<<8); ERTS_FALLTHROUGH(); case 1 : ctx->a+=k[0]; /* case 0: nothing left to add */ } @@ -1964,12 +1964,12 @@ make_internal_hash(Eterm term, erts_ihash_t salt) value = 0; switch(BYTE_SIZE(size) % sizeof(Uint64[2])) { - case 15: value ^= ((Uint64)bytes[it + 14]) << 0x30; - case 14: value ^= ((Uint64)bytes[it + 13]) << 0x28; - case 13: value ^= ((Uint64)bytes[it + 12]) << 0x20; - case 12: value ^= ((Uint64)bytes[it + 11]) << 0x18; - case 11: value ^= ((Uint64)bytes[it + 10]) << 0x10; - case 10: value ^= ((Uint64)bytes[it + 9]) << 0x08; + case 15: value ^= ((Uint64)bytes[it + 14]) << 0x30; ERTS_FALLTHROUGH(); + case 14: value ^= ((Uint64)bytes[it + 13]) << 0x28; ERTS_FALLTHROUGH(); + case 13: value ^= ((Uint64)bytes[it + 12]) << 0x20; ERTS_FALLTHROUGH(); + case 12: value ^= ((Uint64)bytes[it + 11]) << 0x18; ERTS_FALLTHROUGH(); + case 11: value ^= ((Uint64)bytes[it + 10]) << 0x10; ERTS_FALLTHROUGH(); + case 10: value ^= ((Uint64)bytes[it + 9]) << 0x08; ERTS_FALLTHROUGH(); case 9: value ^= ((Uint64)bytes[it + 8]) << 0x00; { value *= IHASH_C2; @@ -1977,15 +1977,15 @@ make_internal_hash(Eterm term, erts_ihash_t salt) value *= IHASH_C1; hash_beta ^= value; value = 0; - /* !! FALL THROUGH !! */ + ERTS_FALLTHROUGH(); } - case 8: value ^= ((Uint64)bytes[it + 7]) << 0x38; - case 7: value ^= ((Uint64)bytes[it + 6]) << 0x30; - case 6: value ^= ((Uint64)bytes[it + 5]) << 0x28; - case 5: value ^= ((Uint64)bytes[it + 4]) << 0x20; - case 4: value ^= ((Uint64)bytes[it + 3]) << 0x18; - case 3: value ^= ((Uint64)bytes[it + 2]) << 0x10; - case 2: value ^= ((Uint64)bytes[it + 1]) << 0x08; + case 8: value ^= ((Uint64)bytes[it + 7]) << 0x38; ERTS_FALLTHROUGH(); + case 7: value ^= ((Uint64)bytes[it + 6]) << 0x30; ERTS_FALLTHROUGH(); + case 6: value ^= ((Uint64)bytes[it + 5]) << 0x28; ERTS_FALLTHROUGH(); + case 5: value ^= ((Uint64)bytes[it + 4]) << 0x20; ERTS_FALLTHROUGH(); + case 4: value ^= ((Uint64)bytes[it + 3]) << 0x18; ERTS_FALLTHROUGH(); + case 3: value ^= ((Uint64)bytes[it + 2]) << 0x10; ERTS_FALLTHROUGH(); + case 2: value ^= ((Uint64)bytes[it + 1]) << 0x08; ERTS_FALLTHROUGH(); case 1: value ^= ((Uint64)bytes[it + 0]) << 0x00; { value *= IHASH_C1; diff --git a/erts/emulator/beam/erl_trace.c b/erts/emulator/beam/erl_trace.c index e28d4be00e6f..c814f81beb17 100644 --- a/erts/emulator/beam/erl_trace.c +++ b/erts/emulator/beam/erl_trace.c @@ -1226,7 +1226,7 @@ erts_call_trace(Process* p, ErtsCodeInfo *info, Binary *match_spec, &tnif, TRACE_FUN_ENABLED, am_trace_status, p->common.id)) { default: - case am_remove: *tracer_p = erts_tracer_nil; + case am_remove: *tracer_p = erts_tracer_nil; ERTS_FALLTHROUGH(); case am_discard: return 0; case am_trace: switch (call_enabled_tracer(tracer, diff --git a/erts/emulator/beam/erl_unicode.c b/erts/emulator/beam/erl_unicode.c index 9e2924946d0a..46f487bec44a 100644 --- a/erts/emulator/beam/erl_unicode.c +++ b/erts/emulator/beam/erl_unicode.c @@ -2164,6 +2164,7 @@ Eterm erts_convert_native_to_filename(Process *p, size_t size, byte *bytes) goto noconvert; case ERL_FILENAME_UTF8_MAC: mac = 1; + ERTS_FALLTHROUGH(); case ERL_FILENAME_UTF8: if (size == 0) return NIL; @@ -2334,6 +2335,7 @@ Sint erts_native_filename_need(Eterm ioterm, int encoding) need += 2; break; } /* else fall through to error */ + ERTS_FALLTHROUGH(); default: DESTROY_ESTACK(stack); return ((Sint) -1); diff --git a/erts/emulator/beam/external.c b/erts/emulator/beam/external.c index 4c8becb666a0..4e99d9e3d076 100644 --- a/erts/emulator/beam/external.c +++ b/erts/emulator/beam/external.c @@ -633,10 +633,13 @@ Sint erts_encode_ext_dist_header_finalize(ErtsDistOutputBuf* ob, switch (flgs_bytes) { case 4: *--ep = (byte) ((flgs >> 24) & 0xff); + ERTS_FALLTHROUGH(); case 3: *--ep = (byte) ((flgs >> 16) & 0xff); + ERTS_FALLTHROUGH(); case 2: *--ep = (byte) ((flgs >> 8) & 0xff); + ERTS_FALLTHROUGH(); case 1: *--ep = (byte) (flgs & 0xff); } @@ -1044,9 +1047,11 @@ erts_prepare_dist_ext(ErtsDistExternal *edep, case 6: case 5: flgs |= (((Uint32) flgsp[2]) << 16); + ERTS_FALLTHROUGH(); case 4: case 3: flgs |= (((Uint32) flgsp[1]) << 8); + ERTS_FALLTHROUGH(); case 2: case 1: flgs |= ((Uint32) flgsp[0]); @@ -3089,11 +3094,11 @@ dec_atom(ErtsDistExternal *edep, const byte* ep, Eterm* objp, int internal_nc) *objp = make_atom(n); break; case NIL_EXT: - if (internal_nc) { - *objp = INTERNAL_LOCAL_SYSNAME; - break; + if (!internal_nc) { + goto error; } - /* else: fail... */ + *objp = INTERNAL_LOCAL_SYSNAME; + break; default: error: *objp = NIL; /* Don't leave a hole in the heap */ diff --git a/erts/emulator/beam/io.c b/erts/emulator/beam/io.c index 78efccc3767c..a80b1863ea2e 100644 --- a/erts/emulator/beam/io.c +++ b/erts/emulator/beam/io.c @@ -3198,6 +3198,7 @@ static int flush_linebuf(LineBufContext *bp) resize_linebuf(bp->b); LINEBUF_DATA(*bp)[((*bp->b)->ovlen)++] = '\r'; ++bp->retlen; /* fall through instead of switching state... */ + ERTS_FALLTHROUGH(); case LINEBUF_MAIN: case LINEBUF_FULL: (*bp->b)->ovlen = 0; diff --git a/erts/emulator/beam/packet_parser.c b/erts/emulator/beam/packet_parser.c index a349c3ff8446..c4adee9f341b 100644 --- a/erts/emulator/beam/packet_parser.c +++ b/erts/emulator/beam/packet_parser.c @@ -388,6 +388,7 @@ int packet_get_length(enum PacketParseType htype, case TCP_PB_HTTPH: case TCP_PB_HTTPH_BIN: *statep = !0; + ERTS_FALLTHROUGH(); case TCP_PB_HTTP: case TCP_PB_HTTP_BIN: /* TCP_PB_HTTP: data \r\n(SP data\r\n)* */ diff --git a/erts/emulator/beam/sys.h b/erts/emulator/beam/sys.h index 02ab60816624..90085e92e11a 100644 --- a/erts/emulator/beam/sys.h +++ b/erts/emulator/beam/sys.h @@ -309,6 +309,16 @@ __decl_noreturn void __noreturn erl_assert_error(const char* expr, const char *f } while (0) #endif +/* Taken from https://best.openssf.org/Compiler-Hardening-Guides/Compiler-Options-Hardening-Guide-for-C-and-C++.html#warn-about-implicit-fallthrough-in-switch-statements */ +#ifdef __has_attribute +# if __has_attribute(__fallthrough__) +# define ERTS_FALLTHROUGH() __attribute__((__fallthrough__)) +# endif +#endif +#ifndef ERTS_FALLTHROUGH +# define ERTS_FALLTHROUGH() do {} while (0) /* fallthrough */ +#endif + /* C99: bool, true and false */ #include diff --git a/erts/emulator/beam/utils.c b/erts/emulator/beam/utils.c index d975bcd2f48d..57f809f29bb2 100644 --- a/erts/emulator/beam/utils.c +++ b/erts/emulator/beam/utils.c @@ -1450,6 +1450,7 @@ int eq(Eterm a, Eterm b) if (aa[0] != bb[0]) goto not_equal; aa++; bb++; + ERTS_FALLTHROUGH(); case HAMT_SUBTAG_NODE_BITMAP: sz = hashmap_bitcount(MAP_HEADER_VAL(hdr)); ASSERT(sz > 0 && sz < 17); @@ -1803,7 +1804,8 @@ Sint erts_cmp_compound(Eterm a, Eterm b, int exact, int eq_only) goto mixed_types; } } - } + } + ERTS_ASSERT(0 && "unreachable"); case TAG_PRIMARY_LIST: if (is_not_list(b)) { a_tag = LIST_DEF; diff --git a/erts/emulator/sys/common/erl_check_io.c b/erts/emulator/sys/common/erl_check_io.c index f821cca9c854..70986d7a0b86 100644 --- a/erts/emulator/sys/common/erl_check_io.c +++ b/erts/emulator/sys/common/erl_check_io.c @@ -589,8 +589,8 @@ abort_tasks(ErtsDrvEventState *state, int mode) return; default: ASSERT(state->type == ERTS_EV_TYPE_DRV_SEL); - /* Fall through */ } + ERTS_FALLTHROUGH(); case ERL_DRV_READ|ERL_DRV_WRITE: case ERL_DRV_WRITE: ASSERT(state->type == ERTS_EV_TYPE_DRV_SEL); @@ -599,6 +599,7 @@ abort_tasks(ErtsDrvEventState *state, int mode) state->type); if (mode == ERL_DRV_WRITE) break; + ERTS_FALLTHROUGH(); case ERL_DRV_READ: ASSERT(state->type == ERTS_EV_TYPE_DRV_SEL); abort_task(state->driver.select->inport, diff --git a/erts/epmd/src/epmd.c b/erts/epmd/src/epmd.c index e71a0528dd44..a0d5e9ab2296 100644 --- a/erts/epmd/src/epmd.c +++ b/erts/epmd/src/epmd.c @@ -523,7 +523,9 @@ static void free_all_nodes(EpmdVars *g) free(tmp); } } -void epmd_cleanup_exit(EpmdVars *g, int exitval) + +__decl_noreturn void __noreturn +epmd_cleanup_exit(EpmdVars *g, int exitval) { int i; diff --git a/erts/epmd/src/epmd_int.h b/erts/epmd/src/epmd_int.h index ed2ca330741a..523a55f3d17f 100644 --- a/erts/epmd/src/epmd_int.h +++ b/erts/epmd/src/epmd_int.h @@ -97,6 +97,21 @@ #define ASSERT(Cnd) #endif +#if __GNUC__ +# define __decl_noreturn +# ifndef __noreturn +# define __noreturn __attribute__((noreturn)) +# endif +#else +# if defined(__WIN32__) && defined(_MSC_VER) +# define __noreturn +# define __decl_noreturn __declspec(noreturn) +# else +# define __noreturn +# define __decl_noreturn +# endif +#endif + #if defined(HAVE_IN6) && defined(AF_INET6) && defined(HAVE_INET_PTON) # define EPMD6 #endif @@ -343,7 +358,7 @@ void dbg_perror(EpmdVars*,const char*,...); void kill_epmd(EpmdVars*); void epmd_call(EpmdVars*,int); void run(EpmdVars*); -void epmd_cleanup_exit(EpmdVars*, int); +__decl_noreturn void __noreturn epmd_cleanup_exit(EpmdVars*, int); int epmd_conn_close(EpmdVars*,Connection*); void stop_cli(EpmdVars *g, char *name); diff --git a/erts/include/internal/ethread.h b/erts/include/internal/ethread.h index e1aa6d412699..d0227a481fad 100644 --- a/erts/include/internal/ethread.h +++ b/erts/include/internal/ethread.h @@ -105,6 +105,15 @@ ethr_assert_failed(const char *file, int line, const char *func, const char *a); #define ETHR_ASSERT(A) ((void) 1) #endif +/* Taken from https://best.openssf.org/Compiler-Hardening-Guides/Compiler-Options-Hardening-Guide-for-C-and-C++.html#warn-about-implicit-fallthrough-in-switch-statements */ +#ifdef __has_attribute +# if __has_attribute(__fallthrough__) +# define ETHR_FALLTHROUGH() __attribute__((__fallthrough__)) +# endif +#endif +#ifndef ETHR_FALLTHROUGH +# define ETHR_FALLTHROUGH() do {} while (0) /* fallthrough */ +#endif #if defined(ETHR_PTHREADS) /* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *\ diff --git a/erts/lib_src/common/erl_printf_format.c b/erts/lib_src/common/erl_printf_format.c index d59a5df2e506..f4a32615b7c0 100644 --- a/erts/lib_src/common/erl_printf_format.c +++ b/erts/lib_src/common/erl_printf_format.c @@ -45,6 +45,17 @@ #include "erl_printf.h" #include "erl_printf_format.h" + +/* Taken from https://best.openssf.org/Compiler-Hardening-Guides/Compiler-Options-Hardening-Guide-for-C-and-C++.html#warn-about-implicit-fallthrough-in-switch-statements */ +#ifdef __has_attribute +# if __has_attribute(__fallthrough__) +# define FALLTHROUGH() __attribute__((__fallthrough__)) +# endif +#endif +#ifndef FALLTHROUGH +# define FALLTHROUGH() do {} while (0) /* fallthrough */ +#endif + #ifdef DEBUG #include #define ASSERT(X) assert(X) @@ -234,6 +245,7 @@ static int fmt_uword(fmtfn_t fn,void* arg,int sign,ErlPfUWord uval, break; case FMTC_X: dc = heX; + FALLTHROUGH(); case FMTC_x: base = 16; break; @@ -286,6 +298,7 @@ static int fmt_long_long(fmtfn_t fn,void* arg,int sign, break; case FMTC_X: dc = heX; + FALLTHROUGH(); case FMTC_x: base = 16; break; diff --git a/erts/lib_src/common/ethr_mutex.c b/erts/lib_src/common/ethr_mutex.c index 636adfe397ca..abfa65964910 100644 --- a/erts/lib_src/common/ethr_mutex.c +++ b/erts/lib_src/common/ethr_mutex.c @@ -2657,6 +2657,7 @@ ethr_rwmutex_init_opt(ethr_rwmutex *rwmtx, ethr_rwmutex_opt *opt) rwmtx->type = ETHR_RWMUTEX_TYPE_EXTREMELY_FREQUENT_READ; } /* Fall through */ + ETHR_FALLTHROUGH(); case ETHR_RWMUTEX_TYPE_EXTREMELY_FREQUENT_READ: { int length; @@ -2688,6 +2689,7 @@ ethr_rwmutex_init_opt(ethr_rwmutex *rwmtx, ethr_rwmutex_opt *opt) break; } } + ETHR_FALLTHROUGH(); case ETHR_RWMUTEX_TYPE_NORMAL: rwmtx->tdata.rs = 0; break; diff --git a/lib/erl_interface/src/misc/ei_format.c b/lib/erl_interface/src/misc/ei_format.c index 6ae5521357b0..74846cb50e7b 100644 --- a/lib/erl_interface/src/misc/ei_format.c +++ b/lib/erl_interface/src/misc/ei_format.c @@ -116,6 +116,7 @@ static int eiformat(const char** fmt, union arg** args, ei_x_buff* x) ei_x_free(&x2); break; } + EI_FALLTHROUGH(); default: if (isdigit((int)*p)) res = pdigit(&p, x); diff --git a/lib/erl_interface/src/misc/eidef.h b/lib/erl_interface/src/misc/eidef.h index 01479887c83d..09d8c8c26189 100644 --- a/lib/erl_interface/src/misc/eidef.h +++ b/lib/erl_interface/src/misc/eidef.h @@ -58,6 +58,16 @@ typedef int socklen_t; # define HAVE_ISFINITE #endif +/* Taken from https://best.openssf.org/Compiler-Hardening-Guides/Compiler-Options-Hardening-Guide-for-C-and-C++.html#warn-about-implicit-fallthrough-in-switch-statements */ +#ifdef __has_attribute +# if __has_attribute(__fallthrough__) +# define EI_FALLTHROUGH() __attribute__((__fallthrough__)) +# endif +#endif +#ifndef EI_FALLTHROUGH +# define EI_FALLTHROUGH() do {} while (0) /* fallthrough */ +#endif + typedef unsigned char uint8; /* FIXME use configure */ typedef unsigned short uint16; typedef unsigned int uint32; diff --git a/lib/erl_interface/src/misc/get_type.c b/lib/erl_interface/src/misc/get_type.c index d76119ca6264..8ff42fd9d5e7 100644 --- a/lib/erl_interface/src/misc/get_type.c +++ b/lib/erl_interface/src/misc/get_type.c @@ -38,12 +38,14 @@ int ei_get_type(const char *buf, const int *index, int *type, int *len) case ERL_SMALL_ATOM_EXT: case ERL_SMALL_ATOM_UTF8_EXT: *type = ERL_ATOM_EXT; + EI_FALLTHROUGH(); case ERL_SMALL_TUPLE_EXT: *len = get8(s); break; case ERL_ATOM_UTF8_EXT: *type = ERL_ATOM_EXT; + EI_FALLTHROUGH(); case ERL_ATOM_EXT: case ERL_STRING_EXT: *len = get16be(s); diff --git a/lib/erl_interface/src/prog/erl_call.c b/lib/erl_interface/src/prog/erl_call.c index 74750d78de8e..bcbe11f8d9a9 100644 --- a/lib/erl_interface/src/prog/erl_call.c +++ b/lib/erl_interface/src/prog/erl_call.c @@ -78,6 +78,27 @@ #include #include +/* In VC++, noreturn is a declspec that has to be before the types, + * but in GNUC it is an attribute to be placed between return type + * and function name, hence __decl_noreturn __noreturn + * + * at some platforms (e.g. Android) __noreturn is defined at sys/cdef.h + */ +#if __GNUC__ +# define __decl_noreturn +# ifndef __noreturn +# define __noreturn __attribute__((noreturn)) +# endif +#else +# if defined(__WIN32__) && defined(_MSC_VER) +# define __noreturn +# define __decl_noreturn __declspec(noreturn) +# else +# define __noreturn +# define __decl_noreturn +# endif +#endif + #include "ei.h" #include "ei_resolve.h" @@ -125,9 +146,9 @@ struct call_flags { /* start an erlang system */ int erl_start_sys(ei_cnode *ec, char *alive, Erl_IpAddr addr, int flags, char *erl, char *add_args[]); -static void usage_arg(const char *progname, const char *switchname); -static void usage_error(const char *progname, const char *switchname); -static void usage(const char *progname); +__decl_noreturn static void __noreturn usage_arg(const char *progname, const char *switchname); +__decl_noreturn static void __noreturn usage_error(const char *progname, const char *switchname); +__decl_noreturn static void __noreturn usage(const char *progname); static int get_module(char **mbuf, char **mname); static int do_connect(ei_cnode *ec, char *nodename, struct call_flags *flags); static int read_stdin(char **buf); @@ -140,7 +161,9 @@ static char* ei_chk_strdup(char *s); static int rpc_print_node_stdout(ei_cnode* ec, int fd, char *mod, char *fun, const char* inbuf, int inbuflen, ei_x_buff* x); -static void exit_free_flags_fields(int exit_status, struct call_flags* flags); +__decl_noreturn static void __noreturn exit_free_flags_fields( + int exit_status, + struct call_flags* flags); /* Converts the given hostname to a shortname, if required. */ static void format_node_hostname(const struct call_flags *flags, @@ -1032,19 +1055,19 @@ static void usage_noexit(const char *progname) { fprintf(stderr," -x use specified erl start script, default is erl\n"); } -static void usage_arg(const char *progname, const char *switchname) { +__decl_noreturn static void __noreturn usage_arg(const char *progname, const char *switchname) { fprintf(stderr, "Missing argument(s) for \'%s\'.\n", switchname); usage_noexit(progname); exit(1); } -static void usage_error(const char *progname, const char *switchname) { +__decl_noreturn static void __noreturn usage_error(const char *progname, const char *switchname) { fprintf(stderr, "Illegal argument \'%s\'.\n", switchname); usage_noexit(progname); exit(1); } -static void usage(const char *progname) { +void __noreturn usage(const char *progname) { usage_noexit(progname); exit(0); } @@ -1181,7 +1204,8 @@ static int rpc_print_node_stdout(ei_cnode* ec, int fd, char *mod, } -void exit_free_flags_fields(int exit_status, struct call_flags* flags) { +__decl_noreturn static void __noreturn +exit_free_flags_fields(int exit_status, struct call_flags* flags) { if (flags->script != NULL) { free(flags->script); } From 8bd211eb3365ab536c9ab4e43ec8a3e67ae67366 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Mon, 28 Oct 2024 09:33:15 +0100 Subject: [PATCH 02/10] erts: Fix bugs found by -Wimplicit-fallthrough --- erts/emulator/beam/io.c | 3 +++ erts/lib_src/common/erl_printf_format.c | 1 + lib/erl_interface/src/misc/show_msg.c | 1 + 3 files changed, 5 insertions(+) diff --git a/erts/emulator/beam/io.c b/erts/emulator/beam/io.c index a80b1863ea2e..be2a3e36a7af 100644 --- a/erts/emulator/beam/io.c +++ b/erts/emulator/beam/io.c @@ -5431,10 +5431,13 @@ erts_stale_drv_select(Eterm port, switch (mode) { case ERL_DRV_READ | ERL_DRV_WRITE: type = "Input/Output"; + break; case ERL_DRV_WRITE: type = "Output"; + break; case ERL_DRV_READ: type = "Input"; + break; default: type = ""; } diff --git a/erts/lib_src/common/erl_printf_format.c b/erts/lib_src/common/erl_printf_format.c index f4a32615b7c0..9449e9f26a66 100644 --- a/erts/lib_src/common/erl_printf_format.c +++ b/erts/lib_src/common/erl_printf_format.c @@ -575,6 +575,7 @@ int erts_printf_format(fmtfn_t fn, void* arg, char* fmt, va_list ap) #else #error No 16-bit integer datatype found #endif + break; case 8: #if SIZEOF_CHAR == 1 fmt |= FMTL_hh; diff --git a/lib/erl_interface/src/misc/show_msg.c b/lib/erl_interface/src/misc/show_msg.c index 87fd9701653b..482788eee7a7 100644 --- a/lib/erl_interface/src/misc/show_msg.c +++ b/lib/erl_interface/src/misc/show_msg.c @@ -157,6 +157,7 @@ int ei_show_sendmsg(FILE *stream, const char *header, const char *msgbuf) if (ei_decode_pid(header,&index,&msg.from) || ei_decode_pid(header,&index,&msg.to)) return -1; mbuf = header+index; + break; case ERL_EXIT_TT: case ERL_EXIT2_TT: From a152e03a64f6d03f97baaa6a370330fe4e47f5f2 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Mon, 28 Oct 2024 09:34:44 +0100 Subject: [PATCH 03/10] erts: Fix -Wformat=2 warnings --- erts/config.h.in | 4 ++ erts/configure | 24 ++++++++++ erts/configure.ac | 11 +++++ erts/etc/unix/run_erl.c | 21 +++++++-- erts/lib_src/common/erl_misc_utils.c | 61 ++++++++++++++----------- erts/lib_src/common/erl_printf_format.c | 7 +++ 6 files changed, 98 insertions(+), 30 deletions(-) diff --git a/erts/config.h.in b/erts/config.h.in index 733e18434043..8a1d0cdb5cb6 100644 --- a/erts/config.h.in +++ b/erts/config.h.in @@ -672,6 +672,10 @@ '-Waddress-of-packed-member'') */ #undef HAVE_GCC_DIAG_IGNORE_WADDRESS_OF_PACKED_MEMBER +/* define if compiler support _Pragma('GCC diagnostic ignored + '-Wformat-nonliteral'') */ +#undef HAVE_GCC_DIAG_IGNORE_WFORMAT_NONLITERAL + /* Define to 1 if you have a good `getaddrinfo' function. */ #undef HAVE_GETADDRINFO diff --git a/erts/configure b/erts/configure index 98efb385c14f..0459e638bcd6 100755 --- a/erts/configure +++ b/erts/configure @@ -26895,6 +26895,30 @@ fi rm -f core conftest.err conftest.$ac_objext conftest.beam conftest.$ac_ext CFLAGS="$saved_CFLAGS" +saved_CFLAGS="$CFLAGS" +CFLAGS="-Werror $CFLAGS" +cat confdefs.h - <<_ACEOF >conftest.$ac_ext +/* end confdefs.h. */ + +int +main (void) +{ +_Pragma("GCC diagnostic push") + _Pragma("GCC diagnostic ignored \"-Wformat-nonliteral\"") + _Pragma("GCC diagnostic pop") + + ; + return 0; +} +_ACEOF +if ac_fn_c_try_compile "$LINENO" +then : + +printf "%s\n" "#define HAVE_GCC_DIAG_IGNORE_WFORMAT_NONLITERAL 1" >>confdefs.h + +fi +rm -f core conftest.err conftest.$ac_objext conftest.beam conftest.$ac_ext +CFLAGS="$saved_CFLAGS" if test "x$GCC" = xyes; then diff --git a/erts/configure.ac b/erts/configure.ac index e79def7c42bf..5bca25bb0bf9 100644 --- a/erts/configure.ac +++ b/erts/configure.ac @@ -3621,6 +3621,17 @@ AC_COMPILE_IFELSE([AC_LANG_PROGRAM([[]], [[_Pragma("GCC diagnostic push") define if compiler support _Pragma('GCC diagnostic ignored '-Waddress-of-packed-member''))],[]) CFLAGS="$saved_CFLAGS" +dnl ---------------------------------------------------------------------- +dnl Check for GCC diagnostic ignored "-Wformat-nonliteral" +dnl ---------------------------------------------------------------------- +saved_CFLAGS="$CFLAGS" +CFLAGS="-Werror $CFLAGS" +AC_COMPILE_IFELSE([AC_LANG_PROGRAM([[]], [[_Pragma("GCC diagnostic push") + _Pragma("GCC diagnostic ignored \"-Wformat-nonliteral\"") + _Pragma("GCC diagnostic pop") + ]])],[AC_DEFINE(HAVE_GCC_DIAG_IGNORE_WFORMAT_NONLITERAL,1, + define if compiler support _Pragma('GCC diagnostic ignored '-Wformat-nonliteral''))],[]) +CFLAGS="$saved_CFLAGS" dnl ---------------------------------------------------------------------- dnl Enable any -Werror flags diff --git a/erts/etc/unix/run_erl.c b/erts/etc/unix/run_erl.c index 615764663058..b0966de60566 100644 --- a/erts/etc/unix/run_erl.c +++ b/erts/etc/unix/run_erl.c @@ -488,6 +488,21 @@ int main(int argc, char **argv) return 0; } /* main() */ +/* Broken out in order to do GCC diagnostic ignore here */ +#ifdef HAVE_GCC_DIAG_IGNORE_WFORMAT_NONLITERAL +_Pragma("GCC diagnostic push"); +_Pragma("GCC diagnostic ignored \"-Wformat-nonliteral\""); +#endif +static int dynamic_strftime( + char *__restrict__ log_alive_buffer, + const char *__restrict__ log_alive_format, + const struct tm *__restrict__ tmptr) { + return strftime(log_alive_buffer, ALIVE_BUFFSIZ, log_alive_format, tmptr); +} +#ifdef HAVE_GCC_DIAG_IGNORE_WFORMAT_NONLITERAL +_Pragma("GCC diagnostic pop"); +#endif + /* pass_on() * Is the work loop of the logger. Selects on the pipe to the to_erl * program erlang. If input arrives from to_erl it is passed on to @@ -584,8 +599,7 @@ static void pass_on(pid_t childpid) } else { tmptr = localtime(&now); } - if (!strftime(log_alive_buffer, ALIVE_BUFFSIZ, log_alive_format, - tmptr)) { + if (!dynamic_strftime(log_alive_buffer, log_alive_format, tmptr)) { strn_cpy(log_alive_buffer, sizeof(log_alive_buffer), "(could not format time in 256 positions " "with current format string.)"); @@ -858,8 +872,7 @@ static int open_log(int log_num, int flags) } else { tmptr = localtime(&now); } - if (!strftime(log_buffer, ALIVE_BUFFSIZ, log_alive_format, - tmptr)) { + if (!dynamic_strftime(log_buffer, log_alive_format, tmptr)) { strn_cpy(log_buffer, sizeof(log_buffer), "(could not format time in 256 positions " "with current format string.)"); diff --git a/erts/lib_src/common/erl_misc_utils.c b/erts/lib_src/common/erl_misc_utils.c index 01f8b35ffe30..74941ce570d0 100644 --- a/erts/lib_src/common/erl_misc_utils.c +++ b/erts/lib_src/common/erl_misc_utils.c @@ -1124,7 +1124,6 @@ get_cgroup_path(const char *controller, const char **out) { enum cgroup_version_t version; char mount_line[10 << 10]; - const char *mount_format; const char *child_path; FILE *mount_file; @@ -1134,27 +1133,10 @@ get_cgroup_path(const char *controller, } version = get_cgroup_child_path(controller, &child_path); - switch (version) { - case ERTS_CGROUP_NONE: + + if (version == ERTS_CGROUP_NONE) { fclose(mount_file); return ERTS_CGROUP_NONE; - case ERTS_CGROUP_V1: - /* Format: - * [Mount id] [Parent id] [Major] [Minor] [Root] [Mounted at] \ - * [Mount flags] ... (options terminated by a single hyphen) ... \ - * [FS type] [Mount source] [Flags] - * - * (See proc(5) for a more complete description.) - * - * This fails if any of the fs options contain a hyphen, but this is - * not likely to happen on a cgroup, so we just skip such lines. */ - mount_format = "%*d %*d %*d:%*d %4095s %4095s %*s%*[^-]- " - "cgroup %*s %511[^\n]\n"; - break; - case ERTS_CGROUP_V2: - mount_format = "%*d %*d %*d:%*d %4095s %4095s %*s%*[^-]- " - "cgroup2 %*s %511[^\n]\n"; - break; } /* As a controller can only belong to one hierarchy, regardless of @@ -1166,12 +1148,39 @@ get_cgroup_path(const char *controller, char root_path[4 << 10]; char fs_flags[512]; - if (sscanf(mount_line, - mount_format, - root_path, - mount_path, - fs_flags) != 3) { - continue; + switch (version) { + + case ERTS_CGROUP_V1: + /* Format: + * [Mount id] [Parent id] [Major] [Minor] [Root] [Mounted at] \ + * [Mount flags] ... (options terminated by a single hyphen) ... \ + * [FS type] [Mount source] [Flags] + * + * (See proc(5) for a more complete description.) + * + * This fails if any of the fs options contain a hyphen, but this is + * not likely to happen on a cgroup, so we just skip such lines. */ + if (sscanf(mount_line, + "%*d %*d %*d:%*d %4095s %4095s %*s%*[^-]- " + "cgroup %*s %511[^\n]\n", + root_path, + mount_path, + fs_flags) != 3) { + continue; + } + break; + case ERTS_CGROUP_V2: + if (sscanf(mount_line, + "%*d %*d %*d:%*d %4095s %4095s %*s%*[^-]- " + "cgroup2 %*s %511[^\n]\n", + root_path, + mount_path, + fs_flags) != 3) { + continue; + } + break; + default: + ASSERT(0 && "Only V1 and V2 should come here"); } if (version == ERTS_CGROUP_V2) { diff --git a/erts/lib_src/common/erl_printf_format.c b/erts/lib_src/common/erl_printf_format.c index 9449e9f26a66..e854825a2a69 100644 --- a/erts/lib_src/common/erl_printf_format.c +++ b/erts/lib_src/common/erl_printf_format.c @@ -426,7 +426,14 @@ static int fmt_double(fmtfn_t fn,void*arg,double val, } } +#ifdef HAVE_GCC_DIAG_IGNORE_WFORMAT_NONLITERAL +_Pragma("GCC diagnostic push"); +_Pragma("GCC diagnostic ignored \"-Wformat-nonliteral\""); +#endif size = sprintf(bufp, format_str, precision, val); +#ifdef HAVE_GCC_DIAG_IGNORE_WFORMAT_NONLITERAL +_Pragma("GCC diagnostic pop"); +#endif if (size < 0) { if (errno > 0) res = -errno; From 7091f816f35f557e77f42942d210b7ee819ee029 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Mon, 28 Oct 2024 11:01:07 +0100 Subject: [PATCH 04/10] otp: Ignore -Werror in CFLAGS during configure --- erts/configure | 10 +++++++--- erts/configure.ac | 14 ++------------ lib/common_test/configure | 16 ++++++++++++++++ lib/common_test/configure.ac | 4 ++++ lib/crypto/configure | 18 ++++++++++++++++++ lib/crypto/configure.ac | 4 ++++ lib/erl_interface/configure | 18 +++++++++++++++++- lib/erl_interface/configure.ac | 6 +++++- lib/megaco/configure | 16 ++++++++++++++++ lib/megaco/configure.ac | 4 ++++ lib/odbc/configure | 16 ++++++++++++++++ lib/odbc/configure.ac | 4 ++++ lib/snmp/configure | 16 ++++++++++++++++ lib/snmp/configure.ac | 4 ++++ lib/wx/configure | 19 ++++++++++++++++--- lib/wx/configure.ac | 7 ++++--- make/autoconf/otp.m4 | 17 +++++++++++++++++ make/configure | 16 ++++++++++++++++ make/configure.ac | 4 ++++ 19 files changed, 190 insertions(+), 23 deletions(-) diff --git a/erts/configure b/erts/configure index 0459e638bcd6..c972cb283d98 100755 --- a/erts/configure +++ b/erts/configure @@ -702,7 +702,6 @@ PROFILE_COMPILER USE_PGO XCRUN LLVM_PROFDATA -WERRORFLAGS WFLAGS DEBUG_FLAGS ERTS_CONFIG_H_IDIR @@ -3663,6 +3662,11 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu + + + + + @@ -8302,7 +8306,6 @@ rm -f core conftest.err conftest.$ac_objext conftest.beam conftest.$ac_ext - ## Check if we can do profile guided optimization of beam_emu { printf "%s\n" "$as_me:${as_lineno-$LINENO}: checking whether $CC accepts -fprofile-generate -Werror..." >&5 @@ -26921,8 +26924,9 @@ rm -f core conftest.err conftest.$ac_objext conftest.beam conftest.$ac_ext CFLAGS="$saved_CFLAGS" + if test "x$GCC" = xyes; then - CFLAGS="$WERRORFLAGS $CFLAGS" + CFLAGS="$WERRORFLAGS $CFLAGS" fi diff --git a/erts/configure.ac b/erts/configure.ac index 5bca25bb0bf9..f546f1a5a5fd 100644 --- a/erts/configure.ac +++ b/erts/configure.ac @@ -29,14 +29,7 @@ m4_include([otp.m4]) LM_PRECIOUS_VARS -dnl We check if -Werror was given on command line and if so -dnl we disable it for the configure and only use it when -dnl actually building erts -no_werror_CFLAGS=$(echo " $CFLAGS " | sed 's/ -Werror / /g') -if test "X $CFLAGS " != "X$no_werror_CFLAGS"; then - CFLAGS="$no_werror_CFLAGS" - WERRORFLAGS=-Werror -fi +ERL_PUSH_WERROR dnl How to set srcdir absolute is taken from the GNU Emacs distribution #### Make srcdir absolute, if it isn't already. It's important to @@ -630,7 +623,6 @@ AC_COMPILE_IFELSE([AC_LANG_PROGRAM([[]],[[ dnl DEBUG_FLAGS is obsolete (I hope) AC_SUBST(DEBUG_FLAGS) AC_SUBST(WFLAGS) -AC_SUBST(WERRORFLAGS) ## Check if we can do profile guided optimization of beam_emu LM_CHECK_RUN_CFLAG([-fprofile-generate -Werror],[PROFILE_GENERATE]) @@ -3637,9 +3629,7 @@ dnl ---------------------------------------------------------------------- dnl Enable any -Werror flags dnl ---------------------------------------------------------------------- -if test "x$GCC" = xyes; then - CFLAGS="$WERRORFLAGS $CFLAGS" -fi +ERL_POP_WERROR dnl ---------------------------------------------------------------------- dnl Enable build determinism flag diff --git a/lib/common_test/configure b/lib/common_test/configure index ebe9da56f81d..6532c0389f5f 100755 --- a/lib/common_test/configure +++ b/lib/common_test/configure @@ -1917,6 +1917,17 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu + + + + + + +no_werror_CFLAGS=$(echo " $CFLAGS " | sed 's/ -Werror / /g') +if test "X $CFLAGS " != "X$no_werror_CFLAGS"; then + CFLAGS="$no_werror_CFLAGS" + WERRORFLAGS=-Werror +fi @@ -2124,6 +2135,11 @@ fi TARGET=$host + +if test "x$GCC" = xyes; then + CFLAGS="$WERRORFLAGS $CFLAGS" +fi + ac_config_files="$ac_config_files priv/$host/Makefile:priv/Makefile.in" cat >confcache <<\_ACEOF diff --git a/lib/common_test/configure.ac b/lib/common_test/configure.ac index 490a64328d6f..4f08ae10d3f4 100644 --- a/lib/common_test/configure.ac +++ b/lib/common_test/configure.ac @@ -5,10 +5,14 @@ m4_include([otp.m4]) AC_CONFIG_AUX_DIR([${ERL_TOP}/make/autoconf]) +ERL_PUSH_WERROR + ERL_CANONICAL_SYSTEM_TYPE TARGET=$host AC_SUBST(TARGET) +ERL_POP_WERROR + AC_CONFIG_FILES([priv/$host/Makefile:priv/Makefile.in]) AC_OUTPUT diff --git a/lib/crypto/configure b/lib/crypto/configure index 02a040621243..efc69ef0e2c6 100755 --- a/lib/crypto/configure +++ b/lib/crypto/configure @@ -3036,6 +3036,17 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu + + + + + + +no_werror_CFLAGS=$(echo " $CFLAGS " | sed 's/ -Werror / /g') +if test "X $CFLAGS " != "X$no_werror_CFLAGS"; then + CFLAGS="$no_werror_CFLAGS" + WERRORFLAGS=-Werror +fi @@ -8047,6 +8058,13 @@ LDFLAGS="$saveLDFLAGS" LIBS="$saveLIBS" +no_werror_CFLAGS=$(echo " $CFLAGS " | sed 's/ -Werror / /g') +if test "X $CFLAGS " != "X$no_werror_CFLAGS"; then + CFLAGS="$no_werror_CFLAGS" + WERRORFLAGS=-Werror +fi + + diff --git a/lib/crypto/configure.ac b/lib/crypto/configure.ac index b5b591424710..fb31f7d350df 100644 --- a/lib/crypto/configure.ac +++ b/lib/crypto/configure.ac @@ -30,6 +30,8 @@ m4_include([otp.m4]) AC_CONFIG_AUX_DIR([${ERL_TOP}/make/autoconf]) +ERL_PUSH_WERROR + ERL_CANONICAL_SYSTEM_TYPE AC_LANG(C) @@ -922,6 +924,8 @@ CFLAGS="$saveCFLAGS" LDFLAGS="$saveLDFLAGS" LIBS="$saveLIBS" +ERL_PUSH_WERROR + AC_SUBST(SSL_INCLUDE) AC_SUBST(SSL_INCDIR) AC_SUBST(SSL_LIBDIR) diff --git a/lib/erl_interface/configure b/lib/erl_interface/configure index 52126d4f6169..13d1b0c15310 100755 --- a/lib/erl_interface/configure +++ b/lib/erl_interface/configure @@ -2898,6 +2898,17 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu + + + + + + +no_werror_CFLAGS=$(echo " $CFLAGS " | sed 's/ -Werror / /g') +if test "X $CFLAGS " != "X$no_werror_CFLAGS"; then + CFLAGS="$no_werror_CFLAGS" + WERRORFLAGS=-Werror +fi #### Make srcdir absolute, if it isn't already. It's important to #### avoid running the path through pwd unnecessary, since pwd can @@ -9944,7 +9955,7 @@ esac # --------------------------------------------------------------------------- -WFLAGS="$DED_WERRORFLAGS $DED_WARN_FLAGS" +WFLAGS="$WERRORFLAGS $DED_WERRORFLAGS $DED_WARN_FLAGS" if test "x$GCC" = xyes then : WFLAGS="$WFLAGS -Wmissing-declarations -Wnested-externs -Winline" @@ -10037,6 +10048,11 @@ esac fi + +if test "x$GCC" = xyes; then + CFLAGS="$WERRORFLAGS $CFLAGS" +fi + # --------------------------------------------------------------------------- # XXX # --------------------------------------------------------------------------- diff --git a/lib/erl_interface/configure.ac b/lib/erl_interface/configure.ac index 4874fd031348..1b20cc8d65b4 100644 --- a/lib/erl_interface/configure.ac +++ b/lib/erl_interface/configure.ac @@ -31,6 +31,8 @@ AC_PREREQ([2.72]) m4_include([otp.m4]) +ERL_PUSH_WERROR + dnl How to set srcdir absolute is taken from the GNU Emacs distribution #### Make srcdir absolute, if it isn't already. It's important to #### avoid running the path through pwd unnecessary, since pwd can @@ -325,7 +327,7 @@ AS_CASE(["$threads_disabled"], # --------------------------------------------------------------------------- AC_SUBST(WFLAGS) -WFLAGS="$DED_WERRORFLAGS $DED_WARN_FLAGS" +WFLAGS="$WERRORFLAGS $DED_WERRORFLAGS $DED_WARN_FLAGS" AS_IF([test "x$GCC" = xyes], [WFLAGS="$WFLAGS -Wmissing-declarations -Wnested-externs -Winline"]) @@ -338,6 +340,8 @@ LM_TRY_ENABLE_CFLAG([-fno-common], [CFLAGS]) # No strict aliasing until we determined it is safe... LM_TRY_ENABLE_CFLAG([-fno-strict-aliasing], [CFLAGS]) +ERL_POP_WERROR + # --------------------------------------------------------------------------- # XXX # --------------------------------------------------------------------------- diff --git a/lib/megaco/configure b/lib/megaco/configure index 1ee2b0325a01..fec557b6b09d 100755 --- a/lib/megaco/configure +++ b/lib/megaco/configure @@ -2779,6 +2779,10 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu + + + + @@ -2985,6 +2989,13 @@ fi +no_werror_CFLAGS=$(echo " $CFLAGS " | sed 's/ -Werror / /g') +if test "X $CFLAGS " != "X$no_werror_CFLAGS"; then + CFLAGS="$no_werror_CFLAGS" + WERRORFLAGS=-Werror +fi + + @@ -5971,6 +5982,11 @@ if test "$PERL" = no_perl; then as_fn_error $? "Perl is required to build the flex scanner!" "$LINENO" 5 fi + +if test "x$GCC" = xyes; then + CFLAGS="$WERRORFLAGS $CFLAGS" +fi + ac_config_files="$ac_config_files examples/meas/Makefile:examples/meas/Makefile.in" cat >confcache <<\_ACEOF diff --git a/lib/megaco/configure.ac b/lib/megaco/configure.ac index 6f243be8d911..a5c3db9e1aae 100644 --- a/lib/megaco/configure.ac +++ b/lib/megaco/configure.ac @@ -33,6 +33,8 @@ AC_CONFIG_AUX_DIR([${ERL_TOP}/make/autoconf]) ERL_CANONICAL_SYSTEM_TYPE +ERL_PUSH_WERROR + dnl ---------------------------------------------------------------------- dnl Checks for programs. dnl ---------------------------------------------------------------------- @@ -169,6 +171,8 @@ if test "$PERL" = no_perl; then AC_MSG_ERROR([Perl is required to build the flex scanner!]) fi +ERL_POP_WERROR + AC_CONFIG_FILES([examples/meas/Makefile:examples/meas/Makefile.in]) AC_OUTPUT AC_CONFIG_FILES([src/flex/$host/Makefile:src/flex/Makefile.in]) diff --git a/lib/odbc/configure b/lib/odbc/configure index 1d27999c11e6..e43c587ccc87 100755 --- a/lib/odbc/configure +++ b/lib/odbc/configure @@ -2878,6 +2878,17 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu + + + + + + +no_werror_CFLAGS=$(echo " $CFLAGS " | sed 's/ -Werror / /g') +if test "X $CFLAGS " != "X$no_werror_CFLAGS"; then + CFLAGS="$no_werror_CFLAGS" + WERRORFLAGS=-Werror +fi @@ -6071,6 +6082,11 @@ fi fi + +if test "x$GCC" = xyes; then + CFLAGS="$WERRORFLAGS $CFLAGS" +fi + ac_config_files="$ac_config_files c_src/$host/Makefile:c_src/Makefile.in" cat >confcache <<\_ACEOF diff --git a/lib/odbc/configure.ac b/lib/odbc/configure.ac index febdd044a573..19abc17670fe 100644 --- a/lib/odbc/configure.ac +++ b/lib/odbc/configure.ac @@ -31,6 +31,8 @@ m4_include([otp.m4]) AC_CONFIG_AUX_DIR([${ERL_TOP}/make/autoconf]) +ERL_PUSH_WERROR + ERL_CANONICAL_SYSTEM_TYPE AC_ARG_WITH(odbc, @@ -256,5 +258,7 @@ AS_IF([test "x$GCC" = xyes], LM_TRY_ENABLE_CFLAG([-Werror=return-type], [CFLAGS]) ]) +ERL_POP_WERROR + AC_CONFIG_FILES([c_src/$host/Makefile:c_src/Makefile.in]) AC_OUTPUT diff --git a/lib/snmp/configure b/lib/snmp/configure index 2cc4116fa912..4d91509f6385 100755 --- a/lib/snmp/configure +++ b/lib/snmp/configure @@ -1912,6 +1912,17 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu + + + + + + +no_werror_CFLAGS=$(echo " $CFLAGS " | sed 's/ -Werror / /g') +if test "X $CFLAGS " != "X$no_werror_CFLAGS"; then + CFLAGS="$no_werror_CFLAGS" + WERRORFLAGS=-Werror +fi @@ -2191,6 +2202,11 @@ fi +if test "x$GCC" = xyes; then + CFLAGS="$WERRORFLAGS $CFLAGS" +fi + + ac_config_files="$ac_config_files mibs/Makefile:mibs/Makefile.in" ac_config_files="$ac_config_files src/agent/Makefile:src/agent/Makefile.in" diff --git a/lib/snmp/configure.ac b/lib/snmp/configure.ac index 8f4c1fd83390..4f7954d4fb81 100644 --- a/lib/snmp/configure.ac +++ b/lib/snmp/configure.ac @@ -31,6 +31,8 @@ m4_include([otp.m4]) AC_CONFIG_AUX_DIRS([${ERL_TOP}/make/autoconf]) +ERL_PUSH_WERROR + dnl ---------------------------------------------------------------------- dnl Checks for programs. dnl ---------------------------------------------------------------------- @@ -64,6 +66,8 @@ fi dnl ---------------------------------------------------------------------- +ERL_POP_WERROR + AC_SUBST(SNMP_EMPTY_PDU_SIZE_DEFAULT) AC_CONFIG_FILES([mibs/Makefile:mibs/Makefile.in]) AC_CONFIG_FILES([src/agent/Makefile:src/agent/Makefile.in]) diff --git a/lib/wx/configure b/lib/wx/configure index 47721faca3bf..776db74b11c8 100755 --- a/lib/wx/configure +++ b/lib/wx/configure @@ -3093,6 +3093,17 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu + + + + + + +no_werror_CFLAGS=$(echo " $CFLAGS " | sed 's/ -Werror / /g') +if test "X $CFLAGS " != "X$no_werror_CFLAGS"; then + CFLAGS="$no_werror_CFLAGS" + WERRORFLAGS=-Werror +fi ## Delete previous failed configure results if test -f ./CONF_INFO; then @@ -7332,6 +7343,11 @@ mkdir -p $WXERL_SYS_TYPE CONFIG_STATUS=$WXERL_SYS_TYPE/config.status +if test "x$GCC" = xyes; then + CFLAGS="$WERRORFLAGS $CFLAGS" +fi + + ac_config_files="$ac_config_files config.mk c_src/Makefile" @@ -8493,6 +8509,3 @@ if test X"$CORES" != X"" ; then echo "Configure dumped core files" > ignore_core_files fi - - - diff --git a/lib/wx/configure.ac b/lib/wx/configure.ac index ba34c709fc2d..3cde261a9387 100644 --- a/lib/wx/configure.ac +++ b/lib/wx/configure.ac @@ -26,6 +26,8 @@ AC_CONFIG_AUX_DIR([${ERL_TOP}/make/autoconf]) AC_PREREQ([2.71]) +ERL_PUSH_WERROR + ## Delete previous failed configure results if test -f ./CONF_INFO; then rm ./CONF_INFO @@ -749,6 +751,8 @@ AC_SUBST(WXERL_SYS_TYPE) mkdir -p $WXERL_SYS_TYPE CONFIG_STATUS=$WXERL_SYS_TYPE/config.status +ERL_POP_WERROR + dnl AC_CONFIG_FILES([ @@ -762,6 +766,3 @@ CORES=`ls core* 2>/dev/null` if test X"$CORES" != X"" ; then echo "Configure dumped core files" > ignore_core_files fi - - - diff --git a/make/autoconf/otp.m4 b/make/autoconf/otp.m4 index 3d7341b0d442..f0fd384c4bd2 100644 --- a/make/autoconf/otp.m4 +++ b/make/autoconf/otp.m4 @@ -30,6 +30,23 @@ dnl macros specific dnl to the Erlang system are prefixed ERL_ (this is dnl not always consistently made...). dnl +dnl We check if -Werror was given on command line and if so +dnl we disable it for the configure and only use it when +dnl actually building erts +AC_DEFUN([ERL_PUSH_WERROR], +[ +no_werror_CFLAGS=$(echo " $CFLAGS " | sed 's/ -Werror / /g') +if test "X $CFLAGS " != "X$no_werror_CFLAGS"; then + CFLAGS="$no_werror_CFLAGS" + WERRORFLAGS=-Werror +fi]) + +AC_DEFUN([ERL_POP_WERROR], +[ +if test "x$GCC" = xyes; then + CFLAGS="$WERRORFLAGS $CFLAGS" +fi]) + AC_DEFUN([ERL_CANONICAL_SYSTEM_TYPE], [ AC_CANONICAL_HOST diff --git a/make/configure b/make/configure index e0cf2796172f..b53787e0ba8e 100755 --- a/make/configure +++ b/make/configure @@ -3306,6 +3306,17 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu + + + + + + +no_werror_CFLAGS=$(echo " $CFLAGS " | sed 's/ -Werror / /g') +if test "X $CFLAGS " != "X$no_werror_CFLAGS"; then + CFLAGS="$no_werror_CFLAGS" + WERRORFLAGS=-Werror +fi default_cache_file=./config.cache @@ -7277,6 +7288,11 @@ fi + + +if test "x$GCC" = xyes; then + CFLAGS="$WERRORFLAGS $CFLAGS" +fi ac_config_files="$ac_config_files ../Makefile output.mk ../make/$host/otp_ded.mk:../make/otp_ded.mk.in" diff --git a/make/configure.ac b/make/configure.ac index f2f423b09ff7..3d14c1901238 100644 --- a/make/configure.ac +++ b/make/configure.ac @@ -26,6 +26,8 @@ m4_include([otp.m4]) LM_PRECIOUS_VARS +ERL_PUSH_WERROR + default_cache_file=./config.cache if test "x$no_recursion" != "xyes" -a "x$OVERRIDE_CONFIG_CACHE" = "x"; then @@ -372,6 +374,8 @@ fi ERL_DED +ERL_POP_WERROR + AC_CONFIG_FILES([../Makefile output.mk ../make/$host/otp_ded.mk:../make/otp_ded.mk.in]) AC_OUTPUT From e0fd4f832dd36912f126437e998654abffc12cc6 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Mon, 28 Oct 2024 11:01:52 +0100 Subject: [PATCH 05/10] erts: Disable some warnings in 3rd party libraries --- erts/emulator/Makefile.in | 4 ++-- erts/emulator/pcre/pcre.mk | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/erts/emulator/Makefile.in b/erts/emulator/Makefile.in index 1bfa891e23d4..f143f3489c62 100644 --- a/erts/emulator/Makefile.in +++ b/erts/emulator/Makefile.in @@ -944,7 +944,7 @@ $(OBJDIR)/%.o: nifs/$(ERLANG_OSTYPE)/%.c # included before any other directives, including other #includes. # ASMJIT_FLAGS=-DASMJIT_EMBED=1 -DASMJIT_NO_BUILDER=1 -DASMJIT_NO_DEPRECATED=1 -DASMJIT_STATIC=1 -DASMJIT_NO_FOREIGN=1 - +ASMJIT_CXXFLAGS=$(filter-out -Wformat -Wformat=2, $(CXXFLAGS)) ASMJIT_PCH_OBJ=$(TTF_DIR)/asmjit/asmjit.hpp.gch ASMJIT_PCH_SRC=$(TTF_DIR)/asmjit/asmjit.hpp @@ -960,7 +960,7 @@ $(OBJDIR)/%.o: beam/jit/$(JIT_ARCH)/%.cpp beam/jit/$(JIT_ARCH)/beam_asm.hpp $(AS $(OBJDIR)/asmjit/%.o: asmjit/%.cpp $(ASMJIT_PCH_OBJ) $(dir $@) $(V_CXX) $(ASMJIT_FLAGS) $(INCLUDES) \ - $(subst -O2, $(GEN_OPT_FLGS), $(CXXFLAGS)) \ + $(subst -O2, $(GEN_OPT_FLGS), $(ASMJIT_CXXFLAGS)) \ -include $(ASMJIT_PCH_SRC) -c $< -o $@ ## The dependency on erl_bif_info.c is in order to trigger a rebuild when diff --git a/erts/emulator/pcre/pcre.mk b/erts/emulator/pcre/pcre.mk index 38b91237a23e..2f536b072dfa 100644 --- a/erts/emulator/pcre/pcre.mk +++ b/erts/emulator/pcre/pcre.mk @@ -49,7 +49,7 @@ PCRE_OBJDIR = $(ERL_TOP)/erts/emulator/pcre/obj/$(TARGET)/$(TYPE) PCRE_DIR = $(ERL_TOP)/erts/emulator/pcre -PCRE_CFLAGS = $(filter-out -DDEBUG,$(CFLAGS)) -DERLANG_INTEGRATION +PCRE_CFLAGS = $(filter-out -DDEBUG -Wimplicit-fallthrough,$(CFLAGS)) -DERLANG_INTEGRATION ifeq ($(TARGET), win32) $(EPCRE_LIB): $(PCRE_OBJS) From ab8c9a660834e404edea4f580c8d5ab4ef554c1c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Mon, 28 Oct 2024 11:03:05 +0100 Subject: [PATCH 06/10] os_mon: Fix some ununsed variables --- lib/os_mon/c_src/memsup.c | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/lib/os_mon/c_src/memsup.c b/lib/os_mon/c_src/memsup.c index ad4a193d99ba..9d08500e58f7 100644 --- a/lib/os_mon/c_src/memsup.c +++ b/lib/os_mon/c_src/memsup.c @@ -288,7 +288,6 @@ get_mem_procfs(memory_ext *me){ int fd, nread; char buffer[4097]; char *bp; - unsigned long value; me->flag = 0; @@ -494,7 +493,7 @@ get_extended_mem(memory_ext *me) { static void get_basic_mem(unsigned long *tot, unsigned long *used, unsigned long *pagesize){ #if defined(_SC_AVPHYS_PAGES) /* Does this exist on others than Solaris2? */ - unsigned long avPhys, phys, pgSz; + unsigned long avPhys, phys; phys = sysconf(_SC_PHYS_PAGES); avPhys = sysconf(_SC_AVPHYS_PAGES); From d9bff4b4b461adf3dab6f0a77f1e51fea90e7490 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Mon, 28 Oct 2024 11:04:01 +0100 Subject: [PATCH 07/10] runtime_tools: Remove usage of obsolete PORT_CONTROL_FLAG_HEAVY This flag is had no effect since at least R13B. --- lib/runtime_tools/c_src/trace_file_drv.c | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/lib/runtime_tools/c_src/trace_file_drv.c b/lib/runtime_tools/c_src/trace_file_drv.c index 37a814977719..ea4a3eefd51b 100644 --- a/lib/runtime_tools/c_src/trace_file_drv.c +++ b/lib/runtime_tools/c_src/trace_file_drv.c @@ -377,17 +377,15 @@ static void trace_file_outputv(ErlDrvData handle, ErlIOVec *ev) static void trace_file_output(ErlDrvData handle, char *buff, ErlDrvSizeT bufflen) { - int heavy = 0; TraceFileData *data = (TraceFileData *) handle; unsigned char b[5] = ""; put_be((unsigned) bufflen, b + 1); switch (my_write(data, (unsigned char *) b, sizeof(b))) { case 1: - heavy = !0; case 0: switch (my_write(data, (unsigned char *) buff, bufflen)) { case 1: - heavy = !0; + break; case 0: break; case -1: @@ -408,12 +406,8 @@ static void trace_file_output(ErlDrvData handle, char *buff, driver_failure_posix(data->port, errno); /* XXX */ return; } - heavy = !0; } } - if (heavy) { - set_port_control_flags(data->port, PORT_CONTROL_FLAG_HEAVY); - } } /* @@ -577,7 +571,6 @@ static int my_write(TraceFileData *data, unsigned char *buff, int siz) } memcpy(data->buff, buff + wrote, siz - wrote); data->buff_pos = siz - wrote; - set_port_control_flags(data->port, PORT_CONTROL_FLAG_HEAVY); return 1; } From a7641178eb999b1f74c51690d9ccac130c1ef8d6 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Mon, 28 Oct 2024 11:04:27 +0100 Subject: [PATCH 08/10] odbc: Don't want for stringop-truncation --- lib/odbc/c_src/odbcserver.c | 11 +++++++++-- lib/odbc/configure | 25 +++++++++++++++++++++++++ lib/odbc/configure.ac | 12 ++++++++++++ 3 files changed, 46 insertions(+), 2 deletions(-) diff --git a/lib/odbc/c_src/odbcserver.c b/lib/odbc/c_src/odbcserver.c index e99f16624ea7..f415a7c083d3 100644 --- a/lib/odbc/c_src/odbcserver.c +++ b/lib/odbc/c_src/odbcserver.c @@ -645,8 +645,15 @@ static db_result_msg db_query(byte *sql, db_state *state) diagnos = get_diagnos(SQL_HANDLE_STMT, statement_handle(state), extended_errors(state)); if(strcmp((char *)diagnos.sqlState, INFO) == 0) { is_error[0] = 0; - strncat((char *)is_error, (char *)diagnos.error_msg, - 5); +#ifdef HAVE_GCC_DIAG_IGNORE_WSTRINGOP_TRUNCATION +_Pragma("GCC diagnostic push"); +_Pragma("GCC diagnostic ignored \"-Wstringop-truncation\""); +#endif + strncat((char *)is_error, (char *)diagnos.error_msg, + 5); +#ifdef HAVE_GCC_DIAG_IGNORE_WSTRINGOP_TRUNCATION +_Pragma("GCC diagnostic pop"); +#endif str_tolower((char *)&is_error, 5); /* The ODBC error handling could have been more predictable but alas ... we try to make the best of diff --git a/lib/odbc/configure b/lib/odbc/configure index e43c587ccc87..aad3e087067c 100755 --- a/lib/odbc/configure +++ b/lib/odbc/configure @@ -6035,6 +6035,31 @@ fi ;; esac fi +saved_CFLAGS="$CFLAGS" +CFLAGS="-Werror $CFLAGS" +cat confdefs.h - <<_ACEOF >conftest.$ac_ext +/* end confdefs.h. */ + +int +main (void) +{ +_Pragma("GCC diagnostic push") + _Pragma("GCC diagnostic ignored \"-Wstringop-truncation\"") + _Pragma("GCC diagnostic pop") + + ; + return 0; +} +_ACEOF +if ac_fn_c_try_compile "$LINENO" +then : + +printf "%s\n" "#define HAVE_GCC_DIAG_IGNORE_WSTRINGOP_TRUNCATION 1" >>confdefs.h + +fi +rm -f core conftest.err conftest.$ac_objext conftest.beam conftest.$ac_ext +CFLAGS="$saved_CFLAGS" + if test "x$GCC" = xyes then : diff --git a/lib/odbc/configure.ac b/lib/odbc/configure.ac index 19abc17670fe..75cd3b3148b4 100644 --- a/lib/odbc/configure.ac +++ b/lib/odbc/configure.ac @@ -252,6 +252,18 @@ AC_SUBST(ODBC_INCLUDE) ]) dnl "$with_odbc" != "no" +dnl ---------------------------------------------------------------------- +dnl Check for GCC diagnostic ignored "-Wstringop-truncation" +dnl ---------------------------------------------------------------------- +saved_CFLAGS="$CFLAGS" +CFLAGS="-Werror $CFLAGS" +AC_COMPILE_IFELSE([AC_LANG_PROGRAM([[]], [[_Pragma("GCC diagnostic push") + _Pragma("GCC diagnostic ignored \"-Wstringop-truncation\"") + _Pragma("GCC diagnostic pop") + ]])],[AC_DEFINE(HAVE_GCC_DIAG_IGNORE_WSTRINGOP_TRUNCATION,1, + define if compiler support _Pragma('GCC diagnostic ignored '-Wstringop-truncation''))],[]) +CFLAGS="$saved_CFLAGS" + AS_IF([test "x$GCC" = xyes], [ # Treat certain GCC warnings as errors From 82af61dafa93fb2c7c6c3c26bd8c58dd4e3f13ad Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Mon, 28 Oct 2024 11:05:27 +0100 Subject: [PATCH 09/10] gh: Enable openssf compiler hardening options --- .github/dockerfiles/Dockerfile.64-bit | 22 +++++++++++++++++++++- 1 file changed, 21 insertions(+), 1 deletion(-) diff --git a/.github/dockerfiles/Dockerfile.64-bit b/.github/dockerfiles/Dockerfile.64-bit index 07054bc81165..4c0d15b05410 100644 --- a/.github/dockerfiles/Dockerfile.64-bit +++ b/.github/dockerfiles/Dockerfile.64-bit @@ -13,11 +13,30 @@ RUN cd /buildroot && tar -xzf ./otp.tar.gz WORKDIR /buildroot/otp/ ENV CFLAGS="-O2 -g -Werror -DwxSTC_DISABLE_MACRO_DEPRECATIONS=1" +ENV CFLAGS="${CFLAGS} -Wall -Wformat -Wformat=2 -Wno-conversion -Wimplicit-fallthrough \ + -Werror=format-security -U_FORTIFY_SOURCE -D_FORTIFY_SOURCE=2 -D_GLIBCXX_ASSERTIONS \ + -fstack-clash-protection -fstack-protector-strong -Wtrampolines \ + -fcf-protection=full -fexceptions -fno-strict-overflow -fno-delete-null-pointer-checks \ + -D_GLIBCXX_ASSERTIONS" +## OpenSSF recommended CFLAGS, skipped are: +## -Wconversion -Wextra -Wsign-conversion - As we have way too many of these warnings +## -fstrict-flex-arrays=3 -Wbidi-chars=any - As gcc 11 does not support it +## -mbranch-protection=standard - Only on arm +## -Werror=implicit -Wincompatible-pointer-types -Wint-conversion - As these do not work on c++ code +ENV SKIPPED_OSSF_CFLAGS="-Wconversion -mbranch-protection=standard \ + -Wextra -Werror=implicit -Werror=incompatible-pointer-types -Werror=int-conversion \ + -Wsign-conversion" +ENV LDFLAGS="-Wl,-z,noexecstack -Wl,-z,relro -Wl,-z,now -Wl,--as-needed -Wl,--no-copy-dt-needed-entries" +## OpenSSF recommended LDFLAGS, skipped are: +## -Wl,-z,nodlopen - as opening drivers/nifs needs this +## -fPIE - not needed with gcc 11 +## -fPIC -shared - only needed for .so files +ENV SKIPPED_OSSF_LDFLAGS="-Wl,-z,nodlopen -fPIE -fPIC -shared" ## Configure (if not cached), check that no application are disabled and then make RUN if [ ! -f Makefile ]; then \ touch README.md && \ - ./configure --prefix="/Erlang ∅⊤℞" && \ + ./configure --prefix="/Erlang ∅⊤℞" --enable-pie && \ if cat lib/*/CONF_INFO || cat lib/*/SKIP || cat lib/SKIP-APPLICATIONS; then exit 1; fi && \ find . -type f -newer README.md | xargs tar --transform 's:^./:otp/:' -cf ../otp_cache.tar; \ fi && \ @@ -26,6 +45,7 @@ RUN if [ ! -f Makefile ]; then \ ## Disable -Werror as testcases do not compile with it on ENV CFLAGS="-O2 -g" +ENV LDFLAGS="" ## Update init.sh with correct env vars RUN echo "export MAKEFLAGS=$MAKEFLAGS" > /buildroot/env.sh && \ From fc9509e53c23dcad310d7230883a099aeeb7917a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= Date: Wed, 6 Nov 2024 10:30:59 +0100 Subject: [PATCH 10/10] gh: Add ossf-compiler-flags-scanner --- .github/scripts/ossf-sarif-generator.es | 106 ++++++++++++++++++ .../ossf-compiler-flags-scanner.yaml | 81 +++++++++++++ 2 files changed, 187 insertions(+) create mode 100755 .github/scripts/ossf-sarif-generator.es create mode 100644 .github/workflows/ossf-compiler-flags-scanner.yaml diff --git a/.github/scripts/ossf-sarif-generator.es b/.github/scripts/ossf-sarif-generator.es new file mode 100755 index 000000000000..1c352e73f0f7 --- /dev/null +++ b/.github/scripts/ossf-sarif-generator.es @@ -0,0 +1,106 @@ +#!/usr/bin/env escript + +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 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. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% %CopyrightEnd% + +%% This script takes a json string as argument and checks that all the compiler flags defined by the OSSF +%% are used. + +main([CompilerFlagsJson]) -> + io:format(standard_error,"~p",[os:env()]), + CFLAGS = proplists:get_value(cflags, erlang:system_info(compile_info)) ++ " " ++ os:getenv("SKIPPED_OSSF_CFLAGS"), + LDFLAGS = proplists:get_value(ldflags, erlang:system_info(compile_info)) ++ " " ++ os:getenv("SKIPPED_OSSF_LDFLAGS"), + {gnuc, {Vsn, _, _} } = erlang:system_info(c_compiler_used), + #{ ~"options" := #{ ~"recommended" := Opts } } = json:decode(unicode:characters_to_binary(CompilerFlagsJson)), + io:format(standard_error, ~s'CFLAGS="~ts"~nLDFLAGS="~ts"~n',[CFLAGS, LDFLAGS]), + Missing = [Opt || Opt <- Opts, check_option(Opt, string:split(CFLAGS, " ", all), string:split(LDFLAGS, " ", all), Vsn)], + io:format("~ts~n",[sarif(Missing)]), + ok. +check_option(#{ ~"requires" := #{ ~"gcc" := GccVsn }, ~"opt" := Opt }, CFLAGS, _LDFLAGS, CurrentGccVsn) -> + io:format(standard_error, "Looking for ~ts...",[Opt]), + case binary_to_integer(hd(string:split(GccVsn, "."))) > CurrentGccVsn of + true -> io:format(standard_error, "skipped!~n",[]), false; + false -> + check_for_flags(Opt, CFLAGS) + end; +check_option(#{ ~"requires" := #{ ~"binutils" := _ }, ~"opt" := Opt }, _CFLAGS, LDFLAGS, _CurrentGccVsn) -> + io:format(standard_error, "Looking for ~ts...",[Opt]), + check_for_flags(Opt, LDFLAGS); +check_option(#{ ~"requires" := #{ ~"libstdc++" := _ }, ~"opt" := Opt }, _CFLAGS, LDFLAGS, _CurrentGccVsn) -> + io:format(standard_error, "Looking for ~ts...",[Opt]), + check_for_flags(Opt, LDFLAGS); +check_option(#{ ~"requires" := Tool, ~"opt" := Opt }, _CFLAGS, _LDFLAGS, _CurrentGccVsn) -> + io:format(standard_error, "~ts not implemented yet using ~p!~n",[Opt, Tool]), + true. + +check_for_flags(Flag, Flags) -> + case lists:any(fun(O) -> lists:search(fun(A) -> string:equal(string:trim(O), string:trim(A)) end, Flags) =:= false end, string:split(Flag, " ", all) ) of + true -> io:format(standard_error, "missing!~n",[]), true; + false -> io:format(standard_error, "found!~n",[]), false + end. + +sarif(Missing) -> + Zip = lists:zip(lists:seq(1,length(Missing)), Missing), + json:encode( + #{ ~"version" => ~"2.1.0", + ~"$schema" => ~"https://raw.githubusercontent.com/oasis-tcs/sarif-spec/main/sarif-2.1/schema/sarif-schema-2.1.0.json", + ~"runs" => + [ #{ + ~"tool" => + #{ ~"driver" => + #{ ~"informationUri" => ~"https://github.com/erlang/otp/.github/workflow/ossf-scanner", + ~"name" => ~"ossf-scanner", + ~"rules" => + [ #{ ~"id" => base64:encode(erlang:md5(Opt)), + ~"name" => ~"MissingCompilerFlag", + ~"shortDescription" => + #{ ~"text" => <<"Missing CFLAGS ", Opt/binary>> }, + ~"helpUri" => ~"https://best.openssf.org/Compiler-Hardening-Guides/Compiler-Options-Hardening-Guide-for-C-and-C++", + ~"fullDescription" => + #{ + ~"text" => <> + } + } + || {_Id, #{ ~"desc" := Desc, ~"opt" := Opt }} <- Zip], + ~"version" => ~"1.0" + } + }, + ~"artifacts" => + [ #{ + ~"location" => #{ + ~"uri" => ~".github/docker/Dockerfile.64-bit" + }, + ~"length" => -1 + } + ], + ~"results" => + [ #{ + ~"ruleId" => base64:encode(erlang:md5(Opt)), + ~"ruleIndex" => Id, + ~"level" => ~"warning", + ~"message" => #{ ~"text" => <<"Missing CFLAGS ", Opt/binary>> }, + ~"locations" => + [ #{ ~"physicalLocation" => + #{ ~"artifactLocation" => + #{ ~"uri" => ~".github/docker/Dockerfile.64-bit" } + } + } ] + } || {Id, #{ ~"opt" := Opt }} <- Zip] + } ] + }). \ No newline at end of file diff --git a/.github/workflows/ossf-compiler-flags-scanner.yaml b/.github/workflows/ossf-compiler-flags-scanner.yaml new file mode 100644 index 000000000000..655a721536bb --- /dev/null +++ b/.github/workflows/ossf-compiler-flags-scanner.yaml @@ -0,0 +1,81 @@ +## %CopyrightBegin% +## +## Copyright Ericsson AB 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. +## You may obtain a copy of the License at +## +## http://www.apache.org/licenses/LICENSE-2.0 +## +## Unless required by applicable law or agreed to in writing, software +## distributed under the License is distributed on an "AS IS" BASIS, +## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +## See the License for the specific language governing permissions and +## limitations under the License. +## +## %CopyrightEnd% + +## This workflow continually scan the master branch to make sure that +## the correct compiler flags are used when testing Erlang/OTP on github. + +name: Open Source Security Foundation + +on: + workflow_dispatch: + schedule: + - cron: 0 1 * * * + +permissions: + # Required to upload SARIF file to CodeQL. + # See: https://github.com/github/codeql-action/issues/2117 + actions: read + # Require writing security events to upload SARIF file to security tab + security-events: write + # Only need to read contents + contents: read + +jobs: + schedule-scan: + runs-on: ubuntu-latest + if: github.repository == 'erlang/otp' + steps: + - uses: actions/checkout@v4.2.1 + - name: Create initial pre-release tar + run: .github/scripts/init-pre-release.sh otp_src.tar.gz + - uses: actions/checkout@v4.2.1 + with: + repository: ossf/wg-best-practices-os-developers + sparse-checkout: docs/Compiler-Hardening-Guides/compiler-options-scraper + path: ossf + + - name: Setup compiler options scraper + run: | + pip3 install -r ossf/docs/Compiler-Hardening-Guides/compiler-options-scraper/requirements.txt + python3 ossf/docs/Compiler-Hardening-Guides/compiler-options-scraper/main.py + cat compiler-options.json + + - uses: ./.github/actions/build-base-image + with: + BASE_BRANCH: master + BUILD_IMAGE: true + + - name: Run compiler flag comparison + run: | + docker run -v `pwd`/.github/scripts:/github --entrypoint "" otp \ + bash -c "/github/ossf-sarif-generator.es '$(cat compiler-options.json)'" > results.sarif + + - name: "Upload artifact" + if: ${{ !cancelled() }} + uses: actions/upload-artifact@v4 # v4.4.3 + with: + name: SARIF file + path: results.sarif + + # Upload the results to GitHub's code scanning dashboard. + - name: "Upload to code-scanning" + if: ${{ !cancelled() }} + uses: github/codeql-action/upload-sarif@v3 + with: + sarif_file: results.sarif +