public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch, fortran] PR59198 - [4.8/4.9/5 Regression] ICE on cyclically dependent polymorphic types
@ 2015-03-15 21:25 Paul Richard Thomas
  0 siblings, 0 replies; 6+ messages in thread
From: Paul Richard Thomas @ 2015-03-15 21:25 UTC (permalink / raw)
  To: fortran, gcc-patches, Janus Weil; +Cc: Juergen Reuter

[-- Attachment #1: Type: text/plain, Size: 1070 bytes --]

Dear All,

As will be apparent from the PR, I have spent a silly amount of time
on this one :-(  Once I became 'de-obsessed' with the fact that the
reduced testcase worked, when 'rng' was made a pointer and
concentrated on the procedure pointer component 'obs1_int', finding
the problem was rather more straightforward, even if not 'obvious'.

The ChangeLog says it all. If the check is not done for components
that are not procedure pointers,
typebound_operator_9.f03 breaks. I am not entirely sure why this is
the case but the fix works fine.

Bootstraps and regtests on FC21/x86_64 - OK for 4.8, 4.9 and 5.0?

Paul

2014-03-15  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/59198
    * trans-types.c (gfc_get_derived_type): If an abstract derived
    type with procedure pointer components has no other type of
    component, return the backend_decl directly. Otherwise build
    the components.

2014-03-15  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/59198
    * gfortran.dg/proc_ptr_comp_44.f90 : New test
    * gfortran.dg/proc_ptr_comp_45.f90 : New test

[-- Attachment #2: submit.diff --]
[-- Type: text/plain, Size: 5372 bytes --]

Index: gcc/fortran/trans-types.c
===================================================================
*** gcc/fortran/trans-types.c	(revision 221333)
--- gcc/fortran/trans-types.c	(working copy)
*************** gfc_get_derived_type (gfc_symbol * deriv
*** 2448,2456 ****
        /* Its components' backend_decl have been built or we are
  	 seeing recursion through the formal arglist of a procedure
  	 pointer component.  */
!       if (TYPE_FIELDS (derived->backend_decl)
! 	    || derived->attr.proc_pointer_comp)
          return derived->backend_decl;
        else
          typenode = derived->backend_decl;
      }
--- 2448,2469 ----
        /* Its components' backend_decl have been built or we are
  	 seeing recursion through the formal arglist of a procedure
  	 pointer component.  */
!       if (TYPE_FIELDS (derived->backend_decl))
          return derived->backend_decl;
+       else if (derived->attr.proc_pointer_comp && derived->attr.abstract)
+ 	{
+ 	  /* If an abstract derived type with procedure pointer components
+ 	     has no other type of component, return the backend_decl.
+ 	     Otherwise build the components.  */
+ 	  for (c = derived->components; c; c = c->next)
+ 	    {
+ 	      if (!c->attr.proc_pointer)
+ 		break;
+ 	      else if (c->next == NULL)
+ 		return derived->backend_decl;
+ 	    }
+ 	  typenode = derived->backend_decl;
+ 	}
        else
          typenode = derived->backend_decl;
      }
Index: gcc/testsuite/gfortran.dg/proc_ptr_comp_44.f90
===================================================================
*** gcc/testsuite/gfortran.dg/proc_ptr_comp_44.f90	(revision 0)
--- gcc/testsuite/gfortran.dg/proc_ptr_comp_44.f90	(working copy)
***************
*** 0 ****
--- 1,71 ----
+ ! { dg-do compile }
+ ! Test the fix for PR59198, where the field for the component 'term' in
+ ! the derived type 'decay_gen_t' was not being built.
+ !
+ ! Contributed by Juergen Reuter  <juergen.reuter@desy.de>
+ !
+ module decays
+   abstract interface
+      function obs_unary_int ()
+      end function obs_unary_int
+   end interface
+ 
+   type, abstract :: any_config_t
+    contains
+      procedure (any_config_final), deferred :: final
+   end type any_config_t
+ 
+   type :: decay_term_t
+      type(unstable_t), dimension(:), pointer :: unstable_product => null ()
+   end type decay_term_t
+ 
+   type, abstract :: decay_gen_t
+      type(decay_term_t), dimension(:), allocatable :: term
+      procedure(obs_unary_int),   nopass, pointer :: obs1_int  => null ()
+   end type decay_gen_t
+ 
+   type, extends (decay_gen_t) :: decay_root_t
+    contains
+      procedure :: final => decay_root_final
+   end type decay_root_t
+ 
+   type, abstract :: rng_t
+   end type rng_t
+ 
+   type, extends (decay_gen_t) :: decay_t
+      class(rng_t), allocatable :: rng
+    contains
+      procedure :: final => decay_final
+   end type decay_t
+ 
+   type, extends (any_config_t) :: unstable_config_t
+    contains
+      procedure :: final => unstable_config_final
+   end type unstable_config_t
+ 
+   type :: unstable_t
+      type(unstable_config_t), pointer :: config => null ()
+      type(decay_t), dimension(:), allocatable :: decay
+   end type unstable_t
+ 
+   interface
+      subroutine any_config_final (object)
+        import
+        class(any_config_t), intent(inout) :: object
+      end subroutine any_config_final
+   end interface
+ 
+ contains
+   subroutine decay_root_final (object)
+     class(decay_root_t), intent(inout) :: object
+   end subroutine decay_root_final
+ 
+   recursive subroutine decay_final (object)
+     class(decay_t), intent(inout) :: object
+   end subroutine decay_final
+ 
+   recursive subroutine unstable_config_final (object)
+     class(unstable_config_t), intent(inout) :: object
+   end subroutine unstable_config_final
+ 
+ end module decays
Index: gcc/testsuite/gfortran.dg/proc_ptr_comp_45.f90
===================================================================
*** gcc/testsuite/gfortran.dg/proc_ptr_comp_45.f90	(revision 0)
--- gcc/testsuite/gfortran.dg/proc_ptr_comp_45.f90	(working copy)
***************
*** 0 ****
--- 1,49 ----
+ ! { dg-do run }
+ ! Test the fix for PR59198, where the field for the component 'term' in
+ ! the derived type 'decay_gen_t' was not being built.
+ !
+ ! Contributed by Paul Thomas and based on the original testcase by
+ ! Juergen Reuter  <juergen.reuter@desy.de>
+ !
+ module decays
+ 
+   implicit none
+ 
+   interface
+     real elemental function iface (arg)
+       real, intent(in) :: arg
+     end function
+   end interface
+ 
+   type :: decay_term_t
+      type(decay_t), pointer :: unstable_product
+      integer :: i
+   end type
+ 
+   type :: decay_gen_t
+      procedure(iface), nopass, pointer :: obs1_int
+      type(decay_term_t), allocatable :: term
+   end type
+ 
+   type :: rng_t
+     integer :: i
+   end type
+ 
+   type, extends (decay_gen_t) :: decay_t
+      class(rng_t), allocatable :: rng
+   end type
+ 
+   class(decay_t), allocatable :: object
+ 
+ end
+ 
+   use decays
+   type(decay_t), pointer :: template
+   real, parameter :: arg = 1.570796327
+   allocate (template)
+   allocate (template%rng)
+   template%obs1_int => cos
+   if (template%obs1_int (arg) .ne. cos (arg)) call abort
+   allocate (object, source = template)
+   if (object%obs1_int (arg) .ne. cos (arg)) call abort
+ end

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

* Re: [Patch, fortran] PR59198 - [4.8/4.9/5 Regression] ICE on cyclically dependent polymorphic types
  2015-03-17 17:33     ` Jakub Jelinek
@ 2015-03-17 21:10       ` Paul Richard Thomas
  0 siblings, 0 replies; 6+ messages in thread
From: Paul Richard Thomas @ 2015-03-17 21:10 UTC (permalink / raw)
  To: Jakub Jelinek
  Cc: Tobias Burnus, gcc-patches, fortran, Janus Weil, Juergen Reuter

Oh bother! Thanks Jakub - I did wonder about that but thought that the
same function would yield the same result :-(

Thanks. I will put it right.

Paul

On 17 March 2015 at 18:32, Jakub Jelinek <jakub@redhat.com> wrote:
> On Tue, Mar 17, 2015 at 06:28:03AM +0100, Paul Richard Thomas wrote:
>> Dear Tobias,
>>
>> As far as I can see, without the patch, gfc_get _derived_type goes
>> into a continuous loop trying to build the abstract type. Why this is
>> not the case with an additional non-procedure pointer component, I do
>> not know. I suspect that there is a corner case out there that will
>> challenge this patch but I was unable to generate it. I decided
>> therefore to commit, with an additional condition in the loop to
>> prevent repeated attempts to build the component field.
>>
>> Committed to trunk as revision 221474.
>
> Note, the proc_ptr_comp_45.f90 testcase fails on i686-linux (unless -mfpmath=sse -msse2
> or -ffloat-store) even at -O0, cos (1.570796327) is folded into constant and the runtime
> function doesn't return exactly the same result, because of extended
> precision.
> So, either you should allow a few ulps epsilon, or use some other function
> where you get reasonably exact result.
>
>         Jakub



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

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

* Re: [Patch, fortran] PR59198 - [4.8/4.9/5 Regression] ICE on cyclically dependent polymorphic types
  2015-03-17  5:28   ` Paul Richard Thomas
@ 2015-03-17 17:33     ` Jakub Jelinek
  2015-03-17 21:10       ` Paul Richard Thomas
  0 siblings, 1 reply; 6+ messages in thread
From: Jakub Jelinek @ 2015-03-17 17:33 UTC (permalink / raw)
  To: Paul Richard Thomas
  Cc: Tobias Burnus, gcc-patches, fortran, Janus Weil, Juergen Reuter

On Tue, Mar 17, 2015 at 06:28:03AM +0100, Paul Richard Thomas wrote:
> Dear Tobias,
> 
> As far as I can see, without the patch, gfc_get _derived_type goes
> into a continuous loop trying to build the abstract type. Why this is
> not the case with an additional non-procedure pointer component, I do
> not know. I suspect that there is a corner case out there that will
> challenge this patch but I was unable to generate it. I decided
> therefore to commit, with an additional condition in the loop to
> prevent repeated attempts to build the component field.
> 
> Committed to trunk as revision 221474.

Note, the proc_ptr_comp_45.f90 testcase fails on i686-linux (unless -mfpmath=sse -msse2
or -ffloat-store) even at -O0, cos (1.570796327) is folded into constant and the runtime
function doesn't return exactly the same result, because of extended
precision.
So, either you should allow a few ulps epsilon, or use some other function
where you get reasonably exact result.

	Jakub

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

* Re: [Patch, fortran] PR59198 - [4.8/4.9/5 Regression] ICE on cyclically dependent polymorphic types
  2015-03-16  8:39 ` Paul Richard Thomas
@ 2015-03-17  5:28   ` Paul Richard Thomas
  2015-03-17 17:33     ` Jakub Jelinek
  0 siblings, 1 reply; 6+ messages in thread
From: Paul Richard Thomas @ 2015-03-17  5:28 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gcc-patches, fortran, Janus Weil, Juergen Reuter

Dear Tobias,

As far as I can see, without the patch, gfc_get _derived_type goes
into a continuous loop trying to build the abstract type. Why this is
not the case with an additional non-procedure pointer component, I do
not know. I suspect that there is a corner case out there that will
challenge this patch but I was unable to generate it. I decided
therefore to commit, with an additional condition in the loop to
prevent repeated attempts to build the component field.

Committed to trunk as revision 221474.

4.8 and 4.9 to follow.

Cheers

Paul


On 16 March 2015 at 09:39, Paul Richard Thomas
<paul.richard.thomas@gmail.com> wrote:
> Dear Tobias,
>
> I think that I have a partial understanding now and will attempt to
> verify it tonight. Certainly to not build the components, when a
> derived type is flagged to have proc_pointer components cannot be
> right just because there can be other components as in the original
> testcase. This led to the lack of DECL_SIZE information for the field
> 'term' and the subsequent ICE. The key to understanding is the problem
> with typebound_operator_9.f03, when the check for proc_pointer
> components is omitted completely. This implies that there is something
> missing from the function (sorry, I forget its name) that build
> proc_pointer fields. I will check that idea - enlightenment might lead
> to a different patch.
>
> Thanks for the review.
>
> Paul
>
> On 16 March 2015 at 09:07, Tobias Burnus
> <tobias.burnus@physik.fu-berlin.de> wrote:
>> Dear Paul,
>>
>> Paul Richard Thomas wrote:
>>> The ChangeLog says it all. If the check is not done for components
>>> that are not procedure pointers,
>>> typebound_operator_9.f03 breaks. I am not entirely sure why this is
>>> the case but the fix works fine.
>>>
>>> Bootstraps and regtests on FC21/x86_64 - OK for 4.8, 4.9 and 5.0?
>>
>> OK. I have to admit that I also do not really understand why that's
>> required.
>>
>> Tobias
>
>
>
> --
> Outside of a dog, a book is a man's best friend. Inside of a dog it's
> too dark to read.
>
> Groucho Marx



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

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

* Re: [Patch, fortran] PR59198 - [4.8/4.9/5 Regression] ICE on cyclically dependent polymorphic types
  2015-03-16  8:07 Tobias Burnus
@ 2015-03-16  8:39 ` Paul Richard Thomas
  2015-03-17  5:28   ` Paul Richard Thomas
  0 siblings, 1 reply; 6+ messages in thread
From: Paul Richard Thomas @ 2015-03-16  8:39 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gcc-patches, fortran, Janus Weil, Juergen Reuter

Dear Tobias,

I think that I have a partial understanding now and will attempt to
verify it tonight. Certainly to not build the components, when a
derived type is flagged to have proc_pointer components cannot be
right just because there can be other components as in the original
testcase. This led to the lack of DECL_SIZE information for the field
'term' and the subsequent ICE. The key to understanding is the problem
with typebound_operator_9.f03, when the check for proc_pointer
components is omitted completely. This implies that there is something
missing from the function (sorry, I forget its name) that build
proc_pointer fields. I will check that idea - enlightenment might lead
to a different patch.

Thanks for the review.

Paul

On 16 March 2015 at 09:07, Tobias Burnus
<tobias.burnus@physik.fu-berlin.de> wrote:
> Dear Paul,
>
> Paul Richard Thomas wrote:
>> The ChangeLog says it all. If the check is not done for components
>> that are not procedure pointers,
>> typebound_operator_9.f03 breaks. I am not entirely sure why this is
>> the case but the fix works fine.
>>
>> Bootstraps and regtests on FC21/x86_64 - OK for 4.8, 4.9 and 5.0?
>
> OK. I have to admit that I also do not really understand why that's
> required.
>
> Tobias



-- 
Outside of a dog, a book is a man's best friend. Inside of a dog it's
too dark to read.

Groucho Marx

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

* Re: [Patch, fortran] PR59198 - [4.8/4.9/5 Regression] ICE on cyclically dependent polymorphic types
@ 2015-03-16  8:07 Tobias Burnus
  2015-03-16  8:39 ` Paul Richard Thomas
  0 siblings, 1 reply; 6+ messages in thread
From: Tobias Burnus @ 2015-03-16  8:07 UTC (permalink / raw)
  To: Paul Richard Thomas, gcc-patches, fortran, Janus Weil; +Cc: Juergen Reuter

Dear Paul,

Paul Richard Thomas wrote:
> The ChangeLog says it all. If the check is not done for components
> that are not procedure pointers,
> typebound_operator_9.f03 breaks. I am not entirely sure why this is
> the case but the fix works fine.
> 
> Bootstraps and regtests on FC21/x86_64 - OK for 4.8, 4.9 and 5.0?

OK. I have to admit that I also do not really understand why that's
required.

Tobias

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

end of thread, other threads:[~2015-03-17 21:10 UTC | newest]

Thread overview: 6+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2015-03-15 21:25 [Patch, fortran] PR59198 - [4.8/4.9/5 Regression] ICE on cyclically dependent polymorphic types Paul Richard Thomas
2015-03-16  8:07 Tobias Burnus
2015-03-16  8:39 ` Paul Richard Thomas
2015-03-17  5:28   ` Paul Richard Thomas
2015-03-17 17:33     ` Jakub Jelinek
2015-03-17 21:10       ` Paul Richard Thomas

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).