diff --git a/gcc/analyzer/analyzer.opt b/gcc/analyzer/analyzer.opt index 6658ac520f14b677ea55cdf2514ee10c26586d31..7917473d1223626a449cbbcda1a756fa21b090c4 100644 --- a/gcc/analyzer/analyzer.opt +++ b/gcc/analyzer/analyzer.opt @@ -214,10 +214,6 @@ Wanalyzer-tainted-size Common Var(warn_analyzer_tainted_size) Init(1) Warning Warn about code paths in which an unsanitized value is used as a size. -Wanalyzer-unterminated-string -Common Var(warn_analyzer_unterminated_string) Init(1) Warning -Warn about code paths which attempt to find the length of an unterminated string. - Wanalyzer-use-after-free Common Var(warn_analyzer_use_after_free) Init(1) Warning Warn about code paths in which a freed value is used. diff --git a/gcc/analyzer/call-details.cc b/gcc/analyzer/call-details.cc index fa86f55177a4ee6d6ea115018fb71167a10ed93c..e497fc58e028e067f9a33aed2b3744489bd4622d 100644 --- a/gcc/analyzer/call-details.cc +++ b/gcc/analyzer/call-details.cc @@ -376,11 +376,13 @@ call_details::lookup_function_attribute (const char *attr_name) const return lookup_attribute (attr_name, TYPE_ATTRIBUTES (allocfntype)); } -void -call_details::check_for_null_terminated_string_arg (unsigned arg_idx) const +const svalue * +call_details:: +check_for_null_terminated_string_arg (unsigned arg_idx, + const svalue **out_sval) const { region_model *model = get_model (); - model->check_for_null_terminated_string_arg (*this, arg_idx); + return model->check_for_null_terminated_string_arg (*this, arg_idx, out_sval); } } // namespace ana diff --git a/gcc/analyzer/call-details.h b/gcc/analyzer/call-details.h index 0622cab7856af15703328952838871c090945a4a..86f0e68072bd6f3dc3671b050bf49b7e18d7579c 100644 --- a/gcc/analyzer/call-details.h +++ b/gcc/analyzer/call-details.h @@ -71,7 +71,9 @@ public: tree lookup_function_attribute (const char *attr_name) const; - void check_for_null_terminated_string_arg (unsigned arg_idx) const; + const svalue * + check_for_null_terminated_string_arg (unsigned arg_idx, + const svalue **out_sval = nullptr) const; private: const gcall *m_call; diff --git a/gcc/analyzer/kf-analyzer.cc b/gcc/analyzer/kf-analyzer.cc index 1a0c94089acaa733e7499a25f2a074e8c5b64703..c767ebcb6615c4151110812a7eb58de5bf7d20ab 100644 --- a/gcc/analyzer/kf-analyzer.cc +++ b/gcc/analyzer/kf-analyzer.cc @@ -369,8 +369,19 @@ public: } void impl_call_pre (const call_details &cd) const final override { - cd.check_for_null_terminated_string_arg (0); - cd.set_any_lhs_with_defaults (); + if (const svalue *bytes_read = cd.check_for_null_terminated_string_arg (0)) + { + region_model_manager *mgr = cd.get_manager (); + /* strlen is (bytes_read - 1). */ + const svalue *strlen_sval + = mgr->get_or_create_binop (size_type_node, + MINUS_EXPR, + bytes_read, + mgr->get_or_create_int_cst (size_type_node, 1)); + cd.maybe_set_lhs (strlen_sval); + } + else + cd.set_any_lhs_with_defaults (); } }; diff --git a/gcc/analyzer/region-model.cc b/gcc/analyzer/region-model.cc index ed93fb89f933bfd53ea1e695d65c4f44c48d518d..0fce18896fbc3e3d4e72b70265a28126c3b2d03c 100644 --- a/gcc/analyzer/region-model.cc +++ b/gcc/analyzer/region-model.cc @@ -3175,26 +3175,6 @@ region_model::set_value (tree lhs, tree rhs, region_model_context *ctxt) set_value (lhs_reg, rhs_sval, ctxt); } -/* Look for the first 0 byte within STRING_CST. - If there is one, write its index to *OUT and return true. - Otherwise, return false. */ - -static bool -get_strlen (tree string_cst, int *out) -{ - gcc_assert (TREE_CODE (string_cst) == STRING_CST); - - if (const void *p = memchr (TREE_STRING_POINTER (string_cst), - 0, - TREE_STRING_LENGTH (string_cst))) - { - *out = (const char *)p - TREE_STRING_POINTER (string_cst); - return true; - } - else - return false; -} - /* A bundle of information about a problematic argument at a callsite for use by pending_diagnostic subclasses for reporting and for deduplication. */ @@ -3236,106 +3216,477 @@ inform_about_expected_null_terminated_string_arg (const call_arg_details &ad) ad.m_arg_idx + 1, ad.m_called_fndecl); } -/* A subclass of pending_diagnostic for complaining about uses - of unterminated strings (thus accessing beyond the bounds - of a buffer). */ +/* A binding of a specific svalue at a concrete byte range. */ -class unterminated_string_arg -: public pending_diagnostic_subclass<unterminated_string_arg> +struct fragment { -public: - unterminated_string_arg (const call_arg_details arg_details) - : m_arg_details (arg_details) + fragment () + : m_byte_range (0, 0), m_sval (nullptr) { - gcc_assert (m_arg_details.m_called_fndecl); } - const char *get_kind () const final override + fragment (const byte_range &bytes, const svalue *sval) + : m_byte_range (bytes), m_sval (sval) { - return "unterminated_string_arg"; } - bool operator== (const unterminated_string_arg &other) const + static int cmp_ptrs (const void *p1, const void *p2) { - return m_arg_details == other.m_arg_details; + const fragment *f1 = (const fragment *)p1; + const fragment *f2 = (const fragment *)p2; + return byte_range::cmp (f1->m_byte_range, f2->m_byte_range); } - int get_controlling_option () const final override + /* Determine if there is a zero terminator somewhere in the + bytes of this fragment, starting at START_READ_OFFSET (which + is absolute to the start of the cluster as a whole), and stopping + at the end of this fragment. + + Return a tristate: + - true if there definitely is a zero byte, writing to *OUT_BYTES_READ + the number of bytes from that would be read, including the zero byte. + - false if there definitely isn't a zero byte + - unknown if we don't know. */ + tristate has_null_terminator (byte_offset_t start_read_offset, + byte_offset_t *out_bytes_read) const { - return OPT_Wanalyzer_unterminated_string; + byte_offset_t rel_start_read_offset + = start_read_offset - m_byte_range.get_start_byte_offset (); + gcc_assert (rel_start_read_offset >= 0); + byte_offset_t available_bytes + = (m_byte_range.get_next_byte_offset () - start_read_offset); + gcc_assert (available_bytes >= 0); + + if (rel_start_read_offset > INT_MAX) + return tristate::TS_UNKNOWN; + HOST_WIDE_INT rel_start_read_offset_hwi = rel_start_read_offset.slow (); + + if (available_bytes > INT_MAX) + return tristate::TS_UNKNOWN; + HOST_WIDE_INT available_bytes_hwi = available_bytes.slow (); + + switch (m_sval->get_kind ()) + { + case SK_CONSTANT: + { + tree cst + = as_a <const constant_svalue *> (m_sval)->get_constant (); + switch (TREE_CODE (cst)) + { + case STRING_CST: + { + /* Look for the first 0 byte within STRING_CST + from START_READ_OFFSET onwards. */ + const HOST_WIDE_INT num_bytes_to_search + = std::min<HOST_WIDE_INT> ((TREE_STRING_LENGTH (cst) + - rel_start_read_offset_hwi), + available_bytes_hwi); + const char *start = (TREE_STRING_POINTER (cst) + + rel_start_read_offset_hwi); + if (num_bytes_to_search >= 0) + if (const void *p = memchr (start, 0, + num_bytes_to_search)) + { + *out_bytes_read = (const char *)p - start + 1; + return tristate (true); + } + + *out_bytes_read = available_bytes; + return tristate (false); + } + break; + case INTEGER_CST: + if (rel_start_read_offset_hwi == 0 + && integer_onep (TYPE_SIZE_UNIT (TREE_TYPE (cst)))) + { + /* Model accesses to the initial byte of a 1-byte + INTEGER_CST. */ + if (zerop (cst)) + { + *out_bytes_read = 1; + return tristate (true); + } + else + { + *out_bytes_read = available_bytes; + return tristate (false); + } + } + /* Treat any other access to an INTEGER_CST as unknown. */ + return tristate::TS_UNKNOWN; + + default: + gcc_unreachable (); + break; + } + } + break; + default: + // TODO: it may be possible to handle other cases here. + return tristate::TS_UNKNOWN; + } } - bool emit (rich_location *rich_loc, logger *) final override + byte_range m_byte_range; + const svalue *m_sval; +}; + +/* A frozen copy of a single base region's binding_cluster within a store, + optimized for traversal of the concrete parts in byte order. + This only captures concrete bindings, and is an implementation detail + of region_model::scan_for_null_terminator. */ + +class iterable_cluster +{ +public: + iterable_cluster (const binding_cluster *cluster) { - auto_diagnostic_group d; - bool warned; - if (m_arg_details.m_arg_expr) - warned = warning_at (rich_loc, get_controlling_option (), - "passing pointer to unterminated string %qE" - " as argument %i of %qE", - m_arg_details.m_arg_expr, - m_arg_details.m_arg_idx + 1, - m_arg_details.m_called_fndecl); - else - warned = warning_at (rich_loc, get_controlling_option (), - "passing pointer to unterminated string" - " as argument %i of %qE", - m_arg_details.m_arg_idx + 1, - m_arg_details.m_called_fndecl); - if (warned) - inform_about_expected_null_terminated_string_arg (m_arg_details); - return warned; + if (!cluster) + return; + for (auto iter : *cluster) + { + const binding_key *key = iter.first; + const svalue *sval = iter.second; + + if (const concrete_binding *concrete_key + = key->dyn_cast_concrete_binding ()) + { + byte_range fragment_bytes (0, 0); + if (concrete_key->get_byte_range (&fragment_bytes)) + m_fragments.safe_push (fragment (fragment_bytes, sval)); + } + } + m_fragments.qsort (fragment::cmp_ptrs); } - label_text describe_final_event (const evdesc::final_event &ev) final override + bool + get_fragment_for_byte (byte_offset_t byte, fragment *out_frag) const { - return ev.formatted_print - ("passing pointer to unterminated buffer as argument %i of %qE" - " would lead to read past the end of the buffer", - m_arg_details.m_arg_idx + 1, - m_arg_details.m_called_fndecl); + /* TODO: binary search rather than linear. */ + unsigned iter_idx; + for (iter_idx = 0; iter_idx < m_fragments.length (); iter_idx++) + { + if (m_fragments[iter_idx].m_byte_range.contains_p (byte)) + { + *out_frag = m_fragments[iter_idx]; + return true; + } + } + return false; } private: - const call_arg_details m_arg_details; + auto_vec<fragment> m_fragments; }; +/* Simulate reading the bytes at BYTES from BASE_REG. + Complain to CTXT about any issues with the read e.g. out-of-bounds. */ + +const svalue * +region_model::get_store_bytes (const region *base_reg, + const byte_range &bytes, + region_model_context *ctxt) const +{ + const svalue *index_sval + = m_mgr->get_or_create_int_cst (size_type_node, + bytes.get_start_byte_offset ()); + const region *offset_reg = m_mgr->get_offset_region (base_reg, + NULL_TREE, + index_sval); + const svalue *byte_size_sval + = m_mgr->get_or_create_int_cst (size_type_node, bytes.m_size_in_bytes); + const region *read_reg = m_mgr->get_sized_region (offset_reg, + NULL_TREE, + byte_size_sval); + + /* Simulate reading those bytes from the store. */ + const svalue *sval = get_store_value (read_reg, ctxt); + return sval; +} + +static tree +get_tree_for_byte_offset (tree ptr_expr, byte_offset_t byte_offset) +{ + gcc_assert (ptr_expr); + return fold_build2 (MEM_REF, + char_type_node, + ptr_expr, wide_int_to_tree (size_type_node, byte_offset)); +} + +/* Simulate a series of reads of REG until we find a 0 byte + (equivalent to calling strlen). + + Complain to CTXT and return NULL if: + - the buffer pointed to isn't null-terminated + - the buffer pointed to has any uninitalized bytes before any 0-terminator + - any of the reads aren't within the bounds of the underlying base region + + Otherwise, return a svalue for the number of bytes read (strlen + 1), + and, if OUT_SVAL is non-NULL, write to *OUT_SVAL with an svalue + representing the content of REG up to and including the terminator. + + Algorithm + ========= + + Get offset for first byte to read. + Find the binding (if any) that contains it. + Find the size in bits of that binding. + Round to the nearest byte (which way???) + Or maybe give up if we have a partial binding there. + Get the svalue from the binding. + Determine the strlen (if any) of that svalue. + Does it have a 0-terminator within it? + If so, we have a partial read up to and including that terminator + Read those bytes from the store; add to the result in the correct place. + Finish + If not, we have a full read of that svalue + Read those bytes from the store; add to the result in the correct place. + Update read/write offsets + Continue + If unknown: + Result is unknown + Finish +*/ + +const svalue * +region_model::scan_for_null_terminator (const region *reg, + tree expr, + const svalue **out_sval, + region_model_context *ctxt) const +{ + store_manager *store_mgr = m_mgr->get_store_manager (); + + region_offset offset = reg->get_offset (m_mgr); + if (offset.symbolic_p ()) + { + if (out_sval) + *out_sval = m_mgr->get_or_create_unknown_svalue (NULL_TREE); + return m_mgr->get_or_create_unknown_svalue (size_type_node); + } + byte_offset_t src_byte_offset; + if (!offset.get_concrete_byte_offset (&src_byte_offset)) + { + if (out_sval) + *out_sval = m_mgr->get_or_create_unknown_svalue (NULL_TREE); + return m_mgr->get_or_create_unknown_svalue (size_type_node); + } + const byte_offset_t initial_src_byte_offset = src_byte_offset; + byte_offset_t dst_byte_offset = 0; + + const region *base_reg = reg->get_base_region (); + + if (const string_region *str_reg = base_reg->dyn_cast_string_region ()) + { + tree string_cst = str_reg->get_string_cst (); + if (const void *p = memchr (TREE_STRING_POINTER (string_cst), + 0, + TREE_STRING_LENGTH (string_cst))) + { + size_t num_bytes_read + = (const char *)p - TREE_STRING_POINTER (string_cst) + 1; + /* Simulate the read. */ + byte_range bytes_to_read (0, num_bytes_read); + const svalue *sval = get_store_bytes (reg, bytes_to_read, ctxt); + if (out_sval) + *out_sval = sval; + return m_mgr->get_or_create_int_cst (size_type_node, + num_bytes_read); + } + } + + const binding_cluster *cluster = m_store.get_cluster (base_reg); + iterable_cluster c (cluster); + binding_map result; + + while (1) + { + fragment f; + if (c.get_fragment_for_byte (src_byte_offset, &f)) + { + byte_offset_t fragment_bytes_read; + tristate is_terminated + = f.has_null_terminator (src_byte_offset, &fragment_bytes_read); + if (is_terminated.is_unknown ()) + { + if (out_sval) + *out_sval = m_mgr->get_or_create_unknown_svalue (NULL_TREE); + return m_mgr->get_or_create_unknown_svalue (size_type_node); + } + + /* Simulate reading those bytes from the store. */ + byte_range bytes_to_read (src_byte_offset, fragment_bytes_read); + const svalue *sval = get_store_bytes (base_reg, bytes_to_read, ctxt); + check_for_poison (sval, expr, nullptr, ctxt); + + if (out_sval) + { + byte_range bytes_to_write (dst_byte_offset, fragment_bytes_read); + const binding_key *key + = store_mgr->get_concrete_binding (bytes_to_write); + result.put (key, sval); + } + + src_byte_offset += fragment_bytes_read; + dst_byte_offset += fragment_bytes_read; + + if (is_terminated.is_true ()) + { + if (out_sval) + *out_sval = m_mgr->get_or_create_compound_svalue (NULL_TREE, + result); + return m_mgr->get_or_create_int_cst (size_type_node, + dst_byte_offset); + } + } + else + break; + } + + /* No binding for this base_region, or no binding at src_byte_offset + (or a symbolic binding). */ + + /* TODO: the various special-cases seen in + region_model::get_store_value. */ + + /* Simulate reading from this byte, then give up. */ + byte_range bytes_to_read (src_byte_offset, 1); + const svalue *sval = get_store_bytes (base_reg, bytes_to_read, ctxt); + tree byte_expr + = get_tree_for_byte_offset (expr, + src_byte_offset - initial_src_byte_offset); + check_for_poison (sval, byte_expr, nullptr, ctxt); + if (base_reg->can_have_initial_svalue_p ()) + { + if (out_sval) + *out_sval = m_mgr->get_or_create_unknown_svalue (NULL_TREE); + return m_mgr->get_or_create_unknown_svalue (size_type_node); + } + else + return nullptr; +} + /* Check that argument ARG_IDX (0-based) to the call described by CD is a pointer to a valid null-terminated string. - Complain if the buffer pointed to isn't null-terminated. + Simulate scanning through the buffer, reading until we find a 0 byte + (equivalent to calling strlen). - TODO: we should also complain if: - - the pointer is NULL (or could be) - - the buffer pointed to is uninitalized before any 0-terminator - - the 0-terminator is within the bounds of the underlying base region + Complain and return NULL if: + - the buffer pointed to isn't null-terminated + - the buffer pointed to has any uninitalized bytes before any 0-terminator + - any of the reads aren't within the bounds of the underlying base region - We're checking that the called function could validly iterate through - the buffer reading it until it finds a 0 byte (such as by calling - strlen, or equivalent code). */ + Otherwise, return a svalue for the number of bytes read (strlen + 1), + and, if OUT_SVAL is non-NULL, write to *OUT_SVAL with an svalue + representing the content of the buffer up to and including the terminator. -void + TODO: we should also complain if: + - the pointer is NULL (or could be). */ + +const svalue * region_model::check_for_null_terminated_string_arg (const call_details &cd, - unsigned arg_idx) + unsigned arg_idx, + const svalue **out_sval) { - region_model_context *ctxt = cd.get_ctxt (); + class null_terminator_check_event : public custom_event + { + public: + null_terminator_check_event (const event_loc_info &loc_info, + const call_arg_details &arg_details) + : custom_event (loc_info), + m_arg_details (arg_details) + { + } + + label_text get_desc (bool can_colorize) const final override + { + if (m_arg_details.m_arg_expr) + return make_label_text (can_colorize, + "while looking for null terminator" + " for argument %i (%qE) of %qD...", + m_arg_details.m_arg_idx + 1, + m_arg_details.m_arg_expr, + m_arg_details.m_called_fndecl); + else + return make_label_text (can_colorize, + "while looking for null terminator" + " for argument %i of %qD...", + m_arg_details.m_arg_idx + 1, + m_arg_details.m_called_fndecl); + } + + private: + const call_arg_details m_arg_details; + }; + + class null_terminator_check_decl_note + : public pending_note_subclass<null_terminator_check_decl_note> + { + public: + null_terminator_check_decl_note (const call_arg_details &arg_details) + : m_arg_details (arg_details) + { + } + + const char *get_kind () const final override + { + return "null_terminator_check_decl_note"; + } + + void emit () const final override + { + inform_about_expected_null_terminated_string_arg (m_arg_details); + } + + bool operator== (const null_terminator_check_decl_note &other) const + { + return m_arg_details == other.m_arg_details; + } + + private: + const call_arg_details m_arg_details; + }; + + /* Subclass of decorated_region_model_context that + adds the above event and note to any saved diagnostics. */ + class annotating_ctxt : public annotating_context + { + public: + annotating_ctxt (const call_details &cd, + unsigned arg_idx) + : annotating_context (cd.get_ctxt ()), + m_cd (cd), + m_arg_idx (arg_idx) + { + } + void add_annotations () final override + { + call_arg_details arg_details (m_cd, m_arg_idx); + event_loc_info loc_info (m_cd.get_location (), + m_cd.get_model ()->get_current_function ()->decl, + m_cd.get_model ()->get_stack_depth ()); + + add_event (make_unique<null_terminator_check_event> (loc_info, + arg_details)); + add_note (make_unique <null_terminator_check_decl_note> (arg_details)); + } + private: + const call_details &m_cd; + unsigned m_arg_idx; + }; + + /* Use this ctxt below so that any diagnostics that get added + get annotated. */ + annotating_ctxt my_ctxt (cd, arg_idx); const svalue *arg_sval = cd.get_arg_svalue (arg_idx); const region *buf_reg - = deref_rvalue (arg_sval, cd.get_arg_tree (arg_idx), ctxt); - - const svalue *contents_sval = get_store_value (buf_reg, ctxt); + = deref_rvalue (arg_sval, cd.get_arg_tree (arg_idx), &my_ctxt); - if (tree cst = contents_sval->maybe_get_constant ()) - if (TREE_CODE (cst) == STRING_CST) - { - int cst_strlen; - if (!get_strlen (cst, &cst_strlen)) - { - call_arg_details arg_details (cd, arg_idx); - ctxt->warn (make_unique<unterminated_string_arg> (arg_details)); - } - } + return scan_for_null_terminator (buf_reg, + cd.get_arg_tree (arg_idx), + out_sval, + &my_ctxt); } /* Remove all bindings overlapping REG within the store. */ diff --git a/gcc/analyzer/region-model.h b/gcc/analyzer/region-model.h index a01399c8e85a85d2b1956357870403f9bffdfc11..63a67b35350baa709420b63fbb92c34ba5d929a6 100644 --- a/gcc/analyzer/region-model.h +++ b/gcc/analyzer/region-model.h @@ -451,6 +451,13 @@ class region_model const svalue *get_store_value (const region *reg, region_model_context *ctxt) const; + const svalue *get_store_bytes (const region *base_reg, + const byte_range &bytes, + region_model_context *ctxt) const; + const svalue *scan_for_null_terminator (const region *reg, + tree expr, + const svalue **out_sval, + region_model_context *ctxt) const; bool region_exists_p (const region *reg) const; @@ -502,8 +509,10 @@ class region_model const svalue *sval_hint, region_model_context *ctxt) const; - void check_for_null_terminated_string_arg (const call_details &cd, - unsigned idx); + const svalue * + check_for_null_terminated_string_arg (const call_details &cd, + unsigned idx, + const svalue **out_sval = nullptr); private: const region *get_lvalue_1 (path_var pv, region_model_context *ctxt) const; diff --git a/gcc/analyzer/store.cc b/gcc/analyzer/store.cc index c7bc4b40f87c8ee41befb4856732226de2e0410d..aeea69311378de7fff0f9de247ce5051fabbe1f3 100644 --- a/gcc/analyzer/store.cc +++ b/gcc/analyzer/store.cc @@ -538,6 +538,15 @@ concrete_binding::overlaps_p (const concrete_binding &other) const return false; } +/* If this is expressible as a concrete byte range, return true + and write it to *OUT. Otherwise return false. */ + +bool +concrete_binding::get_byte_range (byte_range *out) const +{ + return m_bit_range.as_byte_range (out); +} + /* Comparator for use by vec<const concrete_binding *>::qsort. */ int diff --git a/gcc/analyzer/store.h b/gcc/analyzer/store.h index af6cc7ed03c7a13f1db4c2b8c05bbcb8f92cac0e..cf10fa3b0108de6158e29117326e2a7a5aa47511 100644 --- a/gcc/analyzer/store.h +++ b/gcc/analyzer/store.h @@ -399,6 +399,7 @@ public: { return this; } const bit_range &get_bit_range () const { return m_bit_range; } + bool get_byte_range (byte_range *out) const; bit_offset_t get_start_bit_offset () const { @@ -855,6 +856,12 @@ public: return get_concrete_binding (bits.get_start_bit_offset (), bits.m_size_in_bits); } + const concrete_binding * + get_concrete_binding (const byte_range &bytes) + { + bit_range bits = bytes.as_bit_range (); + return get_concrete_binding (bits); + } const symbolic_binding * get_symbolic_binding (const region *region); diff --git a/gcc/doc/invoke.texi b/gcc/doc/invoke.texi index 01aa9efebce5a669299f83c42dbb9fb3e5a0d0b0..ef3f409898600f9ec7fc546bf4767845aadf79ff 100644 --- a/gcc/doc/invoke.texi +++ b/gcc/doc/invoke.texi @@ -488,7 +488,6 @@ Objective-C and Objective-C++ Dialects}. -Wno-analyzer-tainted-size -Wanalyzer-too-complex -Wno-analyzer-unsafe-call-within-signal-handler --Wno-analyzer-unterminated-string -Wno-analyzer-use-after-free -Wno-analyzer-use-of-pointer-in-stale-stack-frame -Wno-analyzer-use-of-uninitialized-value @@ -10328,7 +10327,6 @@ Enabling this option effectively enables the following warnings: -Wanalyzer-shift-count-overflow -Wanalyzer-stale-setjmp-buffer -Wanalyzer-unsafe-call-within-signal-handler --Wanalyzer-unterminated-string -Wanalyzer-use-after-free -Wanalyzer-use-of-pointer-in-stale-stack-frame -Wanalyzer-use-of-uninitialized-value @@ -10918,17 +10916,6 @@ called from a signal handler. See @uref{https://cwe.mitre.org/data/definitions/479.html, CWE-479: Signal Handler Use of a Non-reentrant Function}. -@opindex Wanalyzer-unterminated-string -@opindex Wno-analyzer-unterminated-string -@item -Wno-analyzer-unterminated-string -This warning requires @option{-fanalyzer}, which enables it; use -@option{-Wno-analyzer-unterminated-string} to disable it. - -This diagnostic warns about code paths which attempt to find the length -of an unterminated string. For example, passing a pointer to an unterminated -buffer to @code{strlen} would lead to accesses beyond the end of the buffer -whilst attempting to find the terminating zero character. - @opindex Wanalyzer-use-after-free @opindex Wno-analyzer-use-after-free @item -Wno-analyzer-use-after-free diff --git a/gcc/testsuite/gcc.dg/analyzer/error-1.c b/gcc/testsuite/gcc.dg/analyzer/error-1.c index 491d615e2cb1367ff5993da1392daff87f38eae0..794a9ae7b42d114c92b2d9cc7ad8001d21f437af 100644 --- a/gcc/testsuite/gcc.dg/analyzer/error-1.c +++ b/gcc/testsuite/gcc.dg/analyzer/error-1.c @@ -68,11 +68,27 @@ void test_6 (int st, const char *str) char *test_error_unterminated (int st) { char fmt[3] = "abc"; - error (st, errno, fmt); /* { dg-warning "passing pointer to unterminated string '&fmt' as argument 3 of 'error'" } */ + error (st, errno, fmt); /* { dg-warning "stack-based buffer over-read" } */ + /* { dg-message "while looking for null terminator for argument 3 \\('&fmt'\\) of 'error'..." "event" { target *-*-* } .-1 } */ } char *test_error_at_line_unterminated (int st, int errno) { char fmt[3] = "abc"; - error_at_line (st, errno, __FILE__, __LINE__, fmt); /* { dg-warning "passing pointer to unterminated string '&fmt' as argument 5 of 'error_at_line'" } */ + error_at_line (st, errno, __FILE__, __LINE__, fmt); /* { dg-warning "stack-based buffer over-read" } */ + /* { dg-message "while looking for null terminator for argument 5 \\('&fmt'\\) of 'error_at_line'..." "event" { target *-*-* } .-1 } */ +} + +char *test_error_uninitialized (int st, int errno) +{ + char fmt[16]; + error (st, errno, fmt); /* { dg-warning "use of uninitialized value 'fmt\\\[0\\\]'" } */ + /* { dg-message "while looking for null terminator for argument 3 \\('&fmt'\\) of 'error'..." "event" { target *-*-* } .-1 } */ +} + +char *test_error_at_line_uninitialized (int st, int errno) +{ + char fmt[16]; + error_at_line (st, errno, __FILE__, __LINE__, fmt); /* { dg-warning "use of uninitialized value 'fmt\\\[0\\\]'" } */ + /* { dg-message "while looking for null terminator for argument 5 \\('&fmt'\\) of 'error_at_line'..." "event" { target *-*-* } .-1 } */ } diff --git a/gcc/testsuite/gcc.dg/analyzer/null-terminated-strings-1.c b/gcc/testsuite/gcc.dg/analyzer/null-terminated-strings-1.c index 3379870682370039c92f775a1807dba974e4a68e..1db82a76d3b3ec56c306e5f5b344648ec92368bc 100644 --- a/gcc/testsuite/gcc.dg/analyzer/null-terminated-strings-1.c +++ b/gcc/testsuite/gcc.dg/analyzer/null-terminated-strings-1.c @@ -5,19 +5,47 @@ typedef __SIZE_TYPE__ size_t; void test_terminated (void) { - __analyzer_get_strlen ("abc"); /* { dg-bogus "" } */ + __analyzer_eval (__analyzer_get_strlen ("abc") == 3); /* { dg-warning "TRUE" } */ } void test_unterminated (void) { char buf[3] = "abc"; - __analyzer_get_strlen (buf); /* { dg-warning "passing pointer to unterminated string '&buf' as argument 1 of '__analyzer_get_strlen'" } */ + __analyzer_get_strlen (buf); /* { dg-warning "stack-based buffer over-read" } */ + /* { dg-message "out-of-bounds read at byte 3 but 'buf' ends at byte 3" "bad read event" { target *-*-* } .-1 } */ + /* { dg-message "while looking for null terminator for argument 1 \\('&buf'\\) of '__analyzer_get_strlen'..." "null terminator event" { target *-*-* } .-2 } */ } -void test_embedded_nul (void) +void test_embedded_nuls (void) { - char buf[3] = "a\0c"; - __analyzer_get_strlen (buf); /* { dg-bogus "" } */ + /* 0123 456 78. */ + char buf[9] = "abc\0pq\0xy"; /* unterminated. */ + __analyzer_eval (__analyzer_get_strlen (buf) == 3); /* { dg-warning "TRUE" } */ + __analyzer_eval (__analyzer_get_strlen (buf + 1) == 2); /* { dg-warning "TRUE" } */ + __analyzer_eval (__analyzer_get_strlen (buf + 2) == 1); /* { dg-warning "TRUE" } */ + __analyzer_eval (__analyzer_get_strlen (buf + 3) == 0); /* { dg-warning "TRUE" } */ + __analyzer_eval (__analyzer_get_strlen (buf + 4) == 2); /* { dg-warning "TRUE" } */ + __analyzer_eval (__analyzer_get_strlen (buf + 5) == 1); /* { dg-warning "TRUE" } */ + __analyzer_eval (__analyzer_get_strlen (buf + 6) == 0); /* { dg-warning "TRUE" } */ + __analyzer_get_strlen (buf + 7); /* { dg-warning "stack-based buffer over-read" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('<unknown>'\\) of '__analyzer_get_strlen'..." "event" { target *-*-* } .-1 } */ + // TODO: fix the "<unknown>" here? +} + +void test_before_start_of_buffer (void) +{ + const char *buf = "abc"; + __analyzer_get_strlen (buf - 1); /* { dg-warning "buffer under-read" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('<unknown>'\\) of '__analyzer_get_strlen'..." "event" { target *-*-* } .-1 } */ + // TODO: fix the "<unknown>" here? +} + +void test_after_end_of_buffer (void) +{ + const char *buf = "abc"; + __analyzer_get_strlen (buf + 4); /* { dg-warning "buffer over-read" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('<unknown>'\\) of '__analyzer_get_strlen'..." "event" { target *-*-* } .-1 } */ + // TODO: fix the "<unknown>" here? } void test_fully_initialized_but_unterminated (void) @@ -26,5 +54,93 @@ void test_fully_initialized_but_unterminated (void) buf[0] = 'a'; buf[1] = 'b'; buf[2] = 'c'; - __analyzer_get_strlen (buf); /* { dg-warning "passing pointer to unterminated string '&buf' as argument 1 of '__analyzer_get_strlen'" "" { xfail *-*-* } } */ + __analyzer_get_strlen (buf); /* { dg-warning "stack-based buffer over-read" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('&buf'\\) of '__analyzer_get_strlen'..." "event" { target *-*-* } .-1 } */ +} + +void test_uninitialized (void) +{ + char buf[16]; + __analyzer_get_strlen (buf); /* { dg-warning "use of uninitialized value 'buf\\\[0\\\]'" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('&buf'\\) of '__analyzer_get_strlen'..." "event" { target *-*-* } .-1 } */ +} + +void test_partially_initialized (void) +{ + char buf[16]; + buf[0] = 'a'; + __analyzer_get_strlen (buf); /* { dg-warning "use of uninitialized value 'buf\\\[1\\\]'" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('&buf'\\) of '__analyzer_get_strlen'..." "event" { target *-*-* } .-1 } */ +} + +char *test_dynamic_1 (void) +{ + const char *kvstr = "NAME=value"; + size_t len = __builtin_strlen (kvstr); + char *ptr = __builtin_malloc (len + 1); + if (!ptr) + return NULL; + __builtin_memcpy (ptr, kvstr, len); + ptr[len] = '\0'; + __analyzer_eval (__analyzer_get_strlen (ptr) == 10); /* { dg-warning "UNKNOWN" } */ + // TODO: should be TRUE + return ptr; +} + +char *test_dynamic_2 (void) +{ + const char *kvstr = "NAME=value"; + size_t len = __builtin_strlen (kvstr); + char *ptr = __builtin_malloc (len + 1); + if (!ptr) + return NULL; + __builtin_memcpy (ptr, kvstr, len); + /* Missing termination. */ + __analyzer_get_strlen (ptr); /* { dg-warning "use of uninitialized value '&buf'" "" { xfail *-*-* } } */ + // TODO (xfail) + return ptr; +} + +char *test_dynamic_3 (const char *src) +{ + size_t len = __builtin_strlen (src); + char *ptr = __builtin_malloc (len + 1); + if (!ptr) + return NULL; + __builtin_memcpy (ptr, src, len); + ptr[len] = '\0'; + __analyzer_eval (__analyzer_get_strlen (ptr) == len); /* { dg-warning "UNKNOWN" } */ + // TODO: should get TRUE for this + return ptr; +} + +char *test_dynamic_4 (const char *src) +{ + size_t len = __builtin_strlen (src); + char *ptr = __builtin_malloc (len + 1); + if (!ptr) + return NULL; + __builtin_memcpy (ptr, src, len); + /* Missing termination. */ + __analyzer_get_strlen (ptr); /* { dg-warning "use of uninitialized value 'buf\\\[len\\\]'" "" { xfail *-*-* } } */ + // TODO (xfail) + return ptr; +} + +void test_symbolic_ptr (const char *ptr) +{ + __analyzer_describe (0, __analyzer_get_strlen (ptr)); /* { dg-warning "UNKNOWN" } */ +} + +void test_symbolic_offset (size_t idx) +{ + __analyzer_describe (0, __analyzer_get_strlen ("abc" + idx)); /* { dg-warning "UNKNOWN" } */ +} + +void test_casts (void) +{ + int i = 42; + const char *p = (const char *)&i; + __analyzer_eval (__analyzer_get_strlen (p) == 0); /* { dg-warning "UNKNOWN" } */ + __analyzer_eval (__analyzer_get_strlen (p + 1) == 0); /* { dg-warning "UNKNOWN" } */ } diff --git a/gcc/testsuite/gcc.dg/analyzer/putenv-1.c b/gcc/testsuite/gcc.dg/analyzer/putenv-1.c index 5fa20334c0ab501d454a7bb82e74ff066b8da4fc..5c4e08c68dffe2e2aa3c90983b614b5156055f2d 100644 --- a/gcc/testsuite/gcc.dg/analyzer/putenv-1.c +++ b/gcc/testsuite/gcc.dg/analyzer/putenv-1.c @@ -112,6 +112,15 @@ void test_outer (void) void test_unterminated (void) { char buf[3] = "abc"; - putenv (buf); /* { dg-warning "passing pointer to unterminated string" } */ - /* { dg-warning "'putenv' on a pointer to automatic variable 'buf'" "POS34-C" { target *-*-* } .-1 } */ + putenv (buf); /* { dg-warning "stack-based buffer over-read" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('&buf'\\) of 'putenv'..." "event" { target *-*-* } .-1 } */ + /* { dg-warning "'putenv' on a pointer to automatic variable 'buf'" "POS34-C" { target *-*-* } .-2 } */ +} + +void test_uninitialized (void) +{ + char buf[16]; + putenv (buf); /* { dg-warning "use of uninitialized value 'buf\\\[0\\\]'" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('&buf'\\) of 'putenv'..." "event" { target *-*-* } .-1 } */ + /* { dg-warning "'putenv' on a pointer to automatic variable 'buf'" "POS34-C" { target *-*-* } .-2 } */ } diff --git a/gcc/testsuite/gcc.dg/analyzer/strchr-1.c b/gcc/testsuite/gcc.dg/analyzer/strchr-1.c index 2fb6c76797e80c207670a6201fdbf100fa41c4f5..08c429d8f9096246cf985a3b837317943607007e 100644 --- a/gcc/testsuite/gcc.dg/analyzer/strchr-1.c +++ b/gcc/testsuite/gcc.dg/analyzer/strchr-1.c @@ -29,5 +29,13 @@ void test_3 (const char *s, int c) void test_unterminated (int c) { char buf[3] = "abc"; - strchr (buf, c); /* { dg-warning "passing pointer to unterminated string '&buf' as argument 1 of 'strchr'" } */ + strchr (buf, c); /* { dg-warning "stack-based buffer over-read" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('&buf'\\) of 'strchr'..." "event" { target *-*-* } .-1 } */ +} + +void test_uninitialized (int c) +{ + char buf[16]; + strchr (buf, c); /* { dg-warning "use of uninitialized value 'buf\\\[0\\\]'" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('&buf'\\) of 'strchr'..." "event" { target *-*-* } .-1 } */ } diff --git a/gcc/testsuite/gcc.dg/analyzer/strcpy-1.c b/gcc/testsuite/gcc.dg/analyzer/strcpy-1.c index f23dd69bfb6988c80e4e77197d93ef007405e93e..d21e771751193b29b354f8d1990e94b89d92917d 100644 --- a/gcc/testsuite/gcc.dg/analyzer/strcpy-1.c +++ b/gcc/testsuite/gcc.dg/analyzer/strcpy-1.c @@ -20,5 +20,13 @@ test_1a (char *dst, char *src) char *test_unterminated (char *dst) { char buf[3] = "abc"; - return strcpy (dst, buf); /* { dg-warning "passing pointer to unterminated string '&buf' as argument 2 of 'strcpy'" } */ + return strcpy (dst, buf); /* { dg-warning "stack-based buffer over-read" } */ + /* { dg-message "while looking for null terminator for argument 2 \\('&buf'\\) of 'strcpy'..." "event" { target *-*-* } .-1 } */ +} + +char *test_uninitialized (char *dst) +{ + char buf[16]; + return strcpy (dst, buf); /* { dg-warning "use of uninitialized value 'buf\\\[0\\\]'" } */ + /* { dg-message "while looking for null terminator for argument 2 \\('&buf'\\) of 'strcpy'..." "event" { target *-*-* } .-1 } */ } diff --git a/gcc/testsuite/gcc.dg/analyzer/strdup-1.c b/gcc/testsuite/gcc.dg/analyzer/strdup-1.c index 682bfb90176894ef647086315370bcbffcf8330c..f6c176f174eb2326076efb9c2789dc47a814d967 100644 --- a/gcc/testsuite/gcc.dg/analyzer/strdup-1.c +++ b/gcc/testsuite/gcc.dg/analyzer/strdup-1.c @@ -42,5 +42,13 @@ void test_6 (const char *s) char *test_unterminated (void) { char buf[3] = "abc"; - return strdup (buf); /* { dg-warning "passing pointer to unterminated string '&buf' as argument 1 of 'strdup'" } */ + return strdup (buf); /* { dg-warning "stack-based buffer over-read" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('&buf'\\) of 'strdup'..." "event" { target *-*-* } .-1 } */ +} + +char *test_uninitialized (void) +{ + char buf[16]; + return strdup (buf); /* { dg-warning "use of uninitialized value 'buf\\\[0\\\]'" } */ + /* { dg-message "while looking for null terminator for argument 1 \\('&buf'\\) of 'strdup'..." "event" { target *-*-* } .-1 } */ }