public inbox for gdb-patches@sourceware.org
 help / color / mirror / Atom feed
* [PATCH 0/2] Fortran dynamic type related fixes
@ 2020-07-10 15:22 Andrew Burgess
  2020-07-10 15:22 ` [PATCH 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection Andrew Burgess
                   ` (2 more replies)
  0 siblings, 3 replies; 14+ messages in thread
From: Andrew Burgess @ 2020-07-10 15:22 UTC (permalink / raw)
  To: gdb-patches

Couple of fixes for dynamic type related issues.

---

Andrew Burgess (2):
  gdb/fortran: resolve dynamic types when readjusting after an
    indirection
  gdb/fortran: Access elements of a structure with dynamic type

 gdb/ChangeLog                                 | 16 +++++
 gdb/eval.c                                    | 20 ++++++-
 gdb/testsuite/ChangeLog                       | 10 ++++
 .../gdb.fortran/class-allocatable-array.exp   | 59 +++++++++++++++++++
 .../gdb.fortran/class-allocatable-array.f90   | 54 +++++++++++++++++
 gdb/valops.c                                  | 24 ++++----
 gdb/value.c                                   | 23 +++++---
 gdb/value.h                                   |  7 ++-
 8 files changed, 193 insertions(+), 20 deletions(-)
 create mode 100644 gdb/testsuite/gdb.fortran/class-allocatable-array.exp
 create mode 100644 gdb/testsuite/gdb.fortran/class-allocatable-array.f90

-- 
2.25.4


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

* [PATCH 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection
  2020-07-10 15:22 [PATCH 0/2] Fortran dynamic type related fixes Andrew Burgess
@ 2020-07-10 15:22 ` Andrew Burgess
  2020-07-10 15:22 ` [PATCH 2/2] gdb/fortran: Access elements of a structure with dynamic type Andrew Burgess
  2020-07-13 13:33 ` [PATCHv2 0/2] Fortran dynamic type related fixes Andrew Burgess
  2 siblings, 0 replies; 14+ messages in thread
From: Andrew Burgess @ 2020-07-10 15:22 UTC (permalink / raw)
  To: gdb-patches

After dereferencing a pointer (in value_ind) or following a
reference (in coerce_ref) we call readjust_indirect_value_type to
"fixup" the type of the resulting value object.

This fixup handles cases relating to the type of the resulting object
being different (a sub-class) of the original pointers target type.

If we encounter a pointer to a dynamic type then after dereferencing a
pointer (in value_ind) the type of the object created will have had
its dynamic type resolved.  However, in readjust_indirect_value_type,
we use the target type of the original pointer to "fixup" the type of
the resulting value.  In this case, the target type will be a dynamic
type, so the resulting value object, once again has a dynamic type.

This then triggers an assertion later within GDB.

The solution I propose here is that we call resolve_dynamic_type on
the pointer's target type (within readjust_indirect_value_type) so
that the resulting value is not converted back to a dynamic type.

The test case is based on the original test in the bug report.

gdb/ChangeLog:

	PR fortran/26139
	* valops.c (value_ind): Pass address to
	readjust_indirect_value_type.
	* value.c (readjust_indirect_value_type): Make parameter
	non-const, and add extra address parameter.  Resolve original type
	before using it.
	* value.h (readjust_indirect_value_type): Update function
	signature and comment.

gdb/testsuite/ChangeLog:

	PR fortran/26139
	* gdb.fortran/class-allocatable-array.exp: New file.
	* gdb.fortran/class-allocatable-array.f90: New file.
---
 gdb/ChangeLog                                 | 11 ++++
 gdb/testsuite/ChangeLog                       |  6 +++
 .../gdb.fortran/class-allocatable-array.exp   | 43 +++++++++++++++
 .../gdb.fortran/class-allocatable-array.f90   | 54 +++++++++++++++++++
 gdb/valops.c                                  | 24 +++++----
 gdb/value.c                                   | 23 +++++---
 gdb/value.h                                   |  7 ++-
 7 files changed, 149 insertions(+), 19 deletions(-)
 create mode 100644 gdb/testsuite/gdb.fortran/class-allocatable-array.exp
 create mode 100644 gdb/testsuite/gdb.fortran/class-allocatable-array.f90

diff --git a/gdb/testsuite/gdb.fortran/class-allocatable-array.exp b/gdb/testsuite/gdb.fortran/class-allocatable-array.exp
new file mode 100644
index 00000000000..9475ba3b393
--- /dev/null
+++ b/gdb/testsuite/gdb.fortran/class-allocatable-array.exp
@@ -0,0 +1,43 @@
+# Copyright 2020 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 that GDB can print an allocatable array that is a data field
+# within a class like type.
+
+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] {
+    untested "could not run to main"
+    return -1
+}
+
+gdb_breakpoint [gdb_get_line_number "Break Here"]
+gdb_continue_to_breakpoint "Break Here"
+
+# If this first test fails then the Fortran compiler being used uses
+# different names, or maybe a completely different approach, for
+# representing class like structures.  The following tests are
+# cetainly going to fail.
+gdb_test "print this" " = \\( _data = \[^\r\n\]+, _vptr = \[^\r\n\]+\\)"
+gdb_test "print this%_data" " = \\(PTR TO -> \\( Type test_type \\)\\) \[^\r\n\]+"
+gdb_test "print this%_data%b" " = \\(\\( 1, 2, 3\\) \\( 4, 5, 6\\) \\)"
diff --git a/gdb/testsuite/gdb.fortran/class-allocatable-array.f90 b/gdb/testsuite/gdb.fortran/class-allocatable-array.f90
new file mode 100644
index 00000000000..26d5fab0355
--- /dev/null
+++ b/gdb/testsuite/gdb.fortran/class-allocatable-array.f90
@@ -0,0 +1,54 @@
+! Copyright 2020 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/>.
+
+module test_module
+  type test_type
+     integer a
+     real, allocatable :: b (:, :)
+   contains
+     procedure :: test_proc
+  end type test_type
+
+contains
+
+  subroutine test_proc (this)
+    class(test_type), intent (inout) :: this
+    allocate (this%b (3, 2))
+    call fill_array_2d (this%b)
+    print *, ""		! Break Here
+  contains
+    ! Helper subroutine to fill 2-dimensional array with unique
+    ! values.
+    subroutine fill_array_2d (array)
+      real, dimension (:,:) :: array
+      real :: counter
+
+      counter = 1.0
+      do i=LBOUND (array, 2), UBOUND (array, 2), 1
+         do j=LBOUND (array, 1), UBOUND (array, 1), 1
+            array (j,i) = counter
+            counter = counter + 1
+         end do
+      end do
+    end subroutine fill_array_2d
+  end subroutine test_proc
+end module
+
+program test
+  use test_module
+  implicit none
+  type(test_type) :: t
+  call t%test_proc ()
+end program test
diff --git a/gdb/valops.c b/gdb/valops.c
index afdb429dc37..61625977f00 100644
--- a/gdb/valops.c
+++ b/gdb/valops.c
@@ -1559,20 +1559,24 @@ value_ind (struct value *arg1)
       enc_type = check_typedef (value_enclosing_type (arg1));
       enc_type = TYPE_TARGET_TYPE (enc_type);
 
+      CORE_ADDR base_addr;
       if (check_typedef (enc_type)->code () == TYPE_CODE_FUNC
 	  || check_typedef (enc_type)->code () == TYPE_CODE_METHOD)
-	/* For functions, go through find_function_addr, which knows
-	   how to handle function descriptors.  */
-	arg2 = value_at_lazy (enc_type, 
-			      find_function_addr (arg1, NULL));
+	{
+	  /* For functions, go through find_function_addr, which knows
+	     how to handle function descriptors.  */
+	  base_addr = find_function_addr (arg1, NULL);
+	}
       else
-	/* Retrieve the enclosing object pointed to.  */
-	arg2 = value_at_lazy (enc_type, 
-			      (value_as_address (arg1)
-			       - value_pointed_to_offset (arg1)));
-
+	{
+	  /* Retrieve the enclosing object pointed to.  */
+	  base_addr = (value_as_address (arg1)
+		       - value_pointed_to_offset (arg1));
+	}
+      arg2 = value_at_lazy (enc_type, base_addr);
       enc_type = value_type (arg2);
-      return readjust_indirect_value_type (arg2, enc_type, base_type, arg1);
+      return readjust_indirect_value_type (arg2, enc_type, base_type,
+					   arg1, base_addr);
     }
 
   error (_("Attempt to take contents of a non-pointer value."));
diff --git a/gdb/value.c b/gdb/value.c
index 97a099ddbd3..826cd35b43f 100644
--- a/gdb/value.c
+++ b/gdb/value.c
@@ -3618,10 +3618,20 @@ coerce_ref_if_computed (const struct value *arg)
 struct value *
 readjust_indirect_value_type (struct value *value, struct type *enc_type,
 			      const struct type *original_type,
-			      const struct value *original_value)
+			      struct value *original_value,
+			      CORE_ADDR original_value_address)
 {
+  gdb_assert (original_type->code () == TYPE_CODE_PTR
+	      || TYPE_IS_REFERENCE (original_type));
+
+  struct type *original_target_type = TYPE_TARGET_TYPE (original_type);
+  gdb::array_view<const gdb_byte> view;
+  struct type *resolved_original_target_type
+    = resolve_dynamic_type (original_target_type, view,
+			    original_value_address);
+
   /* Re-adjust type.  */
-  deprecated_set_value_type (value, TYPE_TARGET_TYPE (original_type));
+  deprecated_set_value_type (value, resolved_original_target_type);
 
   /* Add embedding info.  */
   set_value_enclosing_type (value, enc_type);
@@ -3648,12 +3658,11 @@ coerce_ref (struct value *arg)
   enc_type = check_typedef (value_enclosing_type (arg));
   enc_type = TYPE_TARGET_TYPE (enc_type);
 
-  retval = value_at_lazy (enc_type,
-                          unpack_pointer (value_type (arg),
-                                          value_contents (arg)));
+  CORE_ADDR addr = unpack_pointer (value_type (arg), value_contents (arg));
+  retval = value_at_lazy (enc_type, addr);
   enc_type = value_type (retval);
-  return readjust_indirect_value_type (retval, enc_type,
-                                       value_type_arg_tmp, arg);
+  return readjust_indirect_value_type (retval, enc_type, value_type_arg_tmp,
+				       arg, addr);
 }
 
 struct value *
diff --git a/gdb/value.h b/gdb/value.h
index 70c3d5667ae..12e4a13e3e4 100644
--- a/gdb/value.h
+++ b/gdb/value.h
@@ -488,7 +488,9 @@ extern struct value *coerce_ref_if_computed (const struct value *arg);
 
 /* Setup a new value type and enclosing value type for dereferenced value VALUE.
    ENC_TYPE is the new enclosing type that should be set.  ORIGINAL_TYPE and
-   ORIGINAL_VAL are the type and value of the original reference or pointer.
+   ORIGINAL_VAL are the type and value of the original reference or
+   pointer.  ORIGINAL_VALUE_ADDRESS is the address within VALUE, that is
+   the address that was dereferenced.
 
    Note, that VALUE is modified by this function.
 
@@ -497,7 +499,8 @@ extern struct value *coerce_ref_if_computed (const struct value *arg);
 extern struct value * readjust_indirect_value_type (struct value *value,
 						    struct type *enc_type,
 						    const struct type *original_type,
-						    const struct value *original_val);
+						    struct value *original_val,
+						    CORE_ADDR original_value_address);
 
 /* Convert a REF to the object referenced.  */
 
-- 
2.25.4


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

* [PATCH 2/2] gdb/fortran: Access elements of a structure with dynamic type
  2020-07-10 15:22 [PATCH 0/2] Fortran dynamic type related fixes Andrew Burgess
  2020-07-10 15:22 ` [PATCH 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection Andrew Burgess
@ 2020-07-10 15:22 ` Andrew Burgess
  2020-07-13 13:33 ` [PATCHv2 0/2] Fortran dynamic type related fixes Andrew Burgess
  2 siblings, 0 replies; 14+ messages in thread
From: Andrew Burgess @ 2020-07-10 15:22 UTC (permalink / raw)
  To: gdb-patches

After the previous commit I noticed this behaviour:

  (gdb) ptype this
  type = Type __class_test_module_Test_type_t
      PTR TO -> ( Type test_type :: _data )
      PTR TO -> ( Type __vtype_test_module_Test_type :: _vptr )
  End Type __class_test_module_Test_type_t
  (gdb) ptype this%_data
  type = PTR TO -> ( Type test_type
      integer(kind=4) :: a
      real(kind=4), allocatable :: b(:,:)
  End Type test_type )
  (gdb) ptype this%_data%b
  Cannot access memory at address 0x50
  (gdb)

When we ask GDB for the type of field `b`, which has dynamic type,
then GDB is unable to correctly resolve the dynamic type, and ends up
trying to access target memory at address 0x50.

When GDB sees 'this%_data%b' the expression tree looks like this:

  Dump of expression @ 0x500d380, after conversion to prefix form:
  Expression: `test_module::test_proc::this._data.b'
  	Language fortran, 14 elements, 16 bytes each.

  	    0  STRUCTOP_STRUCT       Element name: `b'
  	    5    STRUCTOP_STRUCT       Element name: `_data'
  	   10      OP_VAR_VALUE          Block @0x498cca0, symbol @0x498cc20 (this)

GDB will first get a value for `this`, from which it extracts a value
for the element `_data`, and finally GDB dereferences the pointer
`_data` and extracts the element `b`.

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 `_data` 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.

The solution I present here is to spot the case where:
  (a) we're in EVAL_AVOID_SIDE_EFFECTS mode, and
  (b) the structure element has dynamic type
In this case we fetch the parent object in EVAL_NORMAL mode.  This
means that it will have its actual contents, fetched from the actual
target, rather than the dummy 0 value.  With this done we are able to
correctly evaluate the dynamic type and the above test case now
finishes like this:

  (gdb) ptype this%_data%b
  type = real(kind=4), allocatable (3,2)

You might notice that STRUCTOP_PTR is very similar to STRUCTOP_STRUCT,
but that I have not updated the former.  The reason for this is that
Fortran doesn't make use of STRUCTOP_PTR, so I'm not sure how I would
test any changes to STRUCTOP_PTR.

gdb/ChangeLog:

	* eval.c (evaluate_subexp_standard): Call evaluate_subexp with
	EVAL_NORMAL if we are accessing an element with a dynamic type.

gdb/testsuite/ChangeLog:

	* gdb.fortran/class-allocatable-array.exp: Add more tests.
---
 gdb/ChangeLog                                 |  5 +++++
 gdb/eval.c                                    | 20 ++++++++++++++++++-
 gdb/testsuite/ChangeLog                       |  4 ++++
 .../gdb.fortran/class-allocatable-array.exp   | 16 +++++++++++++++
 4 files changed, 44 insertions(+), 1 deletion(-)

diff --git a/gdb/eval.c b/gdb/eval.c
index f9750816216..9f716ce0624 100644
--- a/gdb/eval.c
+++ b/gdb/eval.c
@@ -2031,12 +2031,30 @@ evaluate_subexp_standard (struct type *expect_type,
     case STRUCTOP_STRUCT:
       tem = longest_to_int (exp->elts[pc + 1].longconst);
       (*pos) += 3 + BYTES_TO_EXP_ELEM (tem + 1);
+      oldpos = *pos;
       arg1 = evaluate_subexp (NULL_TYPE, exp, pos, noside);
       if (noside == EVAL_SKIP)
 	return eval_skip_value (exp);
+      if (noside == EVAL_AVOID_SIDE_EFFECTS)
+	{
+	  /* If the element of the structure has a dynamic type then we
+	     need to get the real value representing the containing
+	     structure so that we can correctly evaluate the type of the
+	     element.  If we're not already avoiding side effects then we
+	     already have the real value of the containing structure, so
+	     this is not needed.  */
+	  type = lookup_struct_elt_type (value_type (arg1),
+					 &exp->elts[pc + 2].string, 1);
+	  if (type != nullptr && is_dynamic_type (type))
+	    {
+	      *pos = oldpos;
+	      arg1 = evaluate_subexp (NULL_TYPE, exp, pos, EVAL_NORMAL);
+	    }
+	}
       arg3 = value_struct_elt (&arg1, NULL, &exp->elts[pc + 2].string,
 			       NULL, "structure");
-      if (noside == EVAL_AVOID_SIDE_EFFECTS)
+      if (noside == EVAL_AVOID_SIDE_EFFECTS
+	  && !is_dynamic_type (check_typedef (value_type (arg3))))
 	arg3 = value_zero (value_type (arg3), VALUE_LVAL (arg3));
       return arg3;
 
diff --git a/gdb/testsuite/gdb.fortran/class-allocatable-array.exp b/gdb/testsuite/gdb.fortran/class-allocatable-array.exp
index 9475ba3b393..355fb0ce9cd 100644
--- a/gdb/testsuite/gdb.fortran/class-allocatable-array.exp
+++ b/gdb/testsuite/gdb.fortran/class-allocatable-array.exp
@@ -41,3 +41,19 @@ gdb_continue_to_breakpoint "Break Here"
 gdb_test "print this" " = \\( _data = \[^\r\n\]+, _vptr = \[^\r\n\]+\\)"
 gdb_test "print this%_data" " = \\(PTR TO -> \\( Type test_type \\)\\) \[^\r\n\]+"
 gdb_test "print this%_data%b" " = \\(\\( 1, 2, 3\\) \\( 4, 5, 6\\) \\)"
+
+set integer4 [fortran_int4]
+set real4 [fortran_real4]
+
+# Check we can correctly access the types of these same objects.
+gdb_test "ptype this" [multi_line \
+			   "type = Type \[^\r\n\]+" \
+			   "    PTR TO -> \\( Type test_type :: _data \\)" \
+			   "    PTR TO -> \\( Type \[^\r\n\]+ :: _vptr \\)" \
+			   "End Type \[^\r\n\]+" ]
+gdb_test "ptype this%_data" [multi_line \
+				 "type = PTR TO -> \\( Type test_type" \
+				 "    ${integer4} :: a" \
+				 "    ${real4}, allocatable :: b\\(:,:\\)" \
+				 "End Type test_type \\)" ]
+gdb_test "ptype this%_data%b" "type = ${real4}, allocatable \\(3,2\\)"
-- 
2.25.4


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

* [PATCHv2 0/2] Fortran dynamic type related fixes
  2020-07-10 15:22 [PATCH 0/2] Fortran dynamic type related fixes Andrew Burgess
  2020-07-10 15:22 ` [PATCH 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection Andrew Burgess
  2020-07-10 15:22 ` [PATCH 2/2] gdb/fortran: Access elements of a structure with dynamic type Andrew Burgess
@ 2020-07-13 13:33 ` Andrew Burgess
  2020-07-13 13:33   ` [PATCHv2 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection Andrew Burgess
  2020-07-13 13:33   ` [PATCHv2 2/2] gdb/fortran: Access elements of a structure with dynamic type Andrew Burgess
  2 siblings, 2 replies; 14+ messages in thread
From: Andrew Burgess @ 2020-07-13 13:33 UTC (permalink / raw)
  To: gdb-patches

Since the v1 patch set I noticed that this series fixes another open
Fortran bug.  The only changes in this series are an extra test, and
updates in the ChangeLog.

---

Andrew Burgess (2):
  gdb/fortran: resolve dynamic types when readjusting after an
    indirection
  gdb/fortran: Access elements of a structure with dynamic type

 gdb/ChangeLog                                 | 17 ++++++
 gdb/eval.c                                    | 20 ++++++-
 gdb/testsuite/ChangeLog                       | 14 +++++
 .../gdb.fortran/class-allocatable-array.exp   | 59 +++++++++++++++++++
 .../gdb.fortran/class-allocatable-array.f90   | 54 +++++++++++++++++
 .../gdb.fortran/pointer-to-pointer.exp        | 47 +++++++++++++++
 .../gdb.fortran/pointer-to-pointer.f90        | 34 +++++++++++
 gdb/valops.c                                  | 24 ++++----
 gdb/value.c                                   | 23 +++++---
 gdb/value.h                                   |  7 ++-
 10 files changed, 279 insertions(+), 20 deletions(-)
 create mode 100644 gdb/testsuite/gdb.fortran/class-allocatable-array.exp
 create mode 100644 gdb/testsuite/gdb.fortran/class-allocatable-array.f90
 create mode 100644 gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
 create mode 100644 gdb/testsuite/gdb.fortran/pointer-to-pointer.f90

-- 
2.25.4


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

* [PATCHv2 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection
  2020-07-13 13:33 ` [PATCHv2 0/2] Fortran dynamic type related fixes Andrew Burgess
@ 2020-07-13 13:33   ` Andrew Burgess
  2020-07-22 19:10     ` Tom Tromey
  2020-07-13 13:33   ` [PATCHv2 2/2] gdb/fortran: Access elements of a structure with dynamic type Andrew Burgess
  1 sibling, 1 reply; 14+ messages in thread
From: Andrew Burgess @ 2020-07-13 13:33 UTC (permalink / raw)
  To: gdb-patches

After dereferencing a pointer (in value_ind) or following a
reference (in coerce_ref) we call readjust_indirect_value_type to
"fixup" the type of the resulting value object.

This fixup handles cases relating to the type of the resulting object
being different (a sub-class) of the original pointers target type.

If we encounter a pointer to a dynamic type then after dereferencing a
pointer (in value_ind) the type of the object created will have had
its dynamic type resolved.  However, in readjust_indirect_value_type,
we use the target type of the original pointer to "fixup" the type of
the resulting value.  In this case, the target type will be a dynamic
type, so the resulting value object, once again has a dynamic type.

This then triggers an assertion later within GDB.

The solution I propose here is that we call resolve_dynamic_type on
the pointer's target type (within readjust_indirect_value_type) so
that the resulting value is not converted back to a dynamic type.

The test case is based on the original test in the bug report.

gdb/ChangeLog:

	PR fortran/23051
	PR fortran/26139
	* valops.c (value_ind): Pass address to
	readjust_indirect_value_type.
	* value.c (readjust_indirect_value_type): Make parameter
	non-const, and add extra address parameter.  Resolve original type
	before using it.
	* value.h (readjust_indirect_value_type): Update function
	signature and comment.

gdb/testsuite/ChangeLog:

	PR fortran/23051
	PR fortran/26139
	* gdb.fortran/class-allocatable-array.exp: New file.
	* gdb.fortran/class-allocatable-array.f90: New file.
	* gdb.fortran/pointer-to-pointer.exp: New file.
	* gdb.fortran/pointer-to-pointer.f90: New file.
---
 gdb/ChangeLog                                 | 12 +++++
 gdb/testsuite/ChangeLog                       |  9 ++++
 .../gdb.fortran/class-allocatable-array.exp   | 43 +++++++++++++++
 .../gdb.fortran/class-allocatable-array.f90   | 54 +++++++++++++++++++
 .../gdb.fortran/pointer-to-pointer.exp        | 46 ++++++++++++++++
 .../gdb.fortran/pointer-to-pointer.f90        | 34 ++++++++++++
 gdb/valops.c                                  | 24 +++++----
 gdb/value.c                                   | 23 +++++---
 gdb/value.h                                   |  7 ++-
 9 files changed, 233 insertions(+), 19 deletions(-)
 create mode 100644 gdb/testsuite/gdb.fortran/class-allocatable-array.exp
 create mode 100644 gdb/testsuite/gdb.fortran/class-allocatable-array.f90
 create mode 100644 gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
 create mode 100644 gdb/testsuite/gdb.fortran/pointer-to-pointer.f90

diff --git a/gdb/testsuite/gdb.fortran/class-allocatable-array.exp b/gdb/testsuite/gdb.fortran/class-allocatable-array.exp
new file mode 100644
index 00000000000..9475ba3b393
--- /dev/null
+++ b/gdb/testsuite/gdb.fortran/class-allocatable-array.exp
@@ -0,0 +1,43 @@
+# Copyright 2020 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 that GDB can print an allocatable array that is a data field
+# within a class like type.
+
+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] {
+    untested "could not run to main"
+    return -1
+}
+
+gdb_breakpoint [gdb_get_line_number "Break Here"]
+gdb_continue_to_breakpoint "Break Here"
+
+# If this first test fails then the Fortran compiler being used uses
+# different names, or maybe a completely different approach, for
+# representing class like structures.  The following tests are
+# cetainly going to fail.
+gdb_test "print this" " = \\( _data = \[^\r\n\]+, _vptr = \[^\r\n\]+\\)"
+gdb_test "print this%_data" " = \\(PTR TO -> \\( Type test_type \\)\\) \[^\r\n\]+"
+gdb_test "print this%_data%b" " = \\(\\( 1, 2, 3\\) \\( 4, 5, 6\\) \\)"
diff --git a/gdb/testsuite/gdb.fortran/class-allocatable-array.f90 b/gdb/testsuite/gdb.fortran/class-allocatable-array.f90
new file mode 100644
index 00000000000..26d5fab0355
--- /dev/null
+++ b/gdb/testsuite/gdb.fortran/class-allocatable-array.f90
@@ -0,0 +1,54 @@
+! Copyright 2020 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/>.
+
+module test_module
+  type test_type
+     integer a
+     real, allocatable :: b (:, :)
+   contains
+     procedure :: test_proc
+  end type test_type
+
+contains
+
+  subroutine test_proc (this)
+    class(test_type), intent (inout) :: this
+    allocate (this%b (3, 2))
+    call fill_array_2d (this%b)
+    print *, ""		! Break Here
+  contains
+    ! Helper subroutine to fill 2-dimensional array with unique
+    ! values.
+    subroutine fill_array_2d (array)
+      real, dimension (:,:) :: array
+      real :: counter
+
+      counter = 1.0
+      do i=LBOUND (array, 2), UBOUND (array, 2), 1
+         do j=LBOUND (array, 1), UBOUND (array, 1), 1
+            array (j,i) = counter
+            counter = counter + 1
+         end do
+      end do
+    end subroutine fill_array_2d
+  end subroutine test_proc
+end module
+
+program test
+  use test_module
+  implicit none
+  type(test_type) :: t
+  call t%test_proc ()
+end program test
diff --git a/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp b/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
new file mode 100644
index 00000000000..7129e431ed1
--- /dev/null
+++ b/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
@@ -0,0 +1,46 @@
+# Copyright 2020 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 for GDB printing a pointer to a type containing a buffer.
+
+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] {
+    untested "could not run to main"
+    return -1
+}
+
+gdb_breakpoint [gdb_get_line_number "Break Here"]
+gdb_continue_to_breakpoint "Break Here"
+
+gdb_test "print *buffer" \
+    " = \\( alpha = \\(1\\.5, 2\\.5, 3\\.5, 4\\.5, 5\\.5\\) \\)"
+
+set l_buffer_type [multi_line \
+		       "Type l_buffer" \
+		       "    real\\(kind=4\\) :: 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 = real\\(kind=4\\) \\(5\\)"
diff --git a/gdb/testsuite/gdb.fortran/pointer-to-pointer.f90 b/gdb/testsuite/gdb.fortran/pointer-to-pointer.f90
new file mode 100644
index 00000000000..353217963a8
--- /dev/null
+++ b/gdb/testsuite/gdb.fortran/pointer-to-pointer.f90
@@ -0,0 +1,34 @@
+! Copyright 2020 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 allocate_array
+
+  type l_buffer
+     real, dimension(:), pointer :: alpha
+  end type l_buffer
+  type(l_buffer), pointer :: buffer
+
+  allocate (buffer)
+  allocate (buffer%alpha (5))
+
+  buffer%alpha (1) = 1.5
+  buffer%alpha (2) = 2.5
+  buffer%alpha (3) = 3.5
+  buffer%alpha (4) = 4.5
+  buffer%alpha (5) = 5.5
+
+  print *, buffer%alpha	! Break Here.
+
+end program allocate_array
diff --git a/gdb/valops.c b/gdb/valops.c
index afdb429dc37..61625977f00 100644
--- a/gdb/valops.c
+++ b/gdb/valops.c
@@ -1559,20 +1559,24 @@ value_ind (struct value *arg1)
       enc_type = check_typedef (value_enclosing_type (arg1));
       enc_type = TYPE_TARGET_TYPE (enc_type);
 
+      CORE_ADDR base_addr;
       if (check_typedef (enc_type)->code () == TYPE_CODE_FUNC
 	  || check_typedef (enc_type)->code () == TYPE_CODE_METHOD)
-	/* For functions, go through find_function_addr, which knows
-	   how to handle function descriptors.  */
-	arg2 = value_at_lazy (enc_type, 
-			      find_function_addr (arg1, NULL));
+	{
+	  /* For functions, go through find_function_addr, which knows
+	     how to handle function descriptors.  */
+	  base_addr = find_function_addr (arg1, NULL);
+	}
       else
-	/* Retrieve the enclosing object pointed to.  */
-	arg2 = value_at_lazy (enc_type, 
-			      (value_as_address (arg1)
-			       - value_pointed_to_offset (arg1)));
-
+	{
+	  /* Retrieve the enclosing object pointed to.  */
+	  base_addr = (value_as_address (arg1)
+		       - value_pointed_to_offset (arg1));
+	}
+      arg2 = value_at_lazy (enc_type, base_addr);
       enc_type = value_type (arg2);
-      return readjust_indirect_value_type (arg2, enc_type, base_type, arg1);
+      return readjust_indirect_value_type (arg2, enc_type, base_type,
+					   arg1, base_addr);
     }
 
   error (_("Attempt to take contents of a non-pointer value."));
diff --git a/gdb/value.c b/gdb/value.c
index 97a099ddbd3..826cd35b43f 100644
--- a/gdb/value.c
+++ b/gdb/value.c
@@ -3618,10 +3618,20 @@ coerce_ref_if_computed (const struct value *arg)
 struct value *
 readjust_indirect_value_type (struct value *value, struct type *enc_type,
 			      const struct type *original_type,
-			      const struct value *original_value)
+			      struct value *original_value,
+			      CORE_ADDR original_value_address)
 {
+  gdb_assert (original_type->code () == TYPE_CODE_PTR
+	      || TYPE_IS_REFERENCE (original_type));
+
+  struct type *original_target_type = TYPE_TARGET_TYPE (original_type);
+  gdb::array_view<const gdb_byte> view;
+  struct type *resolved_original_target_type
+    = resolve_dynamic_type (original_target_type, view,
+			    original_value_address);
+
   /* Re-adjust type.  */
-  deprecated_set_value_type (value, TYPE_TARGET_TYPE (original_type));
+  deprecated_set_value_type (value, resolved_original_target_type);
 
   /* Add embedding info.  */
   set_value_enclosing_type (value, enc_type);
@@ -3648,12 +3658,11 @@ coerce_ref (struct value *arg)
   enc_type = check_typedef (value_enclosing_type (arg));
   enc_type = TYPE_TARGET_TYPE (enc_type);
 
-  retval = value_at_lazy (enc_type,
-                          unpack_pointer (value_type (arg),
-                                          value_contents (arg)));
+  CORE_ADDR addr = unpack_pointer (value_type (arg), value_contents (arg));
+  retval = value_at_lazy (enc_type, addr);
   enc_type = value_type (retval);
-  return readjust_indirect_value_type (retval, enc_type,
-                                       value_type_arg_tmp, arg);
+  return readjust_indirect_value_type (retval, enc_type, value_type_arg_tmp,
+				       arg, addr);
 }
 
 struct value *
diff --git a/gdb/value.h b/gdb/value.h
index 70c3d5667ae..12e4a13e3e4 100644
--- a/gdb/value.h
+++ b/gdb/value.h
@@ -488,7 +488,9 @@ extern struct value *coerce_ref_if_computed (const struct value *arg);
 
 /* Setup a new value type and enclosing value type for dereferenced value VALUE.
    ENC_TYPE is the new enclosing type that should be set.  ORIGINAL_TYPE and
-   ORIGINAL_VAL are the type and value of the original reference or pointer.
+   ORIGINAL_VAL are the type and value of the original reference or
+   pointer.  ORIGINAL_VALUE_ADDRESS is the address within VALUE, that is
+   the address that was dereferenced.
 
    Note, that VALUE is modified by this function.
 
@@ -497,7 +499,8 @@ extern struct value *coerce_ref_if_computed (const struct value *arg);
 extern struct value * readjust_indirect_value_type (struct value *value,
 						    struct type *enc_type,
 						    const struct type *original_type,
-						    const struct value *original_val);
+						    struct value *original_val,
+						    CORE_ADDR original_value_address);
 
 /* Convert a REF to the object referenced.  */
 
-- 
2.25.4


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

* [PATCHv2 2/2] gdb/fortran: Access elements of a structure with dynamic type
  2020-07-13 13:33 ` [PATCHv2 0/2] Fortran dynamic type related fixes Andrew Burgess
  2020-07-13 13:33   ` [PATCHv2 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection Andrew Burgess
@ 2020-07-13 13:33   ` Andrew Burgess
  2020-07-22 19:19     ` Tom Tromey
  1 sibling, 1 reply; 14+ messages in thread
From: Andrew Burgess @ 2020-07-13 13:33 UTC (permalink / raw)
  To: gdb-patches

After the previous commit I noticed this behaviour:

  (gdb) ptype this
  type = Type __class_test_module_Test_type_t
      PTR TO -> ( Type test_type :: _data )
      PTR TO -> ( Type __vtype_test_module_Test_type :: _vptr )
  End Type __class_test_module_Test_type_t
  (gdb) ptype this%_data
  type = PTR TO -> ( Type test_type
      integer(kind=4) :: a
      real(kind=4), allocatable :: b(:,:)
  End Type test_type )
  (gdb) ptype this%_data%b
  Cannot access memory at address 0x50
  (gdb)

When we ask GDB for the type of field `b`, which has dynamic type,
then GDB is unable to correctly resolve the dynamic type, and ends up
trying to access target memory at address 0x50.

When GDB sees 'this%_data%b' the expression tree looks like this:

  Dump of expression @ 0x500d380, after conversion to prefix form:
  Expression: `test_module::test_proc::this._data.b'
  	Language fortran, 14 elements, 16 bytes each.

  	    0  STRUCTOP_STRUCT       Element name: `b'
  	    5    STRUCTOP_STRUCT       Element name: `_data'
  	   10      OP_VAR_VALUE          Block @0x498cca0, symbol @0x498cc20 (this)

GDB will first get a value for `this`, from which it extracts a value
for the element `_data`, and finally GDB dereferences the pointer
`_data` and extracts the element `b`.

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 `_data` 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.

The solution I present here is to spot the case where:
  (a) we're in EVAL_AVOID_SIDE_EFFECTS mode, and
  (b) the structure element has dynamic type
In this case we fetch the parent object in EVAL_NORMAL mode.  This
means that it will have its actual contents, fetched from the actual
target, rather than the dummy 0 value.  With this done we are able to
correctly evaluate the dynamic type and the above test case now
finishes like this:

  (gdb) ptype this%_data%b
  type = real(kind=4), allocatable (3,2)

You might notice that STRUCTOP_PTR is very similar to STRUCTOP_STRUCT,
but that I have not updated the former.  The reason for this is that
Fortran doesn't make use of STRUCTOP_PTR, so I'm not sure how I would
test any changes to STRUCTOP_PTR.

gdb/ChangeLog:

	* eval.c (evaluate_subexp_standard): Call evaluate_subexp with
	EVAL_NORMAL if we are accessing an element with a dynamic type.

gdb/testsuite/ChangeLog:

	* gdb.fortran/class-allocatable-array.exp: Add more tests.
	* gdb.fortran/pointer-to-pointer.exp: Add more tests.
---
 gdb/ChangeLog                                 |  5 +++++
 gdb/eval.c                                    | 20 ++++++++++++++++++-
 gdb/testsuite/ChangeLog                       |  5 +++++
 .../gdb.fortran/class-allocatable-array.exp   | 16 +++++++++++++++
 .../gdb.fortran/pointer-to-pointer.exp        |  1 +
 5 files changed, 46 insertions(+), 1 deletion(-)

diff --git a/gdb/eval.c b/gdb/eval.c
index f9750816216..9f716ce0624 100644
--- a/gdb/eval.c
+++ b/gdb/eval.c
@@ -2031,12 +2031,30 @@ evaluate_subexp_standard (struct type *expect_type,
     case STRUCTOP_STRUCT:
       tem = longest_to_int (exp->elts[pc + 1].longconst);
       (*pos) += 3 + BYTES_TO_EXP_ELEM (tem + 1);
+      oldpos = *pos;
       arg1 = evaluate_subexp (NULL_TYPE, exp, pos, noside);
       if (noside == EVAL_SKIP)
 	return eval_skip_value (exp);
+      if (noside == EVAL_AVOID_SIDE_EFFECTS)
+	{
+	  /* If the element of the structure has a dynamic type then we
+	     need to get the real value representing the containing
+	     structure so that we can correctly evaluate the type of the
+	     element.  If we're not already avoiding side effects then we
+	     already have the real value of the containing structure, so
+	     this is not needed.  */
+	  type = lookup_struct_elt_type (value_type (arg1),
+					 &exp->elts[pc + 2].string, 1);
+	  if (type != nullptr && is_dynamic_type (type))
+	    {
+	      *pos = oldpos;
+	      arg1 = evaluate_subexp (NULL_TYPE, exp, pos, EVAL_NORMAL);
+	    }
+	}
       arg3 = value_struct_elt (&arg1, NULL, &exp->elts[pc + 2].string,
 			       NULL, "structure");
-      if (noside == EVAL_AVOID_SIDE_EFFECTS)
+      if (noside == EVAL_AVOID_SIDE_EFFECTS
+	  && !is_dynamic_type (check_typedef (value_type (arg3))))
 	arg3 = value_zero (value_type (arg3), VALUE_LVAL (arg3));
       return arg3;
 
diff --git a/gdb/testsuite/gdb.fortran/class-allocatable-array.exp b/gdb/testsuite/gdb.fortran/class-allocatable-array.exp
index 9475ba3b393..355fb0ce9cd 100644
--- a/gdb/testsuite/gdb.fortran/class-allocatable-array.exp
+++ b/gdb/testsuite/gdb.fortran/class-allocatable-array.exp
@@ -41,3 +41,19 @@ gdb_continue_to_breakpoint "Break Here"
 gdb_test "print this" " = \\( _data = \[^\r\n\]+, _vptr = \[^\r\n\]+\\)"
 gdb_test "print this%_data" " = \\(PTR TO -> \\( Type test_type \\)\\) \[^\r\n\]+"
 gdb_test "print this%_data%b" " = \\(\\( 1, 2, 3\\) \\( 4, 5, 6\\) \\)"
+
+set integer4 [fortran_int4]
+set real4 [fortran_real4]
+
+# Check we can correctly access the types of these same objects.
+gdb_test "ptype this" [multi_line \
+			   "type = Type \[^\r\n\]+" \
+			   "    PTR TO -> \\( Type test_type :: _data \\)" \
+			   "    PTR TO -> \\( Type \[^\r\n\]+ :: _vptr \\)" \
+			   "End Type \[^\r\n\]+" ]
+gdb_test "ptype this%_data" [multi_line \
+				 "type = PTR TO -> \\( Type test_type" \
+				 "    ${integer4} :: a" \
+				 "    ${real4}, allocatable :: b\\(:,:\\)" \
+				 "End Type test_type \\)" ]
+gdb_test "ptype this%_data%b" "type = ${real4}, allocatable \\(3,2\\)"
diff --git a/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp b/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
index 7129e431ed1..51fb36c683f 100644
--- a/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
+++ b/gdb/testsuite/gdb.fortran/pointer-to-pointer.exp
@@ -44,3 +44,4 @@ set l_buffer_type [multi_line \
 gdb_test "ptype buffer" "type = PTR TO -> \\( ${l_buffer_type} \\)"
 gdb_test "ptype *buffer" "type = ${l_buffer_type}"
 gdb_test "ptype buffer%alpha" "type = real\\(kind=4\\) \\(5\\)"
+gdb_test "ptype (*buffer)%alpha" "type = real\\(kind=4\\) \\(5\\)"
-- 
2.25.4


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

* Re: [PATCHv2 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection
  2020-07-13 13:33   ` [PATCHv2 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection Andrew Burgess
@ 2020-07-22 19:10     ` Tom Tromey
  2020-07-25  0:31       ` Andrew Burgess
  0 siblings, 1 reply; 14+ messages in thread
From: Tom Tromey @ 2020-07-22 19:10 UTC (permalink / raw)
  To: Andrew Burgess; +Cc: gdb-patches

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

Andrew> gdb/ChangeLog:

Andrew> 	PR fortran/23051
Andrew> 	PR fortran/26139
Andrew> 	* valops.c (value_ind): Pass address to
Andrew> 	readjust_indirect_value_type.
Andrew> 	* value.c (readjust_indirect_value_type): Make parameter
Andrew> 	non-const, and add extra address parameter.  Resolve original type
Andrew> 	before using it.
Andrew> 	* value.h (readjust_indirect_value_type): Update function
Andrew> 	signature and comment.

Thanks.  I think this is ok.

Tom

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

* Re: [PATCHv2 2/2] gdb/fortran: Access elements of a structure with dynamic type
  2020-07-13 13:33   ` [PATCHv2 2/2] gdb/fortran: Access elements of a structure with dynamic type Andrew Burgess
@ 2020-07-22 19:19     ` Tom Tromey
  2020-07-23 10:28       ` Andrew Burgess
  0 siblings, 1 reply; 14+ messages in thread
From: Tom Tromey @ 2020-07-22 19:19 UTC (permalink / raw)
  To: Andrew Burgess; +Cc: gdb-patches

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

Andrew>      case STRUCTOP_STRUCT:
Andrew>        tem = longest_to_int (exp->elts[pc + 1].longconst);
Andrew>        (*pos) += 3 + BYTES_TO_EXP_ELEM (tem + 1);
Andrew> +      oldpos = *pos;
Andrew>        arg1 = evaluate_subexp (NULL_TYPE, exp, pos, noside);
Andrew>        if (noside == EVAL_SKIP)
Andrew>  	return eval_skip_value (exp);
Andrew> +      if (noside == EVAL_AVOID_SIDE_EFFECTS)
Andrew> +	{
Andrew> +	  /* If the element of the structure has a dynamic type then we
Andrew> +	     need to get the real value representing the containing
Andrew> +	     structure so that we can correctly evaluate the type of the
Andrew> +	     element.  If we're not already avoiding side effects then we
Andrew> +	     already have the real value of the containing structure, so
Andrew> +	     this is not needed.  */
Andrew> +	  type = lookup_struct_elt_type (value_type (arg1),
Andrew> +					 &exp->elts[pc + 2].string, 1);
Andrew> +	  if (type != nullptr && is_dynamic_type (type))
Andrew> +	    {
Andrew> +	      *pos = oldpos;
Andrew> +	      arg1 = evaluate_subexp (NULL_TYPE, exp, pos, EVAL_NORMAL);

Re-evaluating a subexpression like this can lead to problems; see for
example commit 6830f270e ("Avoid exponential behavior in rust_evaluate_subexp").

I don't know if there's another way to do this, though.

Tom

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

* Re: [PATCHv2 2/2] gdb/fortran: Access elements of a structure with dynamic type
  2020-07-22 19:19     ` Tom Tromey
@ 2020-07-23 10:28       ` Andrew Burgess
  2020-07-24 20:03         ` Tom Tromey
  0 siblings, 1 reply; 14+ messages in thread
From: Andrew Burgess @ 2020-07-23 10:28 UTC (permalink / raw)
  To: Tom Tromey; +Cc: gdb-patches

* Tom Tromey <tom@tromey.com> [2020-07-22 13:19:12 -0600]:

> >>>>> "Andrew" == Andrew Burgess <andrew.burgess@embecosm.com> writes:
> 
> Andrew>      case STRUCTOP_STRUCT:
> Andrew>        tem = longest_to_int (exp->elts[pc + 1].longconst);
> Andrew>        (*pos) += 3 + BYTES_TO_EXP_ELEM (tem + 1);
> Andrew> +      oldpos = *pos;
> Andrew>        arg1 = evaluate_subexp (NULL_TYPE, exp, pos, noside);
> Andrew>        if (noside == EVAL_SKIP)
> Andrew>  	return eval_skip_value (exp);
> Andrew> +      if (noside == EVAL_AVOID_SIDE_EFFECTS)
> Andrew> +	{
> Andrew> +	  /* If the element of the structure has a dynamic type then we
> Andrew> +	     need to get the real value representing the containing
> Andrew> +	     structure so that we can correctly evaluate the type of the
> Andrew> +	     element.  If we're not already avoiding side effects then we
> Andrew> +	     already have the real value of the containing structure, so
> Andrew> +	     this is not needed.  */
> Andrew> +	  type = lookup_struct_elt_type (value_type (arg1),
> Andrew> +					 &exp->elts[pc + 2].string, 1);
> Andrew> +	  if (type != nullptr && is_dynamic_type (type))
> Andrew> +	    {
> Andrew> +	      *pos = oldpos;
> Andrew> +	      arg1 = evaluate_subexp (NULL_TYPE, exp, pos, EVAL_NORMAL);
> 
> Re-evaluating a subexpression like this can lead to problems; see for
> example commit 6830f270e ("Avoid exponential behavior in rust_evaluate_subexp").
> 
> I don't know if there's another way to do this, though.

Thanks for your feedback.

Personally, I'd like to rip out EVAL_AVOID_SIDE_EFFECTS completely.  I
don't know the history here, but I suspect this was a poor-man's lazy
value system.

The behaviour of this flag seems like it should be don't access the
target unless it's required to correctly do the task we're trying to
do.  But it seems like a working lazy value system should give the
same result.....

.... but I'm probably missing something.

Thanks,
Andrew

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

* Re: [PATCHv2 2/2] gdb/fortran: Access elements of a structure with dynamic type
  2020-07-23 10:28       ` Andrew Burgess
@ 2020-07-24 20:03         ` Tom Tromey
  2020-07-26 19:31           ` Tom Tromey
  2020-08-04 19:19           ` Tom Tromey
  0 siblings, 2 replies; 14+ messages in thread
From: Tom Tromey @ 2020-07-24 20:03 UTC (permalink / raw)
  To: Andrew Burgess; +Cc: Tom Tromey, gdb-patches

Andrew> Personally, I'd like to rip out EVAL_AVOID_SIDE_EFFECTS completely.  I
Andrew> don't know the history here, but I suspect this was a poor-man's lazy
Andrew> value system.

I suspect the reason here is that things like "ptype x++" should not
increment x; and "ptype f(x)" should probably not actually invoke the
call.  Also, I think the implementation currently relies on this to
handle type inference for expressions like "x ? a : b" -- where the
types of both "a" and "b" affect the result.

EVAL_SKIP can be removed though.  It is just a workaround for the lame
data structure being used here.  In fact, the whole expression data
structure and evaluator needs to be rewritten.  It's awful as-is.  It's
a big job though.

Andrew> The behaviour of this flag seems like it should be don't access the
Andrew> target unless it's required to correctly do the task we're trying to
Andrew> do.  But it seems like a working lazy value system should give the
Andrew> same result.....

Andrew> .... but I'm probably missing something.

I've never been completely clear on the intended semantics of
EVAL_AVOID_SIDE_EFFECTS.  It refrains from reading inferior memory,
usually (?) -- but is that really needed?

One argument would be that ptype should just evaluate the expression,
and that for 'ptype x++', well, you got what you asked for.  

A plus side is that scenarios like the one you present wouldn't be
possible.

A minus is that things like "ptype variable" would maybe no longer show
the declared type, but rather the dynamic type.

Speaking of, your scenario seems a lot like the C++ "set print object on"
scenario.  There, the dynamic type is pretty much only used when
printing.  I wonder if that makes sense for Fortran.

Tom

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

* Re: [PATCHv2 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection
  2020-07-22 19:10     ` Tom Tromey
@ 2020-07-25  0:31       ` Andrew Burgess
  0 siblings, 0 replies; 14+ messages in thread
From: Andrew Burgess @ 2020-07-25  0:31 UTC (permalink / raw)
  To: Tom Tromey; +Cc: gdb-patches

* Tom Tromey <tom@tromey.com> [2020-07-22 13:10:03 -0600]:

> >>>>> "Andrew" == Andrew Burgess <andrew.burgess@embecosm.com> writes:
> 
> Andrew> gdb/ChangeLog:
> 
> Andrew> 	PR fortran/23051
> Andrew> 	PR fortran/26139
> Andrew> 	* valops.c (value_ind): Pass address to
> Andrew> 	readjust_indirect_value_type.
> Andrew> 	* value.c (readjust_indirect_value_type): Make parameter
> Andrew> 	non-const, and add extra address parameter.  Resolve original type
> Andrew> 	before using it.
> Andrew> 	* value.h (readjust_indirect_value_type): Update function
> Andrew> 	signature and comment.
> 
> Thanks.  I think this is ok.

Thanks.  I've pushed this patch, I guess #2 will wait while I think
over the feedback you've provided.

Thanks,
Andrew

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

* Re: [PATCHv2 2/2] gdb/fortran: Access elements of a structure with dynamic type
  2020-07-24 20:03         ` Tom Tromey
@ 2020-07-26 19:31           ` Tom Tromey
  2020-08-04 19:19           ` Tom Tromey
  1 sibling, 0 replies; 14+ messages in thread
From: Tom Tromey @ 2020-07-26 19:31 UTC (permalink / raw)
  To: Tom Tromey; +Cc: Andrew Burgess, gdb-patches

Tom> Also, I think the implementation currently relies on this to
Tom> handle type inference for expressions like "x ? a : b" -- where the
Tom> types of both "a" and "b" affect the result.

This part isn't true.  Maybe I was remembering something I'd planned to
do, not sure.

However, in some cases EVAL_AVOID_SIDE_EFFECTS really is needed.
For example it's needed to properly implement sizeof(), which doesn't
evaluate its argument.

Tom> In fact, the whole expression data structure and evaluator needs to
Tom> be rewritten.  It's awful as-is.  It's a big job though.

I looked at it a bit this weekend and it is even bigger than I
remembered.  In addition to the data structure and the parsers, the Ada
parser has a resolution pass to rewrite the expression in-place (even, I
think, asking the user questions); the agent expression code translates
expressions to bytecode; and there's another pass that looks to see if
an expression refers to a given objfile.

Tom

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

* Re: [PATCHv2 2/2] gdb/fortran: Access elements of a structure with dynamic type
  2020-07-24 20:03         ` Tom Tromey
  2020-07-26 19:31           ` Tom Tromey
@ 2020-08-04 19:19           ` Tom Tromey
  2020-08-06 15:38             ` Andrew Burgess
  1 sibling, 1 reply; 14+ messages in thread
From: Tom Tromey @ 2020-08-04 19:19 UTC (permalink / raw)
  To: Tom Tromey; +Cc: Andrew Burgess, gdb-patches

Andrew> The behaviour of this flag seems like it should be don't access the
Andrew> target unless it's required to correctly do the task we're trying to
Andrew> do.  But it seems like a working lazy value system should give the
Andrew> same result.....

Andrew> .... but I'm probably missing something.

Tom> I've never been completely clear on the intended semantics of
Tom> EVAL_AVOID_SIDE_EFFECTS.  It refrains from reading inferior memory,
Tom> usually (?) -- but is that really needed?

Tom> One argument would be that ptype should just evaluate the expression,
Tom> and that for 'ptype x++', well, you got what you asked for.  

Tom> A plus side is that scenarios like the one you present wouldn't be
Tom> possible.

Tom> A minus is that things like "ptype variable" would maybe no longer show
Tom> the declared type, but rather the dynamic type.

Tom> Speaking of, your scenario seems a lot like the C++ "set print object on"
Tom> scenario.  There, the dynamic type is pretty much only used when
Tom> printing.  I wonder if that makes sense for Fortran.

This issue has also come up in my work to make the Ada support in gdb
work with DWARF debug info (rather than the "gnat encodings" which are
normally used).  Here, many Ada types now use dynamic properties and are
resolved to concrete types using resolve_dynamic_type.

One thing I was thinking about is that with the "do not evaluate"
approach, there is a difference between:

    (gdb) print x
    (gdb) ptype x

and

    (gdb) print x
    (gdb) ptype $

Here, only the second evaluation would show the dynamic type.

This seemed unnecessarily obscure to me, and I started leaning toward
the view that ptype ought to evaluate.  However, I found that the
current behavior is explicitly documented:

     If ARG is an expression (*note Expressions: Expressions.), it is
     not actually evaluated, and any side-effecting operations (such as
     assignments or function calls) inside it do not take place.

Now, Joel pointed out to me that the Ada expression evaluator already
does something like what is in the patch up-thread.  See "case
OP_VAR_VALUE" in ada_evaluate_subexp:

      if (noside == EVAL_AVOID_SIDE_EFFECTS)
[...]
	      /* Tagged types are a little special in the fact that the real
		 type is dynamic and can only be determined by inspecting the
		 object's tag.  This means that we need to get the object's
		 value first (EVAL_NORMAL) and then extract the actual object
		 type from its tag.

		 Note that we cannot skip the final step where we extract
		 the object type from its tag, because the EVAL_NORMAL phase
		 results in dynamic components being resolved into fixed ones.
		 This can cause problems when trying to print the type
		 description of tagged types whose parent has a dynamic size:
		 We use the type name of the "_parent" component in order
		 to print the name of the ancestor type in the type description.
		 If that component had a dynamic size, the resolution into
		 a fixed type would result in the loss of that type name,
		 thus preventing us from printing the name of the ancestor
		 type in the type description.  */
	      arg1 = evaluate_subexp (NULL_TYPE, exp, pos, EVAL_NORMAL);

So, this is a bit of a funny situation, where on the one hand the code
respects the "avoid side effects" rule (assuming the target isn't using
memory-mapped I/O that is overlaid by some Ada data structure ;), while
also avoiding the spirit of the thing ("not actually evaluated" -- here
in some cases it is).

My understanding is that this particular tweak came from a user request.
You can see here that it was definitely intentional:

    https://sourceware.org/pipermail/gdb-patches/2008-September/060193.html


One idea that came up on irc was to use a flag to ptype to select the
mode.  I think that would be fine -- though it still leaves the question
of which mode ought to be the default; and the question of whether we
ought to remove cases like the above from the code.

Perhaps a related question (mentioned above as well) is whether "set
print object on" ought to be ignored in favor of this flag.

Maybe one final weirdness is that if ptype evaluates, since the value
isn't entered into the value history, there's no way to refer to it
again without re-evaluating.


I am not completely certain but my current proposal would be:

1. ptype should evaluate its argument by default, and should show the
   runtime type.  I'm not concerned about the value history thing,
   because I think I tend not to use ptype on side-effecting expressions
   anyhow.

2. We should add a flag to ptype, say "/s" (for "static type"?), to have
   it not try to evaluate, but instead print the static type.

3. We should remove any special cases for EVAL_AVOID_SIDE_EFFECTS, since
   presumably they won't be needed any more.

4. For "ptype/s $", I guess we will need to have a back-link from the
   resolved type to the dynamic type.  (FWIW I have a patch I wrote to
   experiment with this...)

5. We should ignore the "set print object on" problem entirely.  For
   ptype/s, we should differentiate between "runtime type" and "concrete
   instance of dynamic type", and only try to use back-links for the
   latter.


What do you think?

Tom

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

* Re: [PATCHv2 2/2] gdb/fortran: Access elements of a structure with dynamic type
  2020-08-04 19:19           ` Tom Tromey
@ 2020-08-06 15:38             ` Andrew Burgess
  0 siblings, 0 replies; 14+ messages in thread
From: Andrew Burgess @ 2020-08-06 15:38 UTC (permalink / raw)
  To: Tom Tromey; +Cc: gdb-patches

* Tom Tromey <tromey@adacore.com> [2020-08-04 13:19:39 -0600]:

> Andrew> The behaviour of this flag seems like it should be don't access the
> Andrew> target unless it's required to correctly do the task we're trying to
> Andrew> do.  But it seems like a working lazy value system should give the
> Andrew> same result.....
> 
> Andrew> .... but I'm probably missing something.
> 
> Tom> I've never been completely clear on the intended semantics of
> Tom> EVAL_AVOID_SIDE_EFFECTS.  It refrains from reading inferior memory,
> Tom> usually (?) -- but is that really needed?
> 
> Tom> One argument would be that ptype should just evaluate the expression,
> Tom> and that for 'ptype x++', well, you got what you asked for.  
> 
> Tom> A plus side is that scenarios like the one you present wouldn't be
> Tom> possible.
> 
> Tom> A minus is that things like "ptype variable" would maybe no longer show
> Tom> the declared type, but rather the dynamic type.
> 
> Tom> Speaking of, your scenario seems a lot like the C++ "set print object on"
> Tom> scenario.  There, the dynamic type is pretty much only used when
> Tom> printing.  I wonder if that makes sense for Fortran.
> 
> This issue has also come up in my work to make the Ada support in gdb
> work with DWARF debug info (rather than the "gnat encodings" which are
> normally used).  Here, many Ada types now use dynamic properties and are
> resolved to concrete types using resolve_dynamic_type.
> 
> One thing I was thinking about is that with the "do not evaluate"
> approach, there is a difference between:
> 
>     (gdb) print x
>     (gdb) ptype x
> 
> and
> 
>     (gdb) print x
>     (gdb) ptype $
> 
> Here, only the second evaluation would show the dynamic type.
> 
> This seemed unnecessarily obscure to me, and I started leaning toward
> the view that ptype ought to evaluate.  However, I found that the
> current behavior is explicitly documented:
> 
>      If ARG is an expression (*note Expressions: Expressions.), it is
>      not actually evaluated, and any side-effecting operations (such as
>      assignments or function calls) inside it do not take place.
> 
> Now, Joel pointed out to me that the Ada expression evaluator already
> does something like what is in the patch up-thread.  See "case
> OP_VAR_VALUE" in ada_evaluate_subexp:
> 
>       if (noside == EVAL_AVOID_SIDE_EFFECTS)
> [...]
> 	      /* Tagged types are a little special in the fact that the real
> 		 type is dynamic and can only be determined by inspecting the
> 		 object's tag.  This means that we need to get the object's
> 		 value first (EVAL_NORMAL) and then extract the actual object
> 		 type from its tag.
> 
> 		 Note that we cannot skip the final step where we extract
> 		 the object type from its tag, because the EVAL_NORMAL phase
> 		 results in dynamic components being resolved into fixed ones.
> 		 This can cause problems when trying to print the type
> 		 description of tagged types whose parent has a dynamic size:
> 		 We use the type name of the "_parent" component in order
> 		 to print the name of the ancestor type in the type description.
> 		 If that component had a dynamic size, the resolution into
> 		 a fixed type would result in the loss of that type name,
> 		 thus preventing us from printing the name of the ancestor
> 		 type in the type description.  */
> 	      arg1 = evaluate_subexp (NULL_TYPE, exp, pos, EVAL_NORMAL);
> 
> So, this is a bit of a funny situation, where on the one hand the code
> respects the "avoid side effects" rule (assuming the target isn't using
> memory-mapped I/O that is overlaid by some Ada data structure ;), while
> also avoiding the spirit of the thing ("not actually evaluated" -- here
> in some cases it is).
> 
> My understanding is that this particular tweak came from a user request.
> You can see here that it was definitely intentional:
> 
>     https://sourceware.org/pipermail/gdb-patches/2008-September/060193.html
> 
> 
> One idea that came up on irc was to use a flag to ptype to select the
> mode.  I think that would be fine -- though it still leaves the question
> of which mode ought to be the default; and the question of whether we
> ought to remove cases like the above from the code.
> 
> Perhaps a related question (mentioned above as well) is whether "set
> print object on" ought to be ignored in favor of this flag.
> 
> Maybe one final weirdness is that if ptype evaluates, since the value
> isn't entered into the value history, there's no way to refer to it
> again without re-evaluating.
> 
> 
> I am not completely certain but my current proposal would be:
> 
> 1. ptype should evaluate its argument by default, and should show the
>    runtime type.  I'm not concerned about the value history thing,
>    because I think I tend not to use ptype on side-effecting expressions
>    anyhow.
> 
> 2. We should add a flag to ptype, say "/s" (for "static type"?), to have
>    it not try to evaluate, but instead print the static type.
> 
> 3. We should remove any special cases for EVAL_AVOID_SIDE_EFFECTS, since
>    presumably they won't be needed any more.
> 
> 4. For "ptype/s $", I guess we will need to have a back-link from the
>    resolved type to the dynamic type.  (FWIW I have a patch I wrote to
>    experiment with this...)
> 
> 5. We should ignore the "set print object on" problem entirely.  For
>    ptype/s, we should differentiate between "runtime type" and "concrete
>    instance of dynamic type", and only try to use back-links for the
>    latter.
> 
> 
> What do you think?

FWIW, I think this would be a good direction to move in.

Thanks,
Andrew

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

end of thread, other threads:[~2020-08-06 15:38 UTC | newest]

Thread overview: 14+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2020-07-10 15:22 [PATCH 0/2] Fortran dynamic type related fixes Andrew Burgess
2020-07-10 15:22 ` [PATCH 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection Andrew Burgess
2020-07-10 15:22 ` [PATCH 2/2] gdb/fortran: Access elements of a structure with dynamic type Andrew Burgess
2020-07-13 13:33 ` [PATCHv2 0/2] Fortran dynamic type related fixes Andrew Burgess
2020-07-13 13:33   ` [PATCHv2 1/2] gdb/fortran: resolve dynamic types when readjusting after an indirection Andrew Burgess
2020-07-22 19:10     ` Tom Tromey
2020-07-25  0:31       ` Andrew Burgess
2020-07-13 13:33   ` [PATCHv2 2/2] gdb/fortran: Access elements of a structure with dynamic type Andrew Burgess
2020-07-22 19:19     ` Tom Tromey
2020-07-23 10:28       ` Andrew Burgess
2020-07-24 20:03         ` Tom Tromey
2020-07-26 19:31           ` Tom Tromey
2020-08-04 19:19           ` Tom Tromey
2020-08-06 15:38             ` 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).