From f7d86b5ca830ca95899ec5e1585359f9baf19238 Mon Sep 17 00:00:00 2001
From: Martin Sebor <msebor@redhat.com>
Date: Wed, 11 Dec 2019 19:50:43 +0000
Subject: [PATCH] builtins.c (compute_objsize): Add an argument and set it to
 offset into destination.

gcc/ChangeLog:

	* builtins.c (compute_objsize): Add an argument and set it to offset
	into destination.
	* builtins.h (compute_objsize): Add an argument.
	* tree-object-size.c (addr_object_size): Add an argument and set it
	to offset into destination.
	(compute_builtin_object_size): Same.
	* tree-object-size.h (compute_builtin_object_size): Add an argument.
	* tree-ssa-strlen.c (get_addr_stridx): Add an argument and set it
	to offset into destination.
	(maybe_warn_overflow): New function.
	(handle_store): Call maybe_warn_overflow to issue warnings.

gcc/testsuite/ChangeLog:

	* c-c++-common/Wstringop-overflow-2.c: Adjust text of expected messages.
	* g++.dg/warn/Wstringop-overflow-3.C: Same.
	* gcc.dg/Wstringop-overflow-17.c: Same.

From-SVN: r279248
---
 gcc/ChangeLog                                 |  14 +
 gcc/builtins.c                                |   4 +-
 gcc/testsuite/ChangeLog                       |   6 +
 .../c-c++-common/Wstringop-overflow-2.c       |   8 +-
 .../g++.dg/warn/Wstringop-overflow-3.C        |  80 ++--
 gcc/testsuite/gcc.dg/Wstringop-overflow-17.c  |   2 +-
 gcc/tree-object-size.c                        |  27 +-
 gcc/tree-object-size.h                        |   2 +-
 gcc/tree-ssa-strlen.c                         | 445 +++++++++++++++---
 9 files changed, 477 insertions(+), 111 deletions(-)

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 77723836c29b..88abb6d5ef3f 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,17 @@
+2019-12-11  Martin Sebor  <msebor@redhat.com>
+
+	* builtins.c (compute_objsize): Add an argument and set it to offset
+	into destination.
+	* builtins.h (compute_objsize): Add an argument.
+	* tree-object-size.c (addr_object_size): Add an argument and set it
+	to offset into destination.
+	(compute_builtin_object_size): Same.
+	* tree-object-size.h (compute_builtin_object_size): Add an argument.
+	* tree-ssa-strlen.c (get_addr_stridx): Add an argument and set it
+	to offset into destination.
+	(maybe_warn_overflow): New function.
+	(handle_store): Call maybe_warn_overflow to issue warnings.
+
 2019-12-11  Jozef Lawrynowicz  <jozef.l@mittosystems.com>
 
 	* config/msp430/msp430.h (STARTFILE_SPEC) [!fexceptions]: Use
diff --git a/gcc/builtins.c b/gcc/builtins.c
index 205ac3927b92..4c08214ba293 100644
--- a/gcc/builtins.c
+++ b/gcc/builtins.c
@@ -3817,7 +3817,7 @@ compute_objsize (tree dest, int ostype, tree *pdecl /* = NULL */,
   /* Only the two least significant bits are meaningful.  */
   ostype &= 3;
 
-  if (compute_builtin_object_size (dest, ostype, &size, pdecl))
+  if (compute_builtin_object_size (dest, ostype, &size, pdecl, poff))
     return build_int_cst (sizetype, size);
 
   if (TREE_CODE (dest) == SSA_NAME)
@@ -3924,7 +3924,7 @@ compute_objsize (tree dest, int ostype, tree *pdecl /* = NULL */,
 	  if (integer_zerop (size)
 	      && *pdecl && DECL_P (*pdecl)
 	      && *poff && integer_zerop (*poff))
-	    return integer_zero_node;
+	    return size_zero_node;
 
 	  /* A valid offset into a declared object cannot be negative.  */
 	  if (tree_int_cst_sgn (*poff) < 0)
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 120b1cdef1bf..485659228159 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -20,6 +20,12 @@
 	PR c++/92878 - Parenthesized init of aggregates in new-expression.
 	* g++.dg/cpp2a/paren-init20.C: New test.
 
+2019-12-11  Martin Sebor  <msebor@redhat.com>
+
+	* c-c++-common/Wstringop-overflow-2.c: Adjust text of expected messages.
+	* g++.dg/warn/Wstringop-overflow-3.C: Same.
+	* gcc.dg/Wstringop-overflow-17.c: Same.
+
 2019-12-11  Martin Sebor  <msebor@redhat.com>
 
 	PR middle-end/79221
diff --git a/gcc/testsuite/c-c++-common/Wstringop-overflow-2.c b/gcc/testsuite/c-c++-common/Wstringop-overflow-2.c
index d1aab4805e9f..7c7932e3cf00 100644
--- a/gcc/testsuite/c-c++-common/Wstringop-overflow-2.c
+++ b/gcc/testsuite/c-c++-common/Wstringop-overflow-2.c
@@ -10,7 +10,7 @@ void sink (void*);
 struct Ax
 {
   char n;
-  char a[];                     // { dg-message "destination object declared here" }
+  char a[];                     // { dg-message "declared here" }
 };
 
 // Verify warning for a definition with no initializer.
@@ -91,7 +91,7 @@ void gaxx (void)
 struct A0
 {
   char n;
-  char a[0];                    // { dg-message "destination object declared here" }
+  char a[0];                    // { dg-message "declared here" }
 };
 
 // Verify warning for a definition with no initializer.
@@ -158,7 +158,7 @@ void ga0x (void)
 struct A1
 {
   char n;
-  char a[1];                    // { dg-message "destination object declared here" }
+  char a[1];                    // { dg-message "declared here" }
 };
 
 // Verify warning for a definition with no initializer.
@@ -256,7 +256,7 @@ void ga1x (void)
 struct A1i
 {
   char n;
-  char a[1];                    // { dg-message "destination object declared here" }
+  char a[1];                    // { dg-message "declared here" }
   char x;
 };
 
diff --git a/gcc/testsuite/g++.dg/warn/Wstringop-overflow-3.C b/gcc/testsuite/g++.dg/warn/Wstringop-overflow-3.C
index 99ce427c1b57..db67136b5e79 100644
--- a/gcc/testsuite/g++.dg/warn/Wstringop-overflow-3.C
+++ b/gcc/testsuite/g++.dg/warn/Wstringop-overflow-3.C
@@ -3,6 +3,8 @@
    { dg-do compile }
    { dg-options "-O2 -Wall -Wno-array-bounds" } */
 
+#define NOIPA __attribute__ ((noipa))
+
 void sink (void*);
 
 // Exercise flexible array members.
@@ -10,13 +12,13 @@ void sink (void*);
 struct Ax
 {
   char n;
-  char a[];                     // { dg-message "destination object declared here" }
+  char a[];                     // { dg-message "at offset \[0-2\] to object 'Ax::a' declared here" }
 };
 
 // Verify warning for a definition with no initializer.
 Ax ax_;
 
-void gax_ ()
+NOIPA void gax_ ()
 {
   ax_.a[0] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
   ax_.a[1] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
@@ -27,7 +29,7 @@ void gax_ ()
 // initialize the flexible array member.
 Ax ax0 = { 0 };
 
-void gax0 ()
+NOIPA void gax0 ()
 {
   ax0.a[0] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
   ax0.a[1] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
@@ -38,7 +40,7 @@ void gax0 ()
 // initializes the flexible array member to empty.
 Ax ax0_ = { 0, { } };
 
-void gax0_ ()
+NOIPA void gax0_ ()
 {
   ax0_.a[0] = 0;                // { dg-warning "\\\[-Wstringop-overflow" }
   ax0_.a[1] = 0;                // { dg-warning "\\\[-Wstringop-overflow" }
@@ -49,7 +51,7 @@ void gax0_ ()
 // an initializer.
 Ax ax1 = { 1, { 0 } };
 
-void gax1 ()
+NOIPA void gax1 ()
 {
   ax1.a[0] = 0;
   ax1.a[1] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
@@ -58,7 +60,7 @@ void gax1 ()
 
 Ax ax2 = { 2, { 1, 0 } };
 
-void gax2 ()
+NOIPA void gax2 ()
 {
   ax2.a[0] = 0;
   ax2.a[1] = 0;
@@ -67,7 +69,7 @@ void gax2 ()
 
 
 // Verify no warning for an unknown struct object.
-void gaxp (Ax *p)
+NOIPA void gaxp (Ax *p)
 {
   p->a[0] = 0;
   p->a[3] = 0;
@@ -79,7 +81,7 @@ void gaxp (Ax *p)
 // initialized to any number of elements.
 extern Ax axx;
 
-void gaxx ()
+NOIPA void gaxx ()
 {
   axx.a[0] = 0;
   axx.a[3] = 0;
@@ -91,13 +93,13 @@ void gaxx ()
 struct A0
 {
   char n;
-  char a[0];                    // { dg-message "destination object declared here" }
+  char a[0];                    // { dg-message "at offset \[0-2\] to object 'A0::a' with size 0 declared here" }
 };
 
 // Verify warning for a definition with no initializer.
 A0 a0_;
 
-void ga0_ ()
+NOIPA void ga0_ ()
 {
   a0_.a[0] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
   a0_.a[1] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
@@ -108,7 +110,7 @@ void ga0_ ()
 // initialize the flexible array member.
 A0 a00 = { 0 };
 
-void ga00 ()
+NOIPA void ga00 ()
 {
   a00.a[0] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
   a00.a[1] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
@@ -119,7 +121,7 @@ void ga00 ()
 // initializes the flexible array member to empty.
 A0 a00_ = { 0, { } };
 
-void ga00_ ()
+NOIPA void ga00_ ()
 {
   a00_.a[0] = 0;                // { dg-warning "\\\[-Wstringop-overflow" }
   a00_.a[1] = 0;                // { dg-warning "\\\[-Wstringop-overflow" }
@@ -133,7 +135,7 @@ void ga00_ ()
 
 
 // Verify no warning for an unknown struct object.
-void ga0p (A0 *p)
+NOIPA void ga0p (A0 *p)
 {
   p->a[0] = 0;
   p->a[3] = 0;
@@ -145,7 +147,7 @@ void ga0p (A0 *p)
 // flexible array member) may not be initialized.
 extern A0 a0x;
 
-void ga0x ()
+NOIPA void ga0x ()
 {
   a0x.a[0] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
   a0x.a[3] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
@@ -158,13 +160,13 @@ void ga0x ()
 struct A1
 {
   char n;
-  char a[1];                    // { dg-message "destination object declared here" }
+  char a[1];                    // { dg-message "at offset \[1-9\] to object 'A1::a' with size 1 declared here" }
 };
 
 // Verify warning for a definition with no initializer.
 A1 a1_;
 
-void ga1_ ()
+NOIPA void ga1_ ()
 {
   a1_.a[0] = 0;
   a1_.a[1] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
@@ -175,7 +177,7 @@ void ga1_ ()
 // initialize the one-element array member.
 A1 a1__ = { 0 };
 
-void ga1__ ()
+NOIPA void ga1__ ()
 {
   a1__.a[0] = 0;
   a1__.a[1] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
@@ -186,7 +188,7 @@ void ga1__ ()
 // initializes the one-element array member to empty.
 A1 a1_0 = { 0, { } };
 
-void ga1_0_ ()
+NOIPA void ga1_0_ ()
 {
   a1_0.a[0] = 0;
   a1_0.a[1] = 0;                // { dg-warning "\\\[-Wstringop-overflow" }
@@ -197,7 +199,7 @@ void ga1_0_ ()
 // initializes the one-element array member.
 A1 a1_1 = { 0, { 1 } };
 
-void ga1_1 ()
+NOIPA void ga1_1 ()
 {
   a1_1.a[0] = 0;
   a1_1.a[1] = 0;                // { dg-warning "\\\[-Wstringop-overflow" }
@@ -206,7 +208,7 @@ void ga1_1 ()
 
 
 // Verify no warning for an unknown struct object.
-void ga1p (A1 *p)
+NOIPA void ga1p (A1 *p)
 {
   p->a[0] = 0;
   p->a[3] = 0;
@@ -219,7 +221,7 @@ void ga1p (A1 *p)
 // a single element.
 extern A1 a1x;
 
-void ga1x ()
+NOIPA void ga1x ()
 {
   a1x.a[0] = 0;
   a1x.a[3] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
@@ -232,14 +234,14 @@ void ga1x ()
 struct A1i
 {
   char n;
-  char a[1];                    // { dg-message "destination object declared here" }
+  char a[1];                    // { dg-message "at offset \[1-9\] to object 'A1i::a' with size 1 declared here" }
   char x;
 };
 
 // Verify warning for a definition with no initializer.
 A1i a1i_;
 
-void ga1i_ ()
+NOIPA void ga1i_ ()
 {
   a1i_.a[0] = 0;
   a1i_.a[1] = 0;                // { dg-warning "\\\[-Wstringop-overflow" }
@@ -250,7 +252,7 @@ void ga1i_ ()
 // initialize the one-element array member.
 A1i a1i__ = { 0 };
 
-void ga1i__ ()
+NOIPA void ga1i__ ()
 {
   a1i__.a[0] = 0;
   a1i__.a[1] = 0;                // { dg-warning "\\\[-Wstringop-overflow" }
@@ -261,7 +263,7 @@ void ga1i__ ()
 // initializes the one-element array member to empty.
 A1 a1i_0 = { 0, { } };
 
-void ga1i_0_ ()
+NOIPA void ga1i_0_ ()
 {
   a1i_0.a[0] = 0;
   a1i_0.a[1] = 0;               // { dg-warning "\\\[-Wstringop-overflow" }
@@ -272,7 +274,7 @@ void ga1i_0_ ()
 // initializes the one-element array member.
 A1 a1i_1 = { 0, { 1 } };
 
-void ga1i_1 ()
+NOIPA void ga1i_1 ()
 {
   a1i_1.a[0] = 0;
   a1i_1.a[1] = 0;               // { dg-warning "\\\[-Wstringop-overflow" }
@@ -281,7 +283,7 @@ void ga1i_1 ()
 
 
 // Verify no warning for an unknown struct object.
-void ga1ip (A1i *p)
+NOIPA void ga1ip (A1i *p)
 {
   p->a[0] = 0;
   p->a[3] = 0;                  // { dg-warning "\\\[-Wstringop-overflow" }
@@ -292,7 +294,7 @@ void ga1ip (A1i *p)
 // Verify no warning for an extern struct object.
 extern A1i a1ix;
 
-void ga1ix ()
+NOIPA void ga1ix ()
 {
   a1ix.a[0] = 0;
   a1ix.a[3] = 0;                 // { dg-warning "\\\[-Wstringop-overflow" }
@@ -305,7 +307,7 @@ void ga1ix ()
 struct Bx
 {
   char n;
-  char a[];                     // { dg-message "destination object declared here" }
+  char a[];                     // { dg-message "at offset 0 to object 'Bx::a' declared here" }
 
   // Verify the warning for a constant.
   Bx () { a[0] = 0; }           // { dg-warning "\\\[-Wstringop-overflow" }
@@ -315,13 +317,13 @@ struct Bx
   Bx (int i) { a[i] = 0; }      // { dg-warning "\\\[-Wstringop-overflow" }
 };
 
-void gbx (void)
+NOIPA void gbx (void)
 {
   struct Bx bx;
   sink (&bx);
 }
 
-void gbxi (int i)
+NOIPA void gbxi (int i)
 {
   struct Bx bxi (i);
   sink (&bxi);
@@ -330,13 +332,13 @@ void gbxi (int i)
 struct B0
 {
   char n;
-  char a[0];                    // { dg-message "destination object declared here" }
+  char a[0];                    // { dg-message "at offset 0 to object 'B0::a' with size 0 declared here" }
 
   B0 () { a[0] = 0; }           // { dg-warning "\\\[-Wstringop-overflow" }
 };
 
 
-void gb0 (void)
+NOIPA void gb0 (void)
 {
   struct B0 b0;
   sink (&b0);
@@ -346,12 +348,12 @@ void gb0 (void)
 struct B1
 {
   char n;
-  char a[1];                    // { dg-message "destination object declared here" }
+  char a[1];                    // { dg-message "at offset 1 to object 'B1::a' with size 1 declared here" }
 
   B1 () { a[1] = 0; }           // { dg-warning "\\\[-Wstringop-overflow" }
 };
 
-void gb1 (void)
+NOIPA void gb1 (void)
 {
   struct B1 b1;
   sink (&b1);
@@ -360,12 +362,12 @@ void gb1 (void)
 
 struct B123
 {
-  char a[123];                  // { dg-message "destination object declared here" }
+  char a[123];                  // { dg-message "at offset 123 to object 'B123::a' with size 123 declared here" }
 
   B123 () { a[123] = 0; }       // { dg-warning "\\\[-Wstringop-overflow" }
 };
 
-void gb123 (void)
+NOIPA void gb123 (void)
 {
   struct B123 b123;
   sink (&b123);
@@ -374,12 +376,12 @@ void gb123 (void)
 
 struct B234
 {
-  char a[234];                  // { dg-message "destination object declared here" }
+  char a[234];                  // { dg-message "at offset 234 to object 'B234::a' with size 234 declared here" }
 
   B234 (int i) { a[i] = 0; }    // { dg-warning "\\\[-Wstringop-overflow" }
 };
 
-void g234 (void)
+NOIPA void g234 (void)
 {
   struct B234 b234 (234);
   sink (&b234);
diff --git a/gcc/testsuite/gcc.dg/Wstringop-overflow-17.c b/gcc/testsuite/gcc.dg/Wstringop-overflow-17.c
index fdacea3972dc..b903f6eca0b6 100644
--- a/gcc/testsuite/gcc.dg/Wstringop-overflow-17.c
+++ b/gcc/testsuite/gcc.dg/Wstringop-overflow-17.c
@@ -13,7 +13,7 @@ void sink (void*);
 
 void call_copy_n (const char *s)
 {
-  char a[3];        // { dg-message "destination object declared here" }
+  char a[3];        // { dg-message "declared here" }
   copy_n (a, "1234567", 7);
   sink (a);
 }
diff --git a/gcc/tree-object-size.c b/gcc/tree-object-size.c
index 6e79bbd1d917..d591c36dea34 100644
--- a/gcc/tree-object-size.c
+++ b/gcc/tree-object-size.c
@@ -55,7 +55,7 @@ static const unsigned HOST_WIDE_INT unknown[4] = {
 static tree compute_object_offset (const_tree, const_tree);
 static bool addr_object_size (struct object_size_info *,
 			      const_tree, int, unsigned HOST_WIDE_INT *,
-			      tree * = NULL);
+			      tree * = NULL, tree * = NULL);
 static unsigned HOST_WIDE_INT alloc_object_size (const gcall *, int);
 static tree pass_through_call (const gcall *);
 static void collect_object_sizes_for (struct object_size_info *, tree);
@@ -174,13 +174,15 @@ compute_object_offset (const_tree expr, const_tree var)
 static bool
 addr_object_size (struct object_size_info *osi, const_tree ptr,
 		  int object_size_type, unsigned HOST_WIDE_INT *psize,
-		  tree *pdecl /* = NULL */)
+		  tree *pdecl /* = NULL */, tree *poff /* = NULL */)
 {
   tree pt_var, pt_var_size = NULL_TREE, var_size, bytes;
 
-  tree dummy;
+  tree dummy_decl, dummy_off = size_zero_node;
   if (!pdecl)
-    pdecl = &dummy;
+    pdecl = &dummy_decl;
+  if (!poff)
+    poff = &dummy_off;
 
   gcc_assert (TREE_CODE (ptr) == ADDR_EXPR);
 
@@ -201,7 +203,7 @@ addr_object_size (struct object_size_info *osi, const_tree ptr,
 	  || TREE_CODE (TREE_OPERAND (pt_var, 0)) != SSA_NAME)
 	{
 	  compute_builtin_object_size (TREE_OPERAND (pt_var, 0),
-				       object_size_type & ~1, &sz, pdecl);
+				       object_size_type & ~1, &sz, pdecl, poff);
 	}
       else
 	{
@@ -376,6 +378,7 @@ addr_object_size (struct object_size_info *osi, const_tree ptr,
 	    bytes = size_zero_node;
 	  else
 	    bytes = size_binop (MINUS_EXPR, var_size, bytes);
+	  *poff = bytes;
 	}
       if (var != pt_var
 	  && pt_var_size
@@ -390,6 +393,7 @@ addr_object_size (struct object_size_info *osi, const_tree ptr,
 		bytes2 = size_zero_node;
 	      else
 		bytes2 = size_binop (MINUS_EXPR, pt_var_size, bytes2);
+	      *poff = size_binop (PLUS_EXPR, *poff, bytes2);
 	      bytes = size_binop (MIN_EXPR, bytes, bytes2);
 	    }
 	}
@@ -496,10 +500,16 @@ pass_through_call (const gcall *call)
 bool
 compute_builtin_object_size (tree ptr, int object_size_type,
 			     unsigned HOST_WIDE_INT *psize,
-			     tree *pdecl /* = NULL */)
+			     tree *pdecl /* = NULL */, tree *poff /* = NULL */)
 {
   gcc_assert (object_size_type >= 0 && object_size_type <= 3);
 
+  tree dummy_decl, dummy_off = size_zero_node;
+  if (!pdecl)
+    pdecl = &dummy_decl;
+  if (!poff)
+    poff = &dummy_off;
+
   /* Set to unknown and overwrite just before returning if the size
      could be determined.  */
   *psize = unknown[object_size_type];
@@ -508,7 +518,7 @@ compute_builtin_object_size (tree ptr, int object_size_type,
     init_offset_limit ();
 
   if (TREE_CODE (ptr) == ADDR_EXPR)
-    return addr_object_size (NULL, ptr, object_size_type, psize, pdecl);
+    return addr_object_size (NULL, ptr, object_size_type, psize, pdecl, poff);
 
   if (TREE_CODE (ptr) != SSA_NAME
       || !POINTER_TYPE_P (TREE_TYPE (ptr)))
@@ -533,11 +543,12 @@ compute_builtin_object_size (tree ptr, int object_size_type,
 
 	      if (tree_fits_shwi_p (offset)
 		  && compute_builtin_object_size (ptr, object_size_type,
-						  psize, pdecl))
+						  psize, pdecl, poff))
 		{
 		  /* Return zero when the offset is out of bounds.  */
 		  unsigned HOST_WIDE_INT off = tree_to_shwi (offset);
 		  *psize = off < *psize ? *psize - off : 0;
+		  *poff = offset;
 		  return true;
 		}
 	    }
diff --git a/gcc/tree-object-size.h b/gcc/tree-object-size.h
index 65528b3a696f..d6c7b4906866 100644
--- a/gcc/tree-object-size.h
+++ b/gcc/tree-object-size.h
@@ -23,6 +23,6 @@ along with GCC; see the file COPYING3.  If not see
 extern void init_object_sizes (void);
 extern void fini_object_sizes (void);
 extern bool compute_builtin_object_size (tree, int, unsigned HOST_WIDE_INT *,
-					 tree * = NULL);
+					 tree * = NULL, tree * = NULL);
 
 #endif  // GCC_TREE_OBJECT_SIZE_H
diff --git a/gcc/tree-ssa-strlen.c b/gcc/tree-ssa-strlen.c
index beff17b37f1a..212ac7152bf5 100644
--- a/gcc/tree-ssa-strlen.c
+++ b/gcc/tree-ssa-strlen.c
@@ -188,6 +188,49 @@ struct laststmt_struct
 static int get_stridx_plus_constant (strinfo *, unsigned HOST_WIDE_INT, tree);
 static void handle_builtin_stxncpy (built_in_function, gimple_stmt_iterator *);
 
+/* Sets MINMAX to either the constant value or the range VAL is in
+   and returns true on success.  When nonnull, uses RVALS to get
+   VAL's range.  Otherwise uses get_range_info.  */
+
+static bool
+get_range (tree val, wide_int minmax[2], const vr_values *rvals = NULL)
+{
+  if (tree_fits_uhwi_p (val))
+    {
+      minmax[0] = minmax[1] = wi::to_wide (val);
+      return true;
+    }
+
+  if (TREE_CODE (val) != SSA_NAME)
+    return false;
+
+  if (rvals)
+    {
+      /* The range below may be "inaccurate" if a constant has been
+	 substituted earlier for VAL by this pass that hasn't been
+	 propagated through the CFG.  This shoud be fixed by the new
+	 on-demand VRP if/when it becomes available (hopefully in
+	 GCC 11).  */
+      const value_range *vr
+	= (CONST_CAST (class vr_values *, rvals)->get_value_range (val));
+      value_range_kind rng = vr->kind ();
+      if (rng != VR_RANGE || !range_int_cst_p (vr))
+	return false;
+
+      minmax[0] = wi::to_wide (vr->min ());
+      minmax[1] = wi::to_wide (vr->max ());
+      return true;
+    }
+
+  value_range_kind rng = get_range_info (val, minmax, minmax + 1);
+  if (rng == VR_RANGE)
+    return true;
+
+  /* Do not handle anti-ranges and instead make use of the on-demand
+     VRP if/when it becomes available (hopefully in GCC 11).  */
+  return false;
+}
+
 /* Return:
 
    *  +1  if SI is known to start with more than OFF nonzero characters.
@@ -333,24 +376,32 @@ get_addr_stridx (tree exp, tree ptr, unsigned HOST_WIDE_INT *offset_out,
   return 0;
 }
 
-/* Return string index for EXP.  */
+/* Returns string index for EXP.  When EXP is an SSA_NAME that refers
+   to a known strinfo with an offset and OFFRNG is non-null, sets
+   both elements of the OFFRNG array to the range of the offset and
+   returns the index of the known strinfo.  In this case the result
+   must not be used in for functions that modify the string.  */
 
 static int
-get_stridx (tree exp)
+get_stridx (tree exp, wide_int offrng[2] = NULL)
 {
+  if (offrng)
+    offrng[0] = offrng[1] = wi::zero (TYPE_PRECISION (sizetype));
+
   if (TREE_CODE (exp) == SSA_NAME)
     {
       if (ssa_ver_to_stridx[SSA_NAME_VERSION (exp)])
 	return ssa_ver_to_stridx[SSA_NAME_VERSION (exp)];
 
       tree e = exp;
+      int last_idx = 0;
       HOST_WIDE_INT offset = 0;
       /* Follow a chain of at most 5 assignments.  */
       for (int i = 0; i < 5; i++)
 	{
 	  gimple *def_stmt = SSA_NAME_DEF_STMT (e);
 	  if (!is_gimple_assign (def_stmt))
-	    return 0;
+	    return last_idx;
 
 	  tree_code rhs_code = gimple_assign_rhs_code (def_stmt);
 	  tree ptr, off;
@@ -402,25 +453,69 @@ get_stridx (tree exp)
 	  else
 	    return 0;
 
-	  if (TREE_CODE (ptr) != SSA_NAME
-	      || !tree_fits_shwi_p (off))
+	  if (TREE_CODE (ptr) != SSA_NAME)
 	    return 0;
+
+	  if (!tree_fits_shwi_p (off))
+	    {
+	      if (int idx = ssa_ver_to_stridx[SSA_NAME_VERSION (ptr)])
+		if (offrng)
+		  {
+		    /* Only when requested by setting OFFRNG to non-null,
+		       return the index corresponding to the SSA_NAME.
+		       Do this irrespective of the whether the offset
+		       is known.  */
+		    if (get_range (off, offrng))
+		      {
+			/* When the offset range is known, increment it
+			   it by the constant offset computed in prior
+			   iterations and store it in the OFFRNG array.  */
+ 			offrng[0] += offset;
+			offrng[1] += offset;
+		      }
+		    else
+		      {
+			/* When the offset range cannot be determined
+			   store [0, SIZE_MAX] and let the caller decide
+			   if the offset matters.  */
+			offrng[1] = wi::to_wide (TYPE_MAX_VALUE (sizetype));
+			offrng[0] = wi::zero (offrng[1].get_precision ());
+		      }
+		    return idx;
+		  }
+	      return 0;
+	    }
+
 	  HOST_WIDE_INT this_off = tree_to_shwi (off);
+	  if (offrng)
+	    {
+	      offrng[0] += wi::shwi (this_off, offrng->get_precision ());
+	      offrng[1] += offrng[0];
+	    }
+
 	  if (this_off < 0)
-	    return 0;
+	    return last_idx;
+
 	  offset = (unsigned HOST_WIDE_INT) offset + this_off;
 	  if (offset < 0)
-	    return 0;
-	  if (ssa_ver_to_stridx[SSA_NAME_VERSION (ptr)])
+	    return last_idx;
+
+	  if (int idx = ssa_ver_to_stridx[SSA_NAME_VERSION (ptr)])
 	    {
-	      strinfo *si
-	        = get_strinfo (ssa_ver_to_stridx[SSA_NAME_VERSION (ptr)]);
-	      if (si && compare_nonzero_chars (si, offset) >= 0)
-	        return get_stridx_plus_constant (si, offset, exp);
+	      strinfo *si = get_strinfo (idx);
+	      if (si)
+		{
+		  if (compare_nonzero_chars (si, offset) >= 0)
+		    return get_stridx_plus_constant (si, offset, exp);
+
+		  if (offrng)
+		    last_idx = idx;
+		}
 	    }
 	  e = ptr;
 	}
-      return 0;
+
+      return last_idx;
     }
 
   if (TREE_CODE (exp) == ADDR_EXPR)
@@ -1762,6 +1857,279 @@ maybe_set_strlen_range (tree lhs, tree src, tree bound)
   return set_strlen_range (lhs, min, max, bound);
 }
 
+/* Diagnose buffer overflow by a STMT writing LEN + PLUS_ONE bytes,
+   into an object designated by the LHS of STMT otherise.  */
+
+static void
+maybe_warn_overflow (gimple *stmt, tree len,
+		     const vr_values *rvals = NULL,
+		     strinfo *si = NULL, bool plus_one = false)
+{
+  if (!len || gimple_no_warning_p (stmt))
+    return;
+
+  tree writefn = NULL_TREE;
+  tree destdecl = NULL_TREE;
+  tree destsize = NULL_TREE;
+  tree dest = NULL_TREE;
+
+  /* The offset into the destination object set by compute_objsize
+     but already reflected in DESTSIZE.  */
+  tree destoff = NULL_TREE;
+
+  if (is_gimple_assign (stmt))
+    {
+      dest = gimple_assign_lhs (stmt);
+      if (TREE_NO_WARNING (dest))
+	return;
+
+      /* For assignments try to determine the size of the destination
+	 first.  Set DESTOFF to the the offset on success.  */
+      tree off = size_zero_node;
+      destsize = compute_objsize (dest, 1, &destdecl, &off);
+      if (destsize)
+	destoff = off;
+    }
+  else if (is_gimple_call (stmt))
+    {
+      writefn = gimple_call_fndecl (stmt);
+      dest = gimple_call_arg (stmt, 0);
+    }
+
+  /* The offset into the destination object computed below and not
+     reflected in DESTSIZE.  Either DESTOFF is set above or OFFRNG
+     below.  */
+  wide_int offrng[2];
+  offrng[0] = wi::zero (TYPE_PRECISION (sizetype));
+  offrng[1] = offrng[0];
+
+  if (!destsize && !si && dest)
+    {
+      /* For both assignments and calls, if no destination STRINFO was
+	 provided, try to get it from the DEST.  */
+      tree ref = dest;
+      tree off = NULL_TREE;
+      if (TREE_CODE (ref) == ARRAY_REF)
+	{
+	  /* Handle stores to VLAs (represented as
+	     ARRAY_REF (MEM_REF (vlaptr, 0), N].  */
+	  off = TREE_OPERAND (ref, 1);
+	  ref = TREE_OPERAND (ref, 0);
+	}
+
+      if (TREE_CODE (ref) == MEM_REF)
+	{
+	  tree mem_off = TREE_OPERAND (ref, 1);
+	  if (off)
+	    {
+	      if (!integer_zerop (mem_off))
+		return;
+	    }
+	  else
+	    off = mem_off;
+	  ref = TREE_OPERAND (ref, 0);
+	}
+
+      if (int idx = get_stridx (ref, offrng))
+	{
+	  si = get_strinfo (idx);
+	  if (off && TREE_CODE (off) == INTEGER_CST)
+	    {
+	      wide_int wioff = wi::to_wide (off, offrng->get_precision ());
+	      offrng[0] += wioff;
+	      offrng[1] += wioff;
+	    }
+	}
+      else
+	return;
+    }
+
+  /* Return early if the DESTSIZE size expression is the same as LEN
+     and the offset into the destination is zero.  This might happen
+     in the case of a pair of malloc and memset calls to allocate
+     an object and clear it as if by calloc.  */
+  if (destsize == len && !plus_one && offrng[0] == 0 && offrng[0] == offrng[1])
+    return;
+
+  wide_int lenrng[2];
+  if (!get_range (len, lenrng, rvals))
+    return;
+
+  if (plus_one)
+    {
+      lenrng[0] += 1;
+      lenrng[1] += 1;
+    }
+
+  /* Compute the range of sizes of the destination object.  The range
+     is constant for declared objects but may be a range for allocated
+     objects.  */
+  wide_int sizrng[2];
+  if (!destsize || !get_range (destsize, sizrng, rvals))
+    {
+      /* On failure, rather than bailing outright, use the maximum range
+	 so that overflow in allocated objects whose size depends on
+	 the strlen of the source can still be diagnosed below.  */
+      sizrng[0] = wi::zero (lenrng->get_precision ());
+      sizrng[1] = wi::to_wide (TYPE_MAX_VALUE (ptrdiff_type_node));
+    }
+
+  /* The size of the remaining space in the destination computed as
+     the size of the latter minus the offset into it.  */
+  wide_int spcrng[2] = { sizrng[0], sizrng[1] };
+  if (wi::sign_mask (offrng[0]))
+    {
+      /* FIXME: Handle negative offsets into allocated objects.  */
+      if (destdecl)
+	spcrng[0] = spcrng[1] = wi::zero (spcrng->get_precision ());
+      else
+	return;
+    }
+  else
+    {
+      spcrng[0] -= wi::ltu_p (offrng[0], spcrng[0]) ? offrng[0] : spcrng[0];
+      spcrng[1] -= wi::ltu_p (offrng[0], spcrng[1]) ? offrng[0] : spcrng[1];
+    }
+
+  if (wi::leu_p (lenrng[0], spcrng[0]))
+    return;
+
+  if (lenrng[0] == spcrng[1]
+      && (len != destsize
+	  || !si || !is_strlen_related_p (si->ptr, len)))
+    return;
+
+  location_t loc = gimple_nonartificial_location (stmt);
+  if (loc == UNKNOWN_LOCATION && dest && EXPR_HAS_LOCATION (dest))
+    loc = tree_nonartificial_location (dest);
+  loc = expansion_point_location_if_in_system_header (loc);
+
+  bool warned = false;
+  if (wi::leu_p (lenrng[0], spcrng[1]))
+    {
+      if (len != destsize
+	  && (!si || !is_strlen_related_p (si->ptr, len)))
+	return;
+
+      warned = (writefn
+		? warning_at (loc, OPT_Wstringop_overflow_,
+			      "%G%qD writing one too many bytes into a region "
+			      "of a size that depends on %<strlen%>",
+			      stmt, writefn)
+		: warning_at (loc, OPT_Wstringop_overflow_,
+			      "%Gwriting one too many bytes into a region "
+			      "of a size that depends on %<strlen%>",
+			      stmt));
+    }
+  else if (lenrng[0] == lenrng[1])
+    {
+      if (spcrng[0] == spcrng[1])
+	warned = (writefn
+		  ? warning_n (loc, OPT_Wstringop_overflow_,
+			       lenrng[0].to_uhwi (),
+			       "%G%qD writing %wu byte into a region "
+			       "of size %wu",
+			       "%G%qD writing %wu bytes into a region "
+			       "of size %wu",
+			       stmt, writefn, lenrng[0].to_uhwi (),
+			       spcrng[0].to_uhwi ())
+		  : warning_n (loc, OPT_Wstringop_overflow_,
+			       lenrng[0].to_uhwi (),
+			       "%Gwriting %wu byte into a region "
+			       "of size %wu",
+			       "%Gwriting %wu bytes into a region "
+			       "of size %wu",
+			       stmt, lenrng[0].to_uhwi (),
+			       spcrng[0].to_uhwi ()));
+      else
+	warned = (writefn
+		  ? warning_n (loc, OPT_Wstringop_overflow_,
+			       lenrng[0].to_uhwi (),
+			       "%G%qD writing %wu byte into a region "
+			       "of size between %wu and %wu",
+			       "%G%qD writing %wu bytes into a region "
+			       "of size between %wu and %wu",
+			       stmt, writefn, lenrng[0].to_uhwi (),
+			       spcrng[0].to_uhwi (), spcrng[1].to_uhwi ())
+		  : warning_n (loc, OPT_Wstringop_overflow_,
+			       lenrng[0].to_uhwi (),
+			       "%Gwriting %wu byte into a region "
+			       "of size between %wu and %wu",
+			       "%Gwriting %wu bytes into a region "
+			       "of size between %wu and %wu",
+			       stmt, lenrng[0].to_uhwi (),
+			       spcrng[0].to_uhwi (), spcrng[1].to_uhwi ()));
+    }
+  else if (spcrng[0] == spcrng[1])
+    warned = (writefn
+	      ? warning_at (loc, OPT_Wstringop_overflow_,
+			    "%G%qD writing between %wu and %wu bytes "
+			    "into a region of size %wu",
+			    stmt, writefn, lenrng[0].to_uhwi (),
+			    lenrng[1].to_uhwi (),
+			    spcrng[0].to_uhwi ())
+	      : warning_at (loc, OPT_Wstringop_overflow_,
+			    "%Gwriting between %wu and %wu bytes "
+			    "into a region of size %wu",
+			    stmt, lenrng[0].to_uhwi (),
+			    lenrng[1].to_uhwi (),
+			    spcrng[0].to_uhwi ()));
+  else
+    warned = (writefn
+	      ? warning_at (loc, OPT_Wstringop_overflow_,
+			    "%G%qD writing between %wu and %wu bytes "
+			    "into a region of size between %wu and %wu",
+			    stmt, writefn, lenrng[0].to_uhwi (),
+			    lenrng[1].to_uhwi (),
+			    spcrng[0].to_uhwi (), spcrng[1].to_uhwi ())
+	      : warning_at (loc, OPT_Wstringop_overflow_,
+			    "%Gwriting between %wu and %wu bytes "
+			    "into a region of size between %wu and %wu",
+			    stmt, lenrng[0].to_uhwi (),
+			    lenrng[1].to_uhwi (),
+			    spcrng[0].to_uhwi (), spcrng[1].to_uhwi ()));
+
+  if (!warned)
+    return;
+
+  /* If DESTOFF is not null, use it to format the offset value/range.  */
+  if (destoff)
+    get_range (destoff, offrng);
+
+  /* Format the offset to keep the number of inform calls from growing
+     out of control.  */
+  char offstr[64];
+  if (offrng[0] == offrng[1])
+    sprintf (offstr, "%lli", (long long) offrng[0].to_shwi ());
+  else
+    sprintf (offstr, "[%lli, %lli]",
+	     (long long) offrng[0].to_shwi (), (long long) offrng[1].to_shwi ());
+
+  if (destdecl)
+    {
+      if (tree size = DECL_SIZE_UNIT (destdecl))
+	inform (DECL_SOURCE_LOCATION (destdecl),
+		"at offset %s to object %qD with size %E declared here",
+		offstr, destdecl, size);
+      else
+	inform (DECL_SOURCE_LOCATION (destdecl),
+		"at offset %s to object %qD declared here",
+		offstr, destdecl);
+      return;
+    }
+}
+
+/* Convenience wrapper for the above.  */
+
+static inline void
+maybe_warn_overflow (gimple *stmt, unsigned HOST_WIDE_INT len,
+		     const vr_values *rvals = NULL,
+		     strinfo *si = NULL, bool plus_one = false)
+{
+  maybe_warn_overflow (stmt, build_int_cst (size_type_node, len), rvals,
+		       si, plus_one);
+}
+
 /* Handle a strlen call.  If strlen of the argument is known, replace
    the strlen call with the known value, otherwise remember that strlen
    of the argument is stored in the lhs SSA_NAME.  */
@@ -4333,6 +4701,13 @@ handle_store (gimple_stmt_iterator *gsi, bool *zero_write, const vr_values *rval
 	  else if (si == NULL || compare_nonzero_chars (si, offset, rvals) < 0)
 	    {
 	      *zero_write = initializer_zerop (rhs);
+
+	      bool dummy;
+	      unsigned lenrange[] = { UINT_MAX, 0, 0 };
+	      if (count_nonzero_bytes (rhs, lenrange, &dummy, &dummy, &dummy,
+				       rvals))
+		maybe_warn_overflow (stmt, lenrange[2], rvals);
+
 	      return true;
 	    }
 	}
@@ -4371,49 +4746,7 @@ handle_store (gimple_stmt_iterator *gsi, bool *zero_write, const vr_values *rval
       storing_nonzero_p = lenrange[1] > 0;
       *zero_write = storing_all_zeros_p;
 
-      /* Avoid issuing multiple warnings for the same LHS or statement.
-	 For example, -Warray-bounds may have already been issued for
-	 an out-of-bounds subscript.  */
-      if (!TREE_NO_WARNING (lhs) && !gimple_no_warning_p (stmt))
-	{
-	  /* Set to the declaration referenced by LHS (if known).  */
-	  tree decl = NULL_TREE;
-	  if (tree dstsize = compute_objsize (lhs, 1, &decl))
-	    if (compare_tree_int (dstsize, lenrange[2]) < 0)
-	      {
-		/* Fall back on the LHS location if the statement
-		   doesn't have one.  */
-		location_t loc = gimple_nonartificial_location (stmt);
-		if (loc == UNKNOWN_LOCATION && EXPR_HAS_LOCATION (lhs))
-		  loc = tree_nonartificial_location (lhs);
-		loc = expansion_point_location_if_in_system_header (loc);
-		if (warning_n (loc, OPT_Wstringop_overflow_,
-			       lenrange[2],
-			       "%Gwriting %u byte into a region of size %E",
-			       "%Gwriting %u bytes into a region of size %E",
-			       stmt, lenrange[2], dstsize))
-		  {
-		    if (decl)
-		      {
-			if (TREE_CODE (decl) == SSA_NAME)
-			  {
-			    gimple *stmt = SSA_NAME_DEF_STMT (decl);
-			    if (is_gimple_call (stmt))
-			      {
-				tree allocfn = gimple_call_fndecl (stmt);
-				inform (gimple_location (stmt),
-					"destination region allocated by %qD "
-					"here", allocfn);
-			      }
-			  }
-			else
-			  inform (DECL_SOURCE_LOCATION (decl),
-				  "destination object declared here");
-		      }
-		    gimple_set_no_warning (stmt, true);
-		  }
-	      }
-	}
+      maybe_warn_overflow (stmt, lenrange[2], rvals);
     }
   else
     {
-- 
GitLab