public inbox for gdb-patches@sourceware.org
 help / color / mirror / Atom feed
* [PATCH 0/2] Expression Evaluation Changes For Dynamic Types
@ 2021-01-11 13:20 Andrew Burgess
  2021-01-11 13:20 ` [PATCH 1/2] gdb: call value_ind for pointers to dynamic types in UNOP_IND evaluation Andrew Burgess
                   ` (2 more replies)
  0 siblings, 3 replies; 11+ messages in thread
From: Andrew Burgess @ 2021-01-11 13:20 UTC (permalink / raw)
  To: gdb-patches

Two changes related to expression evaluation w.r.t. dynamic types.

All feedback welcome.

Thanks,
Andrew



---

Andrew Burgess (2):
  gdb: call value_ind for pointers to dynamic types in UNOP_IND
    evaluation
  gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT

 gdb/ChangeLog                                 |  10 ++
 gdb/eval.c                                    |  38 +++--
 gdb/testsuite/ChangeLog                       |   9 +
 .../gdb.fortran/dynamic-ptype-whatis.exp      | 158 ++++++++++++++++++
 .../gdb.fortran/dynamic-ptype-whatis.f90      |  93 +++++++++++
 .../gdb.fortran/pointer-to-pointer.exp        |  29 ++--
 6 files changed, 312 insertions(+), 25 deletions(-)
 create mode 100644 gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.exp
 create mode 100644 gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.f90

-- 
2.25.4


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [PATCH 1/2] gdb: call value_ind for pointers to dynamic types in UNOP_IND evaluation
  2021-01-11 13:20 [PATCH 0/2] Expression Evaluation Changes For Dynamic Types Andrew Burgess
@ 2021-01-11 13:20 ` Andrew Burgess
  2021-02-11 20:41   ` Tom Tromey
  2021-02-24 15:53   ` Andrew Burgess
  2021-01-11 13:20 ` [PATCH 2/2] gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT Andrew Burgess
  2021-01-28 19:57 ` PING: Re: [PATCH 0/2] Expression Evaluation Changes For Dynamic Types Andrew Burgess
  2 siblings, 2 replies; 11+ messages in thread
From: Andrew Burgess @ 2021-01-11 13:20 UTC (permalink / raw)
  To: gdb-patches

When evaluating and expression containing UNOP_IND in mode
EVAL_AVOID_SIDE_EFFECTS, GDB currently (mostly) returns the result of
a call to value_zero meaning we get back an object with the correct
type, but its contents are all zero.

If the target type contains fields with dynamic type then in order to
resolve these dynamic fields GDB will need to read the value of the
field from within the parent object.  In this case the field value
will be zero as a result of the call to value_zero mentioned above.

The idea behind EVAL_AVOID_SIDE_EFFECTS is to avoid the chance that
doing something like `ptype` will modify state within the target, for
example consider: ptype i++.

However, there is already precedence within GDB that sometimes, in
order to get accurate type results, we can't avoid reading from the
target, even when EVAL_AVOID_SIDE_EFFECTS is in effect.  For example I
would point to eval.c:evaluate_var_value, the handling of OP_REGISTER,
the handling of value_x_unop in many places.  I believe the Ada
expression evaluator also ignore EVAL_AVOID_SIDE_EFFECTS in some
cases.

I am therefor proposing that, in the case where a pointer points at a
dynamic type, we allow UNOP_IND to perform the actual indirection.
This allows accurate types to be displayed in more cases.

gdb/ChangeLog:

	* eval.c (evaluate_subexp_standard): Call value_ind for points to
	dynamic types in UNOP_IND.

gdb/testsuite/ChangeLog:

	* gdb.fortran/pointer-to-pointer.exp: Additional tests.
---
 gdb/ChangeLog                                 |  5 +++
 gdb/eval.c                                    | 36 ++++++++++++-------
 gdb/testsuite/ChangeLog                       |  4 +++
 .../gdb.fortran/pointer-to-pointer.exp        | 29 +++++++++------
 4 files changed, 51 insertions(+), 23 deletions(-)

diff --git a/gdb/eval.c b/gdb/eval.c
index e63511b7005..dfe6e403f97 100644
--- a/gdb/eval.c
+++ b/gdb/eval.c
@@ -2422,19 +2422,29 @@ evaluate_subexp_standard (struct type *expect_type,
       else if (noside == EVAL_AVOID_SIDE_EFFECTS)
 	{
 	  type = check_typedef (value_type (arg1));
-	  if (type->code () == TYPE_CODE_PTR
-	      || TYPE_IS_REFERENCE (type)
-	  /* In C you can dereference an array to get the 1st elt.  */
-	      || type->code () == TYPE_CODE_ARRAY
-	    )
-	    return value_zero (TYPE_TARGET_TYPE (type),
-			       lval_memory);
-	  else if (type->code () == TYPE_CODE_INT)
-	    /* GDB allows dereferencing an int.  */
-	    return value_zero (builtin_type (exp->gdbarch)->builtin_int,
-			       lval_memory);
-	  else
-	    error (_("Attempt to take contents of a non-pointer value."));
+
+	  /* If the type pointed to is dynamic then in order to resolve the
+	     dynamic properties we must actually dereference the pointer.
+	     There is a risk that this dereference will have side-effects
+	     in the inferior, but being able to print accurate type
+	     information seems worth the risk. */
+	  if ((type->code () != TYPE_CODE_PTR
+	       && !TYPE_IS_REFERENCE (type))
+	      || !is_dynamic_type (TYPE_TARGET_TYPE (type)))
+	    {
+	      if (type->code () == TYPE_CODE_PTR
+		  || TYPE_IS_REFERENCE (type)
+		  /* In C you can dereference an array to get the 1st elt.  */
+		  || type->code () == TYPE_CODE_ARRAY)
+		return value_zero (TYPE_TARGET_TYPE (type),
+				   lval_memory);
+	      else if (type->code () == TYPE_CODE_INT)
+		/* GDB allows dereferencing an int.  */
+		return value_zero (builtin_type (exp->gdbarch)->builtin_int,
+				   lval_memory);
+	      else
+		error (_("Attempt to take contents of a non-pointer value."));
+	    }
 	}
 
       /* Allow * on an integer so we can cast it to whatever we want.
diff --git a/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp b/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
index 27739cc6cf3..306168b2876 100644
--- a/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
+++ b/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
@@ -30,20 +30,29 @@ if ![fortran_runto_main] {
     return -1
 }
 
-# Depending on the compiler being used, the type names can be printed differently.
+# Depending on the compiler being used, the type names can be printed
+# differently.
 set real4 [fortran_real4]
 
 gdb_breakpoint [gdb_get_line_number "Break Here"]
 gdb_continue_to_breakpoint "Break Here"
 
+gdb_test "print buffer" \
+    " = \\(PTR TO -> \\( Type l_buffer \\)\\) $hex"
+gdb_test "ptype buffer" \
+    [multi_line \
+	 "type = PTR TO -> \\( Type l_buffer" \
+	 "    $real4 :: alpha\\(:\\)" \
+	 "End Type l_buffer \\)" ]
+gdb_test "ptype buffer%alpha" "type = $real4 \\(5\\)"
+
+# GDB allows pointer types to be dereferenced using '*'.  This is not
+# real Fortran syntax, just something extra that GDB supports.
 gdb_test "print *buffer" \
     " = \\( alpha = \\(1\\.5, 2\\.5, 3\\.5, 4\\.5, 5\\.5\\) \\)"
-
-set l_buffer_type [multi_line \
-		       "Type l_buffer" \
-		       "    $real4 :: alpha\\(:\\)" \
-		       "End Type l_buffer" ]
-
-gdb_test "ptype buffer" "type = PTR TO -> \\( ${l_buffer_type} \\)"
-gdb_test "ptype *buffer" "type = ${l_buffer_type}"
-gdb_test "ptype buffer%alpha" "type = $real4 \\(5\\)"
+gdb_test "ptype *buffer" \
+    [multi_line \
+	 "type = Type l_buffer" \
+	 "    $real4 :: alpha\\(5\\)" \
+	 "End Type l_buffer" ]
+gdb_test "ptype (*buffer)%alpha" "type = $real4 \\(5\\)"
-- 
2.25.4


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [PATCH 2/2] gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT
  2021-01-11 13:20 [PATCH 0/2] Expression Evaluation Changes For Dynamic Types Andrew Burgess
  2021-01-11 13:20 ` [PATCH 1/2] gdb: call value_ind for pointers to dynamic types in UNOP_IND evaluation Andrew Burgess
@ 2021-01-11 13:20 ` Andrew Burgess
  2021-02-11 20:43   ` Tom Tromey
  2021-01-28 19:57 ` PING: Re: [PATCH 0/2] Expression Evaluation Changes For Dynamic Types Andrew Burgess
  2 siblings, 1 reply; 11+ messages in thread
From: Andrew Burgess @ 2021-01-11 13:20 UTC (permalink / raw)
  To: gdb-patches

This commit is a replacement for this previously posted patch:

  https://sourceware.org/pipermail/gdb-patches/2020-July/170335.html

However, the solution presented here is more aggressive than the
previous proposal.

The motivation behind the original patch can be seen in the new test,
which gives a GDB session like this:

  (gdb) ptype var8
  type = Type type6
      PTR TO -> ( Type type2 :: ptr_1 )
      PTR TO -> ( Type type2 :: ptr_2 )
  End Type type6
  (gdb) ptype var8%ptr_2
  type = PTR TO -> ( Type type2
      integer(kind=4) :: spacer
      Type type1, allocatable :: t2_array(:)
  End Type type2 )
  (gdb) ptype var8%ptr_2%t2_array
  Cannot access memory at address 0x8
  (gdb)

The final access results in an expression that looks like this:

  Dump of expression @ 0x51897e0, after conversion to prefix form:
  Expression: `MAIN__::var8.ptr_2.t2_array'
  	Language fortran, 14 elements, 16 bytes each.

  	    0  STRUCTOP_STRUCT       Element name: `t2_array'
  	    5    STRUCTOP_STRUCT       Element name: `ptr_2'
  	   10      OP_VAR_VALUE          Block @0x4c53520, symbol @0x4c534a0 (var8)

GDB will first get a value for `var8`, from which it extracts a value
for the element `ptr_2`, and finally GDB dereferences the pointer and
extracts the element `t2_array`.

The problem is that when looking for the type of an expression GDB
evaluates the expression in EVAL_AVOID_SIDE_EFFECTS mode, as a result
the pointer value `ptr_2` is returned with contents set to the
constant value 0.

Normally this is fine as we only plan to look at the type being
pointed too, but for dynamic types we need the pointer value so we can
correctly fetch the dynamic properties of the value from target
memory.  What ends up happening is that GDB reads the pointer value of
zero, and then uses this while evaluating the DWARF expressions.  One
of these expressions requires GDB to access object address plus 8,
which leads to an attempt to read from memory address 0x8.

When considering a solution to this problem I was thinking about what
EVAL_AVOID_SIDE_EFFECTS is actually for.  The motivation is to reduce
the chance that GDB asking for something like `ptype`, will have side
effect in the target.  As with memory mapped devices, even just
reading memory could be enough to modify the target, then GDB is very
defensive and even when extracting a field from a struct, we have an
EVAL_AVOID_SIDE_EFFECTS case.

In the original patch I tried to keep this special case, but ignore it
when dynamic types are found.  However, after more thought I believe
this is pointless.  I now believe handling EVAL_AVOID_SIDE_EFFECTS
in this case should be removed, here's why:

The bottom layer of the expression tree OP_VAR_VALUE already chooses
to NOT handle the EVAL_AVOID_SIDE_EFFECTS.  In this case it is for
'set print object' handling, however, the reasoning could just as
easily apply for dynamic type handling.

What this means is that the OP_VAR_VALUE already returns a lazy value
pointing at the actual variable contents.

Note however, that this is a lazy value.  If all we do with this is
ask GDB about the values type, and the value does not have dynamic
type, the GDB will never actually fetch the value contents from the
target.

Extracting a field from a struct (the STRUCTOP_STRUCT handling), will
itself return a lazy value if we are dealing with a non-dynamically
typed field.  Again, if all we do is ask about the type of this field
then GDB will never actually fetch the field value from the inferior.

It is only when GDB "needs" the field contents in order to resolve a
dynamic type that we end up reading things from the inferior.

The question then becomes which is better in the above case, having
GDB show the accurate (resolved) dynamic type, showing the unresolved
dynamic type, or maybe just throwing a more informative error?

I believe that showing the resolved dynamic type is the best solution,
and I believe that this is what other languages with dynamic types,
like Ada, already do.  I think when debugging, the user is more likely
to want to know the resolved type than the unresolved type.

In order to prove to myself that making the change I propose in this
patch does not cause GDB to access any additional target memory I did
the following:

Modified STRUCTOP_STRUCT handling to make the EVAL_AVOID_SIDE_EFFECTS
block switchable, like:

  if (noside == EVAL_AVOID_SIDE_EFFECTS && gdb_old_structop_struct)
    arg3 = value_zero (value_type (arg3), VALUE_LVAL (arg3));

Then I created a new record_stratum target which implemented the
xfer_partial method only.  In the xfer_partial I recorded into a list
all of the memory accesses that were performed.

Next I modified evaluate_type (the entry point for expression
evaluation for things like ptype and whatis) to do the following:

  - Clear the dcache,
  - Push the new record_stratum target,
  - Set gdb_old_structop_struct to true,
  - Call evaluate_subexp,
  - Take a copy of all memory accesses performed.
  - Now clear the list of all memory accesses in the record_stratum
    target,
  - Set gdb_old_structop_struct to false,
  - Call evaluate_subexp again,
  - Compare the list of memory access between the old way and the new
    way.
  - If we did more memory accesses when using the new way than when
    using the old way, then print a message.

I then re-ran the testsuite and looked to see how many times the
message was printed.

The only times I saw the message being printed was for the new Fortran
tests that I added in this commit - this was expected, as these tests
are the ones that print the type for dynamic fields.

For me this confirms that my reasoning behind this patch is sound and
that it is safe for use to remove the EVAL_AVOID_SIDE_EFFECTS handling
from STRUCTOP_STRUCT and GDB will not access target memory any more
than it currently does.

In this commit I am only proposing that we modify the STRUCTOP_STRUCT
handling, though I think that we could (and possibly should) update
others like STRUCTOP_PTR too.  However, Fortran doesn't make use of
STRUCTOP_PTR so I don't have any actual need to change how this is
handled.

All feedback is welcome.

gdb/ChangeLog:

	* eval.c (evaluate_subexp_standard): Remove
	EVAL_AVOID_SIDE_EFFECTS handling from STRUCTOP_STRUCT.

gdb/testsuite/ChangeLog:

	* gdb.fortran/dynamic-ptype-whatis.exp: New file.
	* gdb.fortran/dynamic-ptype-whatis.f90: New file.
---
 gdb/ChangeLog                                 |   5 +
 gdb/eval.c                                    |   2 -
 gdb/testsuite/ChangeLog                       |   5 +
 .../gdb.fortran/dynamic-ptype-whatis.exp      | 158 ++++++++++++++++++
 .../gdb.fortran/dynamic-ptype-whatis.f90      |  93 +++++++++++
 5 files changed, 261 insertions(+), 2 deletions(-)
 create mode 100644 gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.exp
 create mode 100644 gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.f90

diff --git a/gdb/eval.c b/gdb/eval.c
index dfe6e403f97..0a2ae8baf28 100644
--- a/gdb/eval.c
+++ b/gdb/eval.c
@@ -1837,8 +1837,6 @@ evaluate_subexp_standard (struct type *expect_type,
 	return eval_skip_value (exp);
       arg3 = value_struct_elt (&arg1, NULL, &exp->elts[pc + 2].string,
 			       NULL, "structure");
-      if (noside == EVAL_AVOID_SIDE_EFFECTS)
-	arg3 = value_zero (value_type (arg3), VALUE_LVAL (arg3));
       return arg3;
 
     case STRUCTOP_PTR:
diff --git a/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.exp b/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.exp
new file mode 100644
index 00000000000..d2ffd6d73f7
--- /dev/null
+++ b/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.exp
@@ -0,0 +1,158 @@
+# Copyright 2021 Free Software Foundation, Inc.
+
+# This program is free software; you can redistribute it and/or modify
+# it under the terms of the GNU General Public License as published by
+# the Free Software Foundation; either version 3 of the License, or
+# (at your option) any later version.
+#
+# This program is distributed in the hope that it will be useful,
+# but WITHOUT ANY WARRANTY; without even the implied warranty of
+# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+# GNU General Public License for more details.
+#
+# You should have received a copy of the GNU General Public License
+# along with this program.  If not, see <http://www.gnu.org/licenses/> .
+
+# Test using whatis and ptype on different configurations of dynamic
+# types.
+
+if {[skip_fortran_tests]} { return -1 }
+
+standard_testfile ".f90"
+load_lib fortran.exp
+
+if {[prepare_for_testing ${testfile}.exp ${testfile} ${srcfile} \
+	 {debug f90}]} {
+    return -1
+}
+
+if {![fortran_runto_main]} {
+    perror "Could not run to main."
+    continue
+}
+
+gdb_breakpoint [gdb_get_line_number "Break Here"]
+gdb_continue_to_breakpoint "Break Here"
+
+gdb_test "whatis var1" "type = real\\(kind=4\\) \\(3\\)"
+gdb_test "whatis var2" "type = real\\(kind=4\\), allocatable \\(4\\)"
+gdb_test "whatis var3" "type = Type type1"
+gdb_test "whatis var4" "type = Type type2"
+gdb_test "whatis var5" "type = Type type3"
+gdb_test "whatis var6" "type = Type type4"
+gdb_test "whatis var7" "type = Type type5"
+gdb_test "ptype var1" "type = real\\(kind=4\\) \\(3\\)"
+gdb_test "ptype var2" "type = real\\(kind=4\\), allocatable \\(4\\)"
+gdb_test "ptype var3" \
+    [ multi_line "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1" ]
+gdb_test "ptype var4" \
+    [multi_line "type = Type type2" \
+	 "    integer\\(kind=4\\) :: spacer" \
+	 "    Type type1, allocatable :: t2_array\\(3\\)" \
+	 "End Type type2"]
+gdb_test "ptype var5" \
+    [ multi_line "type = Type type3" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type1 :: t3_array\\(3\\)"\
+	  "End Type type3" ]
+gdb_test "ptype var6" \
+    [ multi_line "type = Type type4" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type2, allocatable :: t4_array\\(3\\)" \
+	  "End Type type4" ]
+gdb_test "ptype var7" \
+    [ multi_line "type = Type type5" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type2 :: t5_array\\(4\\)" \
+	  "End Type type5" ]
+gdb_test "whatis var3%t1_i" "type = integer\\(kind=4\\)"
+gdb_test "whatis var4%t2_array" "type = Type type1, allocatable \\(3\\)"
+gdb_test "whatis var5%t3_array" "type = Type type1 \\(3\\)"
+gdb_test "whatis var6%t4_array" "type = Type type2, allocatable \\(3\\)"
+gdb_test "whatis var7%t5_array" "type = Type type2 \\(4\\)"
+gdb_test "ptype var3%t1_i" [ multi_line "type = integer\\(kind=4\\)" ]
+gdb_test "ptype var4%t2_array" [ multi_line "type = Type type1" \
+				     "    integer\\(kind=4\\) :: spacer" \
+				     "    integer\\(kind=4\\) :: t1_i" \
+				     "End Type type1, allocatable \\(3\\)" ]
+gdb_test "ptype var5%t3_array" [ multi_line "type = Type type1" \
+				     "    integer\\(kind=4\\) :: spacer" \
+				     "    integer\\(kind=4\\) :: t1_i" \
+				     "End Type type1 \\(3\\)" ]
+gdb_test "ptype var6%t4_array" \
+    [ multi_line "type = Type type2" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type1, allocatable :: t2_array\\(:\\)" \
+	  "End Type type2, allocatable \\(3\\)" ]
+gdb_test "ptype var7%t5_array" \
+    [ multi_line "type = Type type2" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type1, allocatable :: t2_array\\(:\\)" \
+	  "End Type type2 \\(4\\)" ]
+gdb_test "whatis var4%t2_array(1)" "type = Type type1"
+gdb_test "whatis var5%t3_array(1)" "type = Type type1"
+gdb_test "whatis var6%t4_array(1)" "type = Type type2"
+gdb_test "whatis var7%t5_array(1)" "type = Type type2"
+gdb_test "ptype var4%t2_array(1)" \
+    [ multi_line "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1" ]
+gdb_test "ptype var5%t3_array(1)" \
+    [ multi_line "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1" ]
+gdb_test "ptype var6%t4_array(1)" \
+    [ multi_line "type = Type type2" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type1, allocatable :: t2_array\\(2\\)" \
+	  "End Type type2" ]
+gdb_test "ptype var7%t5_array(1)" \
+    [ multi_line "type = Type type2" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type1, allocatable :: t2_array\\(2\\)" \
+	  "End Type type2" ]
+gdb_test "whatis var4%t2_array(1)%t1_i" "type = integer\\(kind=4\\)"
+gdb_test "whatis var5%t3_array(1)%t1_i" "type = integer\\(kind=4\\)"
+gdb_test "whatis var6%t4_array(1)%t2_array" \
+    "type = Type type1, allocatable \\(2\\)"
+gdb_test "whatis var7%t5_array(1)%t2_array" \
+    "type = Type type1, allocatable \\(2\\)"
+gdb_test "ptype var4%t2_array(1)%t1_i" "type = integer\\(kind=4\\)"
+gdb_test "ptype var5%t3_array(1)%t1_i" "type = integer\\(kind=4\\)"
+gdb_test "ptype var6%t4_array(1)%t2_array" \
+    [ multi_line "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1, allocatable \\(2\\)" ]
+gdb_test "ptype var7%t5_array(1)%t2_array" \
+    [ multi_line "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1, allocatable \\(2\\)" ]
+gdb_test "whatis var6%t4_array(1)%t2_array(1)" \
+    "type = Type type1"
+gdb_test "whatis var7%t5_array(1)%t2_array(1)" \
+    "type = Type type1"
+gdb_test "ptype var6%t4_array(1)%t2_array(1)" \
+    [ multi_line \
+	  "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1" ]
+gdb_test "ptype var7%t5_array(1)%t2_array(1)" \
+    [ multi_line \
+	  "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1" ]
+gdb_test "ptype var8%ptr_1%t2_array" \
+    [ multi_line \
+	  "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1, allocatable \\(3\\)" ]
diff --git a/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.f90 b/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.f90
new file mode 100644
index 00000000000..e56bf7952dc
--- /dev/null
+++ b/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.f90
@@ -0,0 +1,93 @@
+! Copyright 2021 Free Software Foundation, Inc.
+!
+! This program is free software; you can redistribute it and/or modify
+! it under the terms of the GNU General Public License as published by
+! the Free Software Foundation; either version 3 of the License, or
+! (at your option) any later version.
+!
+! This program is distributed in the hope that it will be useful,
+! but WITHOUT ANY WARRANTY; without even the implied warranty of
+! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+! GNU General Public License for more details.
+!
+! You should have received a copy of the GNU General Public License
+! along with this program.  If not, see <http://www.gnu.org/licenses/>.
+
+program main
+
+  ! A non-dynamic type.
+  type type1
+     integer(kind=4) :: spacer
+     integer(kind=4) t1_i
+  end type type1
+
+  ! A first dynamic type.  The array is of a static type.
+  type type2
+     integer(kind=4) :: spacer
+     type(type1), allocatable :: t2_array(:)
+  end type type2
+
+  ! Another dynamic type, the array is again a static type.
+  type type3
+     integer(kind=4) :: spacer
+     type(type1), pointer :: t3_array(:)
+  end type type3
+
+  ! A dynamic type, this time the array contains a dynamic type.
+  type type4
+     integer(kind=4) :: spacer
+     type(type2), allocatable :: t4_array(:)
+  end type type4
+
+  ! A static type, the array though contains dynamic types.
+  type type5
+     integer(kind=4) :: spacer
+     type(type2) :: t5_array (4)
+  end type type5
+
+  ! A static type containing pointers to a type that contains a
+  ! dynamic array.
+  type type6
+     type(type2), pointer :: ptr_1
+     type(type2), pointer :: ptr_2
+  end type type6
+
+  real, dimension(:), pointer :: var1
+  real, dimension(:), allocatable :: var2
+  type(type1) :: var3
+  type(type2), target :: var4
+  type(type3) :: var5
+  type(type4) :: var6
+  type(type5) :: var7
+  type(type6) :: var8
+
+  allocate (var1 (3))
+
+  allocate (var2 (4))
+
+  allocate (var4%t2_array(3))
+
+  allocate (var5%t3_array(3))
+
+  allocate (var6%t4_array(3))
+  allocate (var6%t4_array(1)%t2_array(2))
+  allocate (var6%t4_array(2)%t2_array(5))
+  allocate (var6%t4_array(3)%t2_array(4))
+
+  allocate (var7%t5_array(1)%t2_array(2))
+  allocate (var7%t5_array(2)%t2_array(5))
+  allocate (var7%t5_array(3)%t2_array(4))
+  allocate (var7%t5_array(4)%t2_array(1))
+
+  var8%ptr_1 => var4
+  var8%ptr_2 => var4
+
+  print *, var1		! Break Here
+  print *, var2
+  print *, var3
+  print *, var4%t2_array(1)
+  print *, var5%t3_array(2)
+  print *, var6%t4_array(1)%t2_array(1)
+  print *, var7%t5_array(1)%t2_array(1)
+
+end program main
-- 
2.25.4


^ permalink raw reply	[flat|nested] 11+ messages in thread

* PING: Re: [PATCH 0/2] Expression Evaluation Changes For Dynamic Types
  2021-01-11 13:20 [PATCH 0/2] Expression Evaluation Changes For Dynamic Types Andrew Burgess
  2021-01-11 13:20 ` [PATCH 1/2] gdb: call value_ind for pointers to dynamic types in UNOP_IND evaluation Andrew Burgess
  2021-01-11 13:20 ` [PATCH 2/2] gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT Andrew Burgess
@ 2021-01-28 19:57 ` Andrew Burgess
  2021-02-11 10:28   ` PINGv2: " Andrew Burgess
  2 siblings, 1 reply; 11+ messages in thread
From: Andrew Burgess @ 2021-01-28 19:57 UTC (permalink / raw)
  To: gdb-patches

ping!

* Andrew Burgess <andrew.burgess@embecosm.com> [2021-01-11 13:20:57 +0000]:

> Two changes related to expression evaluation w.r.t. dynamic types.
> 
> All feedback welcome.
> 
> Thanks,
> Andrew
> 
> 
> 
> ---
> 
> Andrew Burgess (2):
>   gdb: call value_ind for pointers to dynamic types in UNOP_IND
>     evaluation
>   gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT
> 
>  gdb/ChangeLog                                 |  10 ++
>  gdb/eval.c                                    |  38 +++--
>  gdb/testsuite/ChangeLog                       |   9 +
>  .../gdb.fortran/dynamic-ptype-whatis.exp      | 158 ++++++++++++++++++
>  .../gdb.fortran/dynamic-ptype-whatis.f90      |  93 +++++++++++
>  .../gdb.fortran/pointer-to-pointer.exp        |  29 ++--
>  6 files changed, 312 insertions(+), 25 deletions(-)
>  create mode 100644 gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.exp
>  create mode 100644 gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.f90
> 
> -- 
> 2.25.4
> 

^ permalink raw reply	[flat|nested] 11+ messages in thread

* Re: PINGv2: Re: [PATCH 0/2] Expression Evaluation Changes For Dynamic Types
  2021-01-28 19:57 ` PING: Re: [PATCH 0/2] Expression Evaluation Changes For Dynamic Types Andrew Burgess
@ 2021-02-11 10:28   ` Andrew Burgess
  0 siblings, 0 replies; 11+ messages in thread
From: Andrew Burgess @ 2021-02-11 10:28 UTC (permalink / raw)
  To: gdb-patches

Anyone have any thoughts?

Thanks,
Andrew

* Andrew Burgess <andrew.burgess@embecosm.com> [2021-01-28 19:57:53 +0000]:

> ping!
> 
> * Andrew Burgess <andrew.burgess@embecosm.com> [2021-01-11 13:20:57 +0000]:
> 
> > Two changes related to expression evaluation w.r.t. dynamic types.
> > 
> > All feedback welcome.
> > 
> > Thanks,
> > Andrew
> > 
> > 
> > 
> > ---
> > 
> > Andrew Burgess (2):
> >   gdb: call value_ind for pointers to dynamic types in UNOP_IND
> >     evaluation
> >   gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT
> > 
> >  gdb/ChangeLog                                 |  10 ++
> >  gdb/eval.c                                    |  38 +++--
> >  gdb/testsuite/ChangeLog                       |   9 +
> >  .../gdb.fortran/dynamic-ptype-whatis.exp      | 158 ++++++++++++++++++
> >  .../gdb.fortran/dynamic-ptype-whatis.f90      |  93 +++++++++++
> >  .../gdb.fortran/pointer-to-pointer.exp        |  29 ++--
> >  6 files changed, 312 insertions(+), 25 deletions(-)
> >  create mode 100644 gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.exp
> >  create mode 100644 gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.f90
> > 
> > -- 
> > 2.25.4
> > 

^ permalink raw reply	[flat|nested] 11+ messages in thread

* Re: [PATCH 1/2] gdb: call value_ind for pointers to dynamic types in UNOP_IND evaluation
  2021-01-11 13:20 ` [PATCH 1/2] gdb: call value_ind for pointers to dynamic types in UNOP_IND evaluation Andrew Burgess
@ 2021-02-11 20:41   ` Tom Tromey
  2021-02-16 18:10     ` Andrew Burgess
  2021-02-24 15:53   ` Andrew Burgess
  1 sibling, 1 reply; 11+ messages in thread
From: Tom Tromey @ 2021-02-11 20:41 UTC (permalink / raw)
  To: Andrew Burgess; +Cc: gdb-patches

>>>>> "Andrew" == Andrew Burgess <andrew.burgess@embecosm.com> writes:

Andrew> However, there is already precedence within GDB that sometimes, in
Andrew> order to get accurate type results, we can't avoid reading from the
Andrew> target, even when EVAL_AVOID_SIDE_EFFECTS is in effect.

Probably we should adopt the rule that EVAL_AVOID_SIDE_EFFECTS means
"will not write memory" -- but let it read memory.

This isn't bulletproof if someone has memory-mapped peripherals or
something.  Do those still exist?  If so maybe we'd need a mechanism to
deal with them.

Andrew> I am therefor proposing that, in the case where a pointer points at a
Andrew> dynamic type, we allow UNOP_IND to perform the actual indirection.
Andrew> This allows accurate types to be displayed in more cases.

What happens if there is no running inferior or core file?
Normally "ptype mumble" works reasonably well even with just an
executable or a .o.

Tom

^ permalink raw reply	[flat|nested] 11+ messages in thread

* Re: [PATCH 2/2] gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT
  2021-01-11 13:20 ` [PATCH 2/2] gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT Andrew Burgess
@ 2021-02-11 20:43   ` Tom Tromey
  2021-02-16 18:32     ` Andrew Burgess
  0 siblings, 1 reply; 11+ messages in thread
From: Tom Tromey @ 2021-02-11 20:43 UTC (permalink / raw)
  To: Andrew Burgess; +Cc: gdb-patches

>>>>> "Andrew" == Andrew Burgess <andrew.burgess@embecosm.com> writes:

Andrew> In this commit I am only proposing that we modify the STRUCTOP_STRUCT
Andrew> handling, though I think that we could (and possibly should) update
Andrew> others like STRUCTOP_PTR too.  However, Fortran doesn't make use of
Andrew> STRUCTOP_PTR so I don't have any actual need to change how this is
Andrew> handled.

I think it's perhaps best if the two are kept reasonably parallel.

Andrew>        arg3 = value_struct_elt (&arg1, NULL, &exp->elts[pc + 2].string,
Andrew>  			       NULL, "structure");
Andrew> -      if (noside == EVAL_AVOID_SIDE_EFFECTS)
Andrew> -	arg3 = value_zero (value_type (arg3), VALUE_LVAL (arg3));

This bit of code that you have removed seems pretty pointless to me, FWIW.
After all, arg3 was already computed -- so changing it to value_zero
doesn't seem particularly worthwhile.

Tom

^ permalink raw reply	[flat|nested] 11+ messages in thread

* Re: [PATCH 1/2] gdb: call value_ind for pointers to dynamic types in UNOP_IND evaluation
  2021-02-11 20:41   ` Tom Tromey
@ 2021-02-16 18:10     ` Andrew Burgess
  0 siblings, 0 replies; 11+ messages in thread
From: Andrew Burgess @ 2021-02-16 18:10 UTC (permalink / raw)
  To: Tom Tromey; +Cc: gdb-patches

* Tom Tromey <tom@tromey.com> [2021-02-11 13:41:10 -0700]:

> >>>>> "Andrew" == Andrew Burgess <andrew.burgess@embecosm.com> writes:
> 
> Andrew> However, there is already precedence within GDB that sometimes, in
> Andrew> order to get accurate type results, we can't avoid reading from the
> Andrew> target, even when EVAL_AVOID_SIDE_EFFECTS is in effect.
> 
> Probably we should adopt the rule that EVAL_AVOID_SIDE_EFFECTS means
> "will not write memory" -- but let it read memory.

I'd be happy with that.  To some extent we already do this.  Currently
the policy seems to be no writing or reading.  Until a user hits a
case where reading is required, then we introduce an exception.

> 
> This isn't bulletproof if someone has memory-mapped peripherals or
> something.  Do those still exist?  If so maybe we'd need a mechanism to
> deal with them.

Yes that would be a problem.  Any maybe having a switch so the user
could say "really don't access memory unless I say so" would be
useful.  But in general, due to our lazy value system, GDB will only
go and read memory when it is required in order to give the correct
answer.

> 
> Andrew> I am therefor proposing that, in the case where a pointer points at a
> Andrew> dynamic type, we allow UNOP_IND to perform the actual indirection.
> Andrew> This allows accurate types to be displayed in more cases.
> 
> What happens if there is no running inferior or core file?
> Normally "ptype mumble" works reasonably well even with just an
> executable or a .o.

So mumble would have to be something of dynamic type.  Which kind-of
implies runtime behaviour.  No runtime, no type I guess.

Honestly, in Fortran I don't know how you'd get to a position where
you could ask 'ptype mumble' about something dynamic _without_ having
a running target or a core file, as, as I understand Fortran,
everything is wrapped inside either a program of subroutine.  But I
don't claim to be any kind of super knowledgeable Fortran programmer.

But I think we can imagine what would happen.  In order to ask for the
type of mumble in this no running target situation, mumble must surely
be global.  The type of mumble will have some dynamic properties,
these usually say things like:

  Upper_Bound: Push_object_address, Read_4_bytes
  Lower_Bound: Push_object_address, Add_4, Read_4_bytes
  etc...

As mumble is global, then the object address would be some known
static address (in the object file), which presumably points to some
object description that includes space for the upper bound, lower
bound, etc.  These would all be initialised to some sane default (we
hope), which GDB would then read and process.

If the fields don't have sane defaults then GDB is going to display
garbage, but garbage that correctly reflects the current state of the
system I think.

But just to be clear.  The change I propose isn't going to effect any
statically typed language.  This will only impact dynamically typed
languages, when asking about a variable with dynamic type.

Thanks,
Andrew

^ permalink raw reply	[flat|nested] 11+ messages in thread

* Re: [PATCH 2/2] gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT
  2021-02-11 20:43   ` Tom Tromey
@ 2021-02-16 18:32     ` Andrew Burgess
  2021-02-20  0:00       ` Tom Tromey
  0 siblings, 1 reply; 11+ messages in thread
From: Andrew Burgess @ 2021-02-16 18:32 UTC (permalink / raw)
  To: Tom Tromey; +Cc: gdb-patches

* Tom Tromey <tom@tromey.com> [2021-02-11 13:43:48 -0700]:

> >>>>> "Andrew" == Andrew Burgess <andrew.burgess@embecosm.com> writes:
> 
> Andrew> In this commit I am only proposing that we modify the STRUCTOP_STRUCT
> Andrew> handling, though I think that we could (and possibly should) update
> Andrew> others like STRUCTOP_PTR too.  However, Fortran doesn't make use of
> Andrew> STRUCTOP_PTR so I don't have any actual need to change how this is
> Andrew> handled.
> 
> I think it's perhaps best if the two are kept reasonably parallel.
> 
> Andrew>        arg3 = value_struct_elt (&arg1, NULL, &exp->elts[pc + 2].string,
> Andrew>  			       NULL, "structure");
> Andrew> -      if (noside == EVAL_AVOID_SIDE_EFFECTS)
> Andrew> -	arg3 = value_zero (value_type (arg3), VALUE_LVAL (arg3));
> 
> This bit of code that you have removed seems pretty pointless to me, FWIW.
> After all, arg3 was already computed -- so changing it to value_zero
> doesn't seem particularly worthwhile.

I guess the thinking is that by replacing the lazy value obtained by
calling value_struct_elt with value_zero then future attempts to
fetch the contents of this value (arg3) will just return zero without
going to the target.

My problem with this is that IF this is happening, then this surely is
a bug in GDB's lazy value system, OR, as in my case, fetching the
contents of arg3 is required in order to correctly figure out the
type.

So I would say, lets remove the code as I propose, then if someone
comes back with an example of a statically typed case where GDB ends
up reading target memory, this is most likely a lazy value bug which
should be fixed elsewhere in GDB.

I don't want to argue to hard otherwise I might convince you the code
should stay ;-)

Here's an updated version of the patch that removes the code from
STRUCTOP_STRUCT, and STRUCTOP_PTR.

Thanks,
Andrew

---

commit 91ce37e82818ba451d594c17a3554a7296d06077
Author: Andrew Burgess <andrew.burgess@embecosm.com>
Date:   Fri Jan 8 13:07:32 2021 +0000

    gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT
    
    This commit is a replacement for this previously posted patch:
    
      https://sourceware.org/pipermail/gdb-patches/2020-July/170335.html
    
    However, the solution presented here is more aggressive than the
    previous proposal.
    
    The motivation behind the original patch can be seen in the new test,
    which gives a GDB session like this:
    
      (gdb) ptype var8
      type = Type type6
          PTR TO -> ( Type type2 :: ptr_1 )
          PTR TO -> ( Type type2 :: ptr_2 )
      End Type type6
      (gdb) ptype var8%ptr_2
      type = PTR TO -> ( Type type2
          integer(kind=4) :: spacer
          Type type1, allocatable :: t2_array(:)
      End Type type2 )
      (gdb) ptype var8%ptr_2%t2_array
      Cannot access memory at address 0x8
      (gdb)
    
    The final access results in an expression that looks like this:
    
      Dump of expression @ 0x51897e0, after conversion to prefix form:
      Expression: `MAIN__::var8.ptr_2.t2_array'
            Language fortran, 14 elements, 16 bytes each.
    
                0  STRUCTOP_STRUCT       Element name: `t2_array'
                5    STRUCTOP_STRUCT       Element name: `ptr_2'
               10      OP_VAR_VALUE          Block @0x4c53520, symbol @0x4c534a0 (var8)
    
    GDB will first get a value for `var8`, from which it extracts a value
    for the element `ptr_2`, and finally GDB dereferences the pointer and
    extracts the element `t2_array`.
    
    The problem is that when looking for the type of an expression GDB
    evaluates the expression in EVAL_AVOID_SIDE_EFFECTS mode, as a result
    the pointer value `ptr_2` is returned with contents set to the
    constant value 0.
    
    Normally this is fine as we only plan to look at the type being
    pointed too, but for dynamic types we need the pointer value so we can
    correctly fetch the dynamic properties of the value from target
    memory.  What ends up happening is that GDB reads the pointer value of
    zero, and then uses this while evaluating the DWARF expressions.  One
    of these expressions requires GDB to access object address plus 8,
    which leads to an attempt to read from memory address 0x8.
    
    When considering a solution to this problem I was thinking about what
    EVAL_AVOID_SIDE_EFFECTS is actually for.  The motivation is to reduce
    the chance that GDB asking for something like `ptype`, will have side
    effect in the target.  As with memory mapped devices, even just
    reading memory could be enough to modify the target, then GDB is very
    defensive and even when extracting a field from a struct, we have an
    EVAL_AVOID_SIDE_EFFECTS case.
    
    In the original patch I tried to keep this special case, but ignore it
    when dynamic types are found.  However, after more thought I believe
    this is pointless.  I now believe handling EVAL_AVOID_SIDE_EFFECTS
    in this case should be removed, here's why:
    
    The bottom layer of the expression tree OP_VAR_VALUE already chooses
    to NOT handle the EVAL_AVOID_SIDE_EFFECTS.  In this case it is for
    'set print object' handling, however, the reasoning could just as
    easily apply for dynamic type handling.
    
    What this means is that the OP_VAR_VALUE already returns a lazy value
    pointing at the actual variable contents.
    
    Note however, that this is a lazy value.  If all we do with this is
    ask GDB about the values type, and the value does not have dynamic
    type, the GDB will never actually fetch the value contents from the
    target.
    
    Extracting a field from a struct (the STRUCTOP_STRUCT handling), will
    itself return a lazy value if we are dealing with a non-dynamically
    typed field.  Again, if all we do is ask about the type of this field
    then GDB will never actually fetch the field value from the inferior.
    
    It is only when GDB "needs" the field contents in order to resolve a
    dynamic type that we end up reading things from the inferior.
    
    The question then becomes which is better in the above case, having
    GDB show the accurate (resolved) dynamic type, showing the unresolved
    dynamic type, or maybe just throwing a more informative error?
    
    I believe that showing the resolved dynamic type is the best solution,
    and I believe that this is what other languages with dynamic types,
    like Ada, already do.  I think when debugging, the user is more likely
    to want to know the resolved type than the unresolved type.
    
    In order to prove to myself that making the change I propose in this
    patch does not cause GDB to access any additional target memory I did
    the following:
    
    Modified STRUCTOP_STRUCT handling to make the EVAL_AVOID_SIDE_EFFECTS
    block switchable, like:
    
      if (noside == EVAL_AVOID_SIDE_EFFECTS && gdb_old_structop_struct)
        arg3 = value_zero (value_type (arg3), VALUE_LVAL (arg3));
    
    Then I created a new record_stratum target which implemented the
    xfer_partial method only.  In the xfer_partial I recorded into a list
    all of the memory accesses that were performed.
    
    Next I modified evaluate_type (the entry point for expression
    evaluation for things like ptype and whatis) to do the following:
    
      - Clear the dcache,
      - Push the new record_stratum target,
      - Set gdb_old_structop_struct to true,
      - Call evaluate_subexp,
      - Take a copy of all memory accesses performed.
      - Now clear the list of all memory accesses in the record_stratum
        target,
      - Set gdb_old_structop_struct to false,
      - Call evaluate_subexp again,
      - Compare the list of memory access between the old way and the new
        way.
      - If we did more memory accesses when using the new way than when
        using the old way, then print a message.
    
    I then re-ran the testsuite and looked to see how many times the
    message was printed.
    
    The only times I saw the message being printed was for the new Fortran
    tests that I added in this commit - this was expected, as these tests
    are the ones that print the type for dynamic fields.
    
    For me this confirms that my reasoning behind this patch is sound and
    that it is safe for use to remove the EVAL_AVOID_SIDE_EFFECTS handling
    from STRUCTOP_STRUCT and GDB will not access target memory any more
    than it currently does.
    
    The above discussion is all about STRUCTOP_STRUCT, however, I believe
    the same logic applies to STRUCTOP_PTR too.  However, Fortran doesn't
    exercise the STRUCTOP_PTR case, so I have no way of testing this
    code.
    
    However, regardless, I have changed STRUCTOP_PTR inline with my
    proposed change to STRUCTOP_STRUCT so that these two blocks of code
    are consistent.
    
    All feedback is welcome.
    
    gdb/ChangeLog:
    
            * eval.c (evaluate_subexp_standard): Remove
            EVAL_AVOID_SIDE_EFFECTS handling from STRUCTOP_STRUCT and
            STRUCTOP_PTR.
    
    gdb/testsuite/ChangeLog:
    
            * gdb.fortran/dynamic-ptype-whatis.exp: New file.
            * gdb.fortran/dynamic-ptype-whatis.f90: New file.

diff --git a/gdb/eval.c b/gdb/eval.c
index dfe6e403f97..866ef09c88f 100644
--- a/gdb/eval.c
+++ b/gdb/eval.c
@@ -1837,8 +1837,6 @@ evaluate_subexp_standard (struct type *expect_type,
 	return eval_skip_value (exp);
       arg3 = value_struct_elt (&arg1, NULL, &exp->elts[pc + 2].string,
 			       NULL, "structure");
-      if (noside == EVAL_AVOID_SIDE_EFFECTS)
-	arg3 = value_zero (value_type (arg3), VALUE_LVAL (arg3));
       return arg3;
 
     case STRUCTOP_PTR:
@@ -1892,8 +1890,6 @@ evaluate_subexp_standard (struct type *expect_type,
 
       arg3 = value_struct_elt (&arg1, NULL, &exp->elts[pc + 2].string,
 			       NULL, "structure pointer");
-      if (noside == EVAL_AVOID_SIDE_EFFECTS)
-	arg3 = value_zero (value_type (arg3), VALUE_LVAL (arg3));
       return arg3;
 
     case STRUCTOP_MEMBER:
diff --git a/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.exp b/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.exp
new file mode 100644
index 00000000000..d2ffd6d73f7
--- /dev/null
+++ b/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.exp
@@ -0,0 +1,158 @@
+# Copyright 2021 Free Software Foundation, Inc.
+
+# This program is free software; you can redistribute it and/or modify
+# it under the terms of the GNU General Public License as published by
+# the Free Software Foundation; either version 3 of the License, or
+# (at your option) any later version.
+#
+# This program is distributed in the hope that it will be useful,
+# but WITHOUT ANY WARRANTY; without even the implied warranty of
+# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+# GNU General Public License for more details.
+#
+# You should have received a copy of the GNU General Public License
+# along with this program.  If not, see <http://www.gnu.org/licenses/> .
+
+# Test using whatis and ptype on different configurations of dynamic
+# types.
+
+if {[skip_fortran_tests]} { return -1 }
+
+standard_testfile ".f90"
+load_lib fortran.exp
+
+if {[prepare_for_testing ${testfile}.exp ${testfile} ${srcfile} \
+	 {debug f90}]} {
+    return -1
+}
+
+if {![fortran_runto_main]} {
+    perror "Could not run to main."
+    continue
+}
+
+gdb_breakpoint [gdb_get_line_number "Break Here"]
+gdb_continue_to_breakpoint "Break Here"
+
+gdb_test "whatis var1" "type = real\\(kind=4\\) \\(3\\)"
+gdb_test "whatis var2" "type = real\\(kind=4\\), allocatable \\(4\\)"
+gdb_test "whatis var3" "type = Type type1"
+gdb_test "whatis var4" "type = Type type2"
+gdb_test "whatis var5" "type = Type type3"
+gdb_test "whatis var6" "type = Type type4"
+gdb_test "whatis var7" "type = Type type5"
+gdb_test "ptype var1" "type = real\\(kind=4\\) \\(3\\)"
+gdb_test "ptype var2" "type = real\\(kind=4\\), allocatable \\(4\\)"
+gdb_test "ptype var3" \
+    [ multi_line "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1" ]
+gdb_test "ptype var4" \
+    [multi_line "type = Type type2" \
+	 "    integer\\(kind=4\\) :: spacer" \
+	 "    Type type1, allocatable :: t2_array\\(3\\)" \
+	 "End Type type2"]
+gdb_test "ptype var5" \
+    [ multi_line "type = Type type3" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type1 :: t3_array\\(3\\)"\
+	  "End Type type3" ]
+gdb_test "ptype var6" \
+    [ multi_line "type = Type type4" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type2, allocatable :: t4_array\\(3\\)" \
+	  "End Type type4" ]
+gdb_test "ptype var7" \
+    [ multi_line "type = Type type5" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type2 :: t5_array\\(4\\)" \
+	  "End Type type5" ]
+gdb_test "whatis var3%t1_i" "type = integer\\(kind=4\\)"
+gdb_test "whatis var4%t2_array" "type = Type type1, allocatable \\(3\\)"
+gdb_test "whatis var5%t3_array" "type = Type type1 \\(3\\)"
+gdb_test "whatis var6%t4_array" "type = Type type2, allocatable \\(3\\)"
+gdb_test "whatis var7%t5_array" "type = Type type2 \\(4\\)"
+gdb_test "ptype var3%t1_i" [ multi_line "type = integer\\(kind=4\\)" ]
+gdb_test "ptype var4%t2_array" [ multi_line "type = Type type1" \
+				     "    integer\\(kind=4\\) :: spacer" \
+				     "    integer\\(kind=4\\) :: t1_i" \
+				     "End Type type1, allocatable \\(3\\)" ]
+gdb_test "ptype var5%t3_array" [ multi_line "type = Type type1" \
+				     "    integer\\(kind=4\\) :: spacer" \
+				     "    integer\\(kind=4\\) :: t1_i" \
+				     "End Type type1 \\(3\\)" ]
+gdb_test "ptype var6%t4_array" \
+    [ multi_line "type = Type type2" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type1, allocatable :: t2_array\\(:\\)" \
+	  "End Type type2, allocatable \\(3\\)" ]
+gdb_test "ptype var7%t5_array" \
+    [ multi_line "type = Type type2" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type1, allocatable :: t2_array\\(:\\)" \
+	  "End Type type2 \\(4\\)" ]
+gdb_test "whatis var4%t2_array(1)" "type = Type type1"
+gdb_test "whatis var5%t3_array(1)" "type = Type type1"
+gdb_test "whatis var6%t4_array(1)" "type = Type type2"
+gdb_test "whatis var7%t5_array(1)" "type = Type type2"
+gdb_test "ptype var4%t2_array(1)" \
+    [ multi_line "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1" ]
+gdb_test "ptype var5%t3_array(1)" \
+    [ multi_line "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1" ]
+gdb_test "ptype var6%t4_array(1)" \
+    [ multi_line "type = Type type2" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type1, allocatable :: t2_array\\(2\\)" \
+	  "End Type type2" ]
+gdb_test "ptype var7%t5_array(1)" \
+    [ multi_line "type = Type type2" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    Type type1, allocatable :: t2_array\\(2\\)" \
+	  "End Type type2" ]
+gdb_test "whatis var4%t2_array(1)%t1_i" "type = integer\\(kind=4\\)"
+gdb_test "whatis var5%t3_array(1)%t1_i" "type = integer\\(kind=4\\)"
+gdb_test "whatis var6%t4_array(1)%t2_array" \
+    "type = Type type1, allocatable \\(2\\)"
+gdb_test "whatis var7%t5_array(1)%t2_array" \
+    "type = Type type1, allocatable \\(2\\)"
+gdb_test "ptype var4%t2_array(1)%t1_i" "type = integer\\(kind=4\\)"
+gdb_test "ptype var5%t3_array(1)%t1_i" "type = integer\\(kind=4\\)"
+gdb_test "ptype var6%t4_array(1)%t2_array" \
+    [ multi_line "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1, allocatable \\(2\\)" ]
+gdb_test "ptype var7%t5_array(1)%t2_array" \
+    [ multi_line "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1, allocatable \\(2\\)" ]
+gdb_test "whatis var6%t4_array(1)%t2_array(1)" \
+    "type = Type type1"
+gdb_test "whatis var7%t5_array(1)%t2_array(1)" \
+    "type = Type type1"
+gdb_test "ptype var6%t4_array(1)%t2_array(1)" \
+    [ multi_line \
+	  "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1" ]
+gdb_test "ptype var7%t5_array(1)%t2_array(1)" \
+    [ multi_line \
+	  "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1" ]
+gdb_test "ptype var8%ptr_1%t2_array" \
+    [ multi_line \
+	  "type = Type type1" \
+	  "    integer\\(kind=4\\) :: spacer" \
+	  "    integer\\(kind=4\\) :: t1_i" \
+	  "End Type type1, allocatable \\(3\\)" ]
diff --git a/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.f90 b/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.f90
new file mode 100644
index 00000000000..e56bf7952dc
--- /dev/null
+++ b/gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.f90
@@ -0,0 +1,93 @@
+! Copyright 2021 Free Software Foundation, Inc.
+!
+! This program is free software; you can redistribute it and/or modify
+! it under the terms of the GNU General Public License as published by
+! the Free Software Foundation; either version 3 of the License, or
+! (at your option) any later version.
+!
+! This program is distributed in the hope that it will be useful,
+! but WITHOUT ANY WARRANTY; without even the implied warranty of
+! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+! GNU General Public License for more details.
+!
+! You should have received a copy of the GNU General Public License
+! along with this program.  If not, see <http://www.gnu.org/licenses/>.
+
+program main
+
+  ! A non-dynamic type.
+  type type1
+     integer(kind=4) :: spacer
+     integer(kind=4) t1_i
+  end type type1
+
+  ! A first dynamic type.  The array is of a static type.
+  type type2
+     integer(kind=4) :: spacer
+     type(type1), allocatable :: t2_array(:)
+  end type type2
+
+  ! Another dynamic type, the array is again a static type.
+  type type3
+     integer(kind=4) :: spacer
+     type(type1), pointer :: t3_array(:)
+  end type type3
+
+  ! A dynamic type, this time the array contains a dynamic type.
+  type type4
+     integer(kind=4) :: spacer
+     type(type2), allocatable :: t4_array(:)
+  end type type4
+
+  ! A static type, the array though contains dynamic types.
+  type type5
+     integer(kind=4) :: spacer
+     type(type2) :: t5_array (4)
+  end type type5
+
+  ! A static type containing pointers to a type that contains a
+  ! dynamic array.
+  type type6
+     type(type2), pointer :: ptr_1
+     type(type2), pointer :: ptr_2
+  end type type6
+
+  real, dimension(:), pointer :: var1
+  real, dimension(:), allocatable :: var2
+  type(type1) :: var3
+  type(type2), target :: var4
+  type(type3) :: var5
+  type(type4) :: var6
+  type(type5) :: var7
+  type(type6) :: var8
+
+  allocate (var1 (3))
+
+  allocate (var2 (4))
+
+  allocate (var4%t2_array(3))
+
+  allocate (var5%t3_array(3))
+
+  allocate (var6%t4_array(3))
+  allocate (var6%t4_array(1)%t2_array(2))
+  allocate (var6%t4_array(2)%t2_array(5))
+  allocate (var6%t4_array(3)%t2_array(4))
+
+  allocate (var7%t5_array(1)%t2_array(2))
+  allocate (var7%t5_array(2)%t2_array(5))
+  allocate (var7%t5_array(3)%t2_array(4))
+  allocate (var7%t5_array(4)%t2_array(1))
+
+  var8%ptr_1 => var4
+  var8%ptr_2 => var4
+
+  print *, var1		! Break Here
+  print *, var2
+  print *, var3
+  print *, var4%t2_array(1)
+  print *, var5%t3_array(2)
+  print *, var6%t4_array(1)%t2_array(1)
+  print *, var7%t5_array(1)%t2_array(1)
+
+end program main

^ permalink raw reply	[flat|nested] 11+ messages in thread

* Re: [PATCH 2/2] gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT
  2021-02-16 18:32     ` Andrew Burgess
@ 2021-02-20  0:00       ` Tom Tromey
  0 siblings, 0 replies; 11+ messages in thread
From: Tom Tromey @ 2021-02-20  0:00 UTC (permalink / raw)
  To: Andrew Burgess; +Cc: Tom Tromey, gdb-patches

>>>>> "Andrew" == Andrew Burgess <andrew.burgess@embecosm.com> writes:

Andrew> Here's an updated version of the patch that removes the code from
Andrew> STRUCTOP_STRUCT, and STRUCTOP_PTR.

Looks good.  Thank you.

Tom

^ permalink raw reply	[flat|nested] 11+ messages in thread

* Re: [PATCH 1/2] gdb: call value_ind for pointers to dynamic types in UNOP_IND evaluation
  2021-01-11 13:20 ` [PATCH 1/2] gdb: call value_ind for pointers to dynamic types in UNOP_IND evaluation Andrew Burgess
  2021-02-11 20:41   ` Tom Tromey
@ 2021-02-24 15:53   ` Andrew Burgess
  1 sibling, 0 replies; 11+ messages in thread
From: Andrew Burgess @ 2021-02-24 15:53 UTC (permalink / raw)
  To: gdb-patches

I have now pushed this patch only from this series.  The last minute
change I made to patch #2 caused a test regression which I'm
investigating.

Thanks,
Andrew

* Andrew Burgess <andrew.burgess@embecosm.com> [2021-01-11 13:20:58 +0000]:

> When evaluating and expression containing UNOP_IND in mode
> EVAL_AVOID_SIDE_EFFECTS, GDB currently (mostly) returns the result of
> a call to value_zero meaning we get back an object with the correct
> type, but its contents are all zero.
> 
> If the target type contains fields with dynamic type then in order to
> resolve these dynamic fields GDB will need to read the value of the
> field from within the parent object.  In this case the field value
> will be zero as a result of the call to value_zero mentioned above.
> 
> The idea behind EVAL_AVOID_SIDE_EFFECTS is to avoid the chance that
> doing something like `ptype` will modify state within the target, for
> example consider: ptype i++.
> 
> However, there is already precedence within GDB that sometimes, in
> order to get accurate type results, we can't avoid reading from the
> target, even when EVAL_AVOID_SIDE_EFFECTS is in effect.  For example I
> would point to eval.c:evaluate_var_value, the handling of OP_REGISTER,
> the handling of value_x_unop in many places.  I believe the Ada
> expression evaluator also ignore EVAL_AVOID_SIDE_EFFECTS in some
> cases.
> 
> I am therefor proposing that, in the case where a pointer points at a
> dynamic type, we allow UNOP_IND to perform the actual indirection.
> This allows accurate types to be displayed in more cases.
> 
> gdb/ChangeLog:
> 
> 	* eval.c (evaluate_subexp_standard): Call value_ind for points to
> 	dynamic types in UNOP_IND.
> 
> gdb/testsuite/ChangeLog:
> 
> 	* gdb.fortran/pointer-to-pointer.exp: Additional tests.
> ---
>  gdb/ChangeLog                                 |  5 +++
>  gdb/eval.c                                    | 36 ++++++++++++-------
>  gdb/testsuite/ChangeLog                       |  4 +++
>  .../gdb.fortran/pointer-to-pointer.exp        | 29 +++++++++------
>  4 files changed, 51 insertions(+), 23 deletions(-)
> 
> diff --git a/gdb/eval.c b/gdb/eval.c
> index e63511b7005..dfe6e403f97 100644
> --- a/gdb/eval.c
> +++ b/gdb/eval.c
> @@ -2422,19 +2422,29 @@ evaluate_subexp_standard (struct type *expect_type,
>        else if (noside == EVAL_AVOID_SIDE_EFFECTS)
>  	{
>  	  type = check_typedef (value_type (arg1));
> -	  if (type->code () == TYPE_CODE_PTR
> -	      || TYPE_IS_REFERENCE (type)
> -	  /* In C you can dereference an array to get the 1st elt.  */
> -	      || type->code () == TYPE_CODE_ARRAY
> -	    )
> -	    return value_zero (TYPE_TARGET_TYPE (type),
> -			       lval_memory);
> -	  else if (type->code () == TYPE_CODE_INT)
> -	    /* GDB allows dereferencing an int.  */
> -	    return value_zero (builtin_type (exp->gdbarch)->builtin_int,
> -			       lval_memory);
> -	  else
> -	    error (_("Attempt to take contents of a non-pointer value."));
> +
> +	  /* If the type pointed to is dynamic then in order to resolve the
> +	     dynamic properties we must actually dereference the pointer.
> +	     There is a risk that this dereference will have side-effects
> +	     in the inferior, but being able to print accurate type
> +	     information seems worth the risk. */
> +	  if ((type->code () != TYPE_CODE_PTR
> +	       && !TYPE_IS_REFERENCE (type))
> +	      || !is_dynamic_type (TYPE_TARGET_TYPE (type)))
> +	    {
> +	      if (type->code () == TYPE_CODE_PTR
> +		  || TYPE_IS_REFERENCE (type)
> +		  /* In C you can dereference an array to get the 1st elt.  */
> +		  || type->code () == TYPE_CODE_ARRAY)
> +		return value_zero (TYPE_TARGET_TYPE (type),
> +				   lval_memory);
> +	      else if (type->code () == TYPE_CODE_INT)
> +		/* GDB allows dereferencing an int.  */
> +		return value_zero (builtin_type (exp->gdbarch)->builtin_int,
> +				   lval_memory);
> +	      else
> +		error (_("Attempt to take contents of a non-pointer value."));
> +	    }
>  	}
>  
>        /* Allow * on an integer so we can cast it to whatever we want.
> diff --git a/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp b/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
> index 27739cc6cf3..306168b2876 100644
> --- a/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
> +++ b/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
> @@ -30,20 +30,29 @@ if ![fortran_runto_main] {
>      return -1
>  }
>  
> -# Depending on the compiler being used, the type names can be printed differently.
> +# Depending on the compiler being used, the type names can be printed
> +# differently.
>  set real4 [fortran_real4]
>  
>  gdb_breakpoint [gdb_get_line_number "Break Here"]
>  gdb_continue_to_breakpoint "Break Here"
>  
> +gdb_test "print buffer" \
> +    " = \\(PTR TO -> \\( Type l_buffer \\)\\) $hex"
> +gdb_test "ptype buffer" \
> +    [multi_line \
> +	 "type = PTR TO -> \\( Type l_buffer" \
> +	 "    $real4 :: alpha\\(:\\)" \
> +	 "End Type l_buffer \\)" ]
> +gdb_test "ptype buffer%alpha" "type = $real4 \\(5\\)"
> +
> +# GDB allows pointer types to be dereferenced using '*'.  This is not
> +# real Fortran syntax, just something extra that GDB supports.
>  gdb_test "print *buffer" \
>      " = \\( alpha = \\(1\\.5, 2\\.5, 3\\.5, 4\\.5, 5\\.5\\) \\)"
> -
> -set l_buffer_type [multi_line \
> -		       "Type l_buffer" \
> -		       "    $real4 :: alpha\\(:\\)" \
> -		       "End Type l_buffer" ]
> -
> -gdb_test "ptype buffer" "type = PTR TO -> \\( ${l_buffer_type} \\)"
> -gdb_test "ptype *buffer" "type = ${l_buffer_type}"
> -gdb_test "ptype buffer%alpha" "type = $real4 \\(5\\)"
> +gdb_test "ptype *buffer" \
> +    [multi_line \
> +	 "type = Type l_buffer" \
> +	 "    $real4 :: alpha\\(5\\)" \
> +	 "End Type l_buffer" ]
> +gdb_test "ptype (*buffer)%alpha" "type = $real4 \\(5\\)"
> -- 
> 2.25.4
> 

^ permalink raw reply	[flat|nested] 11+ messages in thread

end of thread, other threads:[~2021-02-24 15:53 UTC | newest]

Thread overview: 11+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2021-01-11 13:20 [PATCH 0/2] Expression Evaluation Changes For Dynamic Types Andrew Burgess
2021-01-11 13:20 ` [PATCH 1/2] gdb: call value_ind for pointers to dynamic types in UNOP_IND evaluation Andrew Burgess
2021-02-11 20:41   ` Tom Tromey
2021-02-16 18:10     ` Andrew Burgess
2021-02-24 15:53   ` Andrew Burgess
2021-01-11 13:20 ` [PATCH 2/2] gdb: ignore EVAL_AVOID_SIDE_EFFECTS for STRUCTOP_STRUCT Andrew Burgess
2021-02-11 20:43   ` Tom Tromey
2021-02-16 18:32     ` Andrew Burgess
2021-02-20  0:00       ` Tom Tromey
2021-01-28 19:57 ` PING: Re: [PATCH 0/2] Expression Evaluation Changes For Dynamic Types Andrew Burgess
2021-02-11 10:28   ` PINGv2: " Andrew Burgess

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).