Bug 44978 - derived types are resolved more than once
Summary: derived types are resolved more than once
Status: NEW
Alias: None
Product: gcc
Classification: Unclassified
Component: fortran (show other bugs)
Version: 4.6.0
: P3 normal
Target Milestone: ---
Assignee: Not yet assigned to anyone
URL:
Keywords: diagnostic
Depends on:
Blocks:
 
Reported: 2010-07-18 14:28 UTC by janus
Modified: 2015-01-15 18:43 UTC (History)
2 users (show)

See Also:
Host:
Target:
Build:
Known to work:
Known to fail:
Last reconfirmed: 2013-06-15 00:00:00


Attachments
patch (1.33 KB, patch)
2013-08-09 13:37 UTC, janus
Details | Diff
Janus' patch with void functions (3.73 KB, patch)
2013-08-10 14:31 UTC, Mikael Morin
Details | Diff
patch with bool and flags to store the return value (2.98 KB, patch)
2013-08-11 19:12 UTC, Mikael Morin
Details | Diff
Differences between the errors printed with patches 30629 and 30633 (875 bytes, text/plain)
2013-08-13 09:40 UTC, Dominique d'Humieres
Details
Test showing a spectacular improvement with both patches (820 bytes, text/plain)
2013-08-13 09:54 UTC, Dominique d'Humieres
Details

Note You need to log in before you can comment on or make changes to this bug.
Description janus 2010-07-18 14:28:44 UTC
Consider the following test case:

type :: t1
  type(xy),pointer :: c
end type t1

type, extends(t1) :: t2
end type

type, extends(t2) :: t3
end type

end


This is correctly rejected with:

  type(xy),pointer :: c
                       1
Error: The pointer component 'c' of 't1' at (1) is a type that has not been declared


The problem is that the error message occurs three times (or even more, if one adds further types which extend upon t1), because resolve_fl_derived is called more than once for the base type.
Comment 1 janus 2013-04-13 11:15:01 UTC
Similar problems of multiple error messages occur also with non-extended types which have type-bound procedures. Reduced example from PR 55959 comment 4:

module pdfs

    type :: pdf_point
    contains
        procedure :: pdf_point_getx
    end type

contains

    function pdf_point_getx (this)
        class(pdf_point), intent(in) :: this
        real, dimension(x) :: pdf_point_getx
    end function

end module



The following error message occurs three times here:


        real, dimension(x) :: pdf_point_getx
                        1
Error: Expression at (1) must be of INTEGER type, found REAL
Comment 2 Dominique d'Humieres 2013-06-15 11:12:17 UTC
Still present at revision 200122.
Comment 3 janus 2013-08-08 20:00:54 UTC
For another example, see PR 51945. In this case, the double resolution seems to be related to the default initialization.

So, there are at least three distinct causes of multiple resolution of type symbols:
1) type extension
2) type-bound procedures
3) default initialization


To get rid of all of them, I would propose to use the gfc_symbol.resolved field (this is already done for ordinary symbols in 'resolve_symbol'). For derived types, however, one may have to add another value of this flag (other than '0' and '1') to distinguish between the two different resolution levels of resolve_fl_derived0 vs resolve_fl_derived.
Comment 4 janus 2013-08-08 21:24:20 UTC
(In reply to janus from comment #3)
> For another example, see PR 51945. In this case, the double resolution seems
> to be related to the default initialization.

Here is a reduced test case from this PR:


type t
end type

type ::  t2
end type

type my_t
  type(t) :: y = t2() ! Invalid
end type

type(my_t) :: a
end


It gives three times the error message:

  type(t) :: y = t2() ! Invalid
                1
Error: Can't convert TYPE(t2) to TYPE(t) at (1)
Comment 5 janus 2013-08-09 06:00:12 UTC
(In reply to janus from comment #3)
> To get rid of all of them, I would propose to use the gfc_symbol.resolved
> field (this is already done for ordinary symbols in 'resolve_symbol'). For
> derived types, however, one may have to add another value of this flag
> (other than '0' and '1') to distinguish between the two different resolution
> levels of resolve_fl_derived0 vs resolve_fl_derived.

The following draft patch does exactly this and gets the error count down to one for comment 1 and down to two for comment 1 and 4:


Index: gcc/fortran/gfortran.h
===================================================================
--- gcc/fortran/gfortran.h	(revision 201576)
+++ gcc/fortran/gfortran.h	(working copy)
@@ -1250,7 +1250,7 @@ typedef struct gfc_symbol
   /* Set if this variable is used as an index name in a FORALL.  */
   unsigned forall_index:1;
   /* Used to avoid multiple resolutions of a single symbol.  */
-  unsigned resolved:1;
+  unsigned resolved:2;
 
   int refs;
   struct gfc_namespace *ns;	/* namespace containing this symbol */
Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c	(revision 201576)
+++ gcc/fortran/resolve.c	(working copy)
@@ -11962,6 +11962,10 @@ resolve_fl_derived0 (gfc_symbol *sym)
   gfc_symbol* super_type;
   gfc_component *c;
 
+  if (sym->resolved>1)
+    return true;
+  sym->resolved = 2;
+
   if (sym->attr.unlimited_polymorphic)
     return true;
 
@@ -12381,6 +12385,13 @@ resolve_fl_derived (gfc_symbol *sym)
 {
   gfc_symbol *gen_dt = NULL;
 
+  if (!resolve_fl_derived0 (sym))
+    return false;
+
+  if (sym->resolved>2)
+    return true;
+  sym->resolved = 3;
+
   if (sym->attr.unlimited_polymorphic)
     return true;
 
@@ -12422,9 +12433,6 @@ resolve_fl_derived (gfc_symbol *sym)
 	}
     }
 
-  if (!resolve_fl_derived0 (sym))
-    return false;
-
   /* Resolve the type-bound procedures.  */
   if (!resolve_typebound_procedures (sym))
     return false;
@@ -12624,16 +12632,13 @@ resolve_symbol (gfc_symbol *sym)
   gfc_array_spec *as;
   bool saved_specification_expr;
 
-  if (sym->resolved)
+  if (sym->resolved>0)
     return;
   sym->resolved = 1;
 
-  if (sym->attr.artificial)
+  if (sym->attr.artificial || sym->attr.unlimited_polymorphic)
     return;
 
-  if (sym->attr.unlimited_polymorphic)
-    return;
-
   if (sym->attr.flavor == FL_UNKNOWN
       || (sym->attr.flavor == FL_PROCEDURE && !sym->attr.intrinsic
 	  && !sym->attr.generic && !sym->attr.external
Comment 6 janus 2013-08-09 13:37:10 UTC
Created attachment 30629 [details]
patch

Unfortunately the patch in comment 5 shows a rather larger number of failures in the testsuite, but the attached variant seems to be clean.
Comment 7 janus 2013-08-09 13:59:48 UTC
(In reply to janus from comment #5)
> The following draft patch does exactly this and gets the error count down to
> one for comment 1 and down to two for comment 1 and 4:

The remaining duplication in comment 4 should be fixed by the patch in PR 51945 comment 4.

For comment 1, there should also be a way to get rid of it (however, one technical problem there is that 'resolve_symbol' does not have a return value to report its success or failure).
Comment 8 Mikael Morin 2013-08-09 15:03:14 UTC
I'm not convinced by the following:

(In reply to janus from comment #6)
> @@ -11962,6 +11957,10 @@ resolve_fl_derived0 (gfc_symbol *sym)
>    gfc_symbol* super_type;
>    gfc_component *c;
>  
> +  if (sym->resolved>1)
> +    return true;
> +  sym->resolved = 2;
> +
>    if (sym->attr.unlimited_polymorphic)
>      return true;

The first time we hit the function, sym->resolved is set to 2.
Suppose that an error is issued, and the function returns false.
Then, on the next time the function is called with the same symbol argument, no error is issued (this is the purpose of the patch), but as a side effect the function will return true, so that the caller will proceed as if the symbol was well formed.
Comment 9 janus 2013-08-09 19:23:17 UTC
(In reply to Mikael Morin from comment #8)
> > @@ -11962,6 +11957,10 @@ resolve_fl_derived0 (gfc_symbol *sym)
> >    gfc_symbol* super_type;
> >    gfc_component *c;
> >  
> > +  if (sym->resolved>1)
> > +    return true;
> > +  sym->resolved = 2;
> > +
> >    if (sym->attr.unlimited_polymorphic)
> >      return true;
> 
> The first time we hit the function, sym->resolved is set to 2.
> Suppose that an error is issued, and the function returns false.
> Then, on the next time the function is called with the same symbol argument,
> no error is issued (this is the purpose of the patch), but as a side effect
> the function will return true, so that the caller will proceed as if the
> symbol was well formed.

That's true, but I'm not sure that it is really a problem (at least the gfortran testsuite does not seem to have a problem with it).

Do you have a simple idea how to improve the patch in this regard? Or can you give an example where it would create a problem?
Comment 10 Mikael Morin 2013-08-09 19:55:48 UTC
(In reply to janus from comment #9)
> (In reply to Mikael Morin from comment #8)
> > > @@ -11962,6 +11957,10 @@ resolve_fl_derived0 (gfc_symbol *sym)
> > >    gfc_symbol* super_type;
> > >    gfc_component *c;
> > >  
> > > +  if (sym->resolved>1)
> > > +    return true;
> > > +  sym->resolved = 2;
> > > +
> > >    if (sym->attr.unlimited_polymorphic)
> > >      return true;
> > 
> > The first time we hit the function, sym->resolved is set to 2.
> > Suppose that an error is issued, and the function returns false.
> > Then, on the next time the function is called with the same symbol argument,
> > no error is issued (this is the purpose of the patch), but as a side effect
> > the function will return true, so that the caller will proceed as if the
> > symbol was well formed.
> 
> That's true, but I'm not sure that it is really a problem (at least the
> gfortran testsuite does not seem to have a problem with it).
> 
Well if that's not a problem, then the return value is not useful or at least not a used in a way that impacts the compiler so it can as well be void.

> Do you have a simple idea how to improve the patch in this regard?
The first one that comes to mind (beyond changing the return type to void) is caching the return value(s) in the symbol, one for each procedure.

Another possibility: change the code to:

  if (sym->resolved>1)
    return false;

  old_resolved = sym->resolved;
  sym->resolved = 2;

  /* blah... */

  sym->resolved = old_resolved;
  return true;
}


This only avoids the duplicate errors.  Multiple resolutions still happens when they are successful (which is the common case unfortunately).

> Or can
> you give an example where it would create a problem?

No, it was more a general design comment. I will try to find one.
Comment 11 janus 2013-08-10 07:55:30 UTC
(In reply to Mikael Morin from comment #10)
> > Do you have a simple idea how to improve the patch in this regard?
> The first one that comes to mind (beyond changing the return type to void)
> is caching the return value(s) in the symbol, one for each procedure.

IMHO it is probably not worth the hassle. I wouldn't like to do this without having a concrete reason for it (and with a clean testsuite I don't see any).


> Another possibility: change the code to:
> 
>   if (sym->resolved>1)
>     return false;
> 
>   old_resolved = sym->resolved;
>   sym->resolved = 2;
> 
>   /* blah... */
> 
>   sym->resolved = old_resolved;
>   return true;
> }
> 
> 
> This only avoids the duplicate errors.  Multiple resolutions still happens
> when they are successful (which is the common case unfortunately).

Well, the advantage of my original patch is obviously that it not only avoids the double errors, but it also prevents us from doing double the work in resolving the symbols, so it might even give a performance improvement for large codes, in particular with heavy OOP (not sure if it's anywhere close to being significant, though).
Comment 12 Mikael Morin 2013-08-10 14:31:52 UTC
Created attachment 30630 [details]
Janus' patch with void functions

(In reply to janus from comment #11)
> IMHO it is probably not worth the hassle. I wouldn't like to do this without
> having a concrete reason for it (and with a clean testsuite I don't see any).
> 
The reason is: 
the sym->resolved flag is an internal detail that should not be externally visible; it shouldn't change the return value.

> 
> Well, the advantage of my original patch is obviously that it not only
> avoids the double errors, but it also prevents us from doing double the work
> in resolving the symbols, so it might even give a performance improvement
> for large codes, in particular with heavy OOP (not sure if it's anywhere
> close to being significant, though).

All right, the only one solution left that I see is the one making the functions void. See the attached patch (comments welcome).
I ran the testsuite partially on it and it was clean, but I don't have the time to finish that right now. It looked as slow as usual by the way. ;-)
Comment 13 janus 2013-08-11 08:53:54 UTC
(In reply to Mikael Morin from comment #12)
> > IMHO it is probably not worth the hassle. I wouldn't like to do this without
> > having a concrete reason for it (and with a clean testsuite I don't see any).
> > 
> The reason is: 
> the sym->resolved flag is an internal detail that should not be externally
> visible; it shouldn't change the return value.

well, I guess one could argue that the return value of 'resolve_fl_derived' is an internal detail in the same sense as sym->resolved (both are not directly 'user-visible').


> > Well, the advantage of my original patch is obviously that it not only
> > avoids the double errors, but it also prevents us from doing double the work
> > in resolving the symbols, so it might even give a performance improvement
> > for large codes, in particular with heavy OOP (not sure if it's anywhere
> > close to being significant, though).
> 
> All right, the only one solution left that I see is the one making the
> functions void. See the attached patch (comments welcome).
> I ran the testsuite partially on it and it was clean, but I don't have the
> time to finish that right now. It looked as slow as usual by the way. ;-)

Your patch does not compile cleanly, but after a small fix to make it compile, the testsuite runs through successfully. (Btw I would not really expect a visible performance effect in the testsuite, because the share of OOP code in there is probably still rather low, even if it's growing slowly.)

However, I don't quite see the point of doing this: Doesn't a void return value have basically the same effect as returning true? (i.e. to "keep going", whereas returning false means to "back out", since there was a problem)

Therefore I don't really see the improvement here. To the contrary: I would rather say we should propagate the return values as far as possible (one case where it is currently not propagated is resolve_symbol). This alone might even get rid of the double errors (if one pulls it through fully), but again it does not really help with double resolution in the non-error case, so I'd say we still need to rely on sym->resolved.

But in addition (as a follow-up?) it might be worth to use more bool return values instead of void in the resolve_* routines (e.g. resolve_symbol). IIRC there might even be a another PR where this helps (will see if I can still find it ...)
Comment 14 Mikael Morin 2013-08-11 11:34:44 UTC
(In reply to janus from comment #13)
> > > Well, the advantage of my original patch is obviously that it not only
> > > avoids the double errors, but it also prevents us from doing double the work
> > > in resolving the symbols, so it might even give a performance improvement
> > > for large codes, in particular with heavy OOP (not sure if it's anywhere
> > > close to being significant, though).
> > 
> > All right, the only one solution left that I see is the one making the
> > functions void. See the attached patch (comments welcome).
> > I ran the testsuite partially on it and it was clean, but I don't have the
> > time to finish that right now. It looked as slow as usual by the way. ;-)
> 
> Your patch does not compile cleanly, but after a small fix to make it
> compile, the testsuite runs through successfully. 

Uh? My trunk is a few weeks old. I guess that's the reason.

> However, I don't quite see the point of doing this: Doesn't a void return
> value have basically the same effect as returning true? (i.e. to "keep
> going", whereas returning false means to "back out", since there was a
> problem)
> 
The point is: if the return value is not reliable, let's remove it.

The void is indeed the same as returning true ("keep going"). I think it's better to "always keep going" rather than "keep going because the function was already called, even if it returned 'back out' the first time".

> Therefore I don't really see the improvement here. To the contrary: I would
> rather say we should propagate the return values as far as possible (one
> case where it is currently not propagated is resolve_symbol). This alone
> might even get rid of the double errors (if one pulls it through fully), but
> again it does not really help with double resolution in the non-error case,
> so I'd say we still need to rely on sym->resolved.
> 
OK, let's use more bool; but then the return value shall be consistent across multiple calls.
So I would say use two bits for each function: one telling whether the function was already called on the symbol, and one telling the return value.
There are three functions as far as I know (resolve_symbol, resolve_fl_derived and resolve_fl_derived0) which makes six bits.
Even if you are concerned about wasted memory, that doesn't consume extra memory because of fields alignments.


(In reply to Mikael Morin from comment #10)
> > Or can
> > you give an example where it would create a problem?
> 
> No, it was more a general design comment. I will try to find one.

I couldn't find one; but my opinion remains the same. I think it's bad design to return different values across repeated calls.
Comment 15 janus 2013-08-11 17:22:51 UTC
(In reply to Mikael Morin from comment #14)
> > However, I don't quite see the point of doing this: Doesn't a void return
> > value have basically the same effect as returning true? (i.e. to "keep
> > going", whereas returning false means to "back out", since there was a
> > problem)
> > 
> The point is: if the return value is not reliable, let's remove it.
> 
> The void is indeed the same as returning true ("keep going"). I think it's
> better to "always keep going" rather than "keep going because the function
> was already called, even if it returned 'back out' the first time".

I don't really see an advantage in "always keep going", except for consistency maybe (if there is a simple way to always back out, I'm all for it, but I don't have the feeling we should invest too much work into this point, since the back-out procedure is anyway not pulled through all the way right now).


> > Therefore I don't really see the improvement here. To the contrary: I would
> > rather say we should propagate the return values as far as possible (one
> > case where it is currently not propagated is resolve_symbol). This alone
> > might even get rid of the double errors (if one pulls it through fully), but
> > again it does not really help with double resolution in the non-error case,
> > so I'd say we still need to rely on sym->resolved.
> > 
> OK, let's use more bool; but then the return value shall be consistent
> across multiple calls.
> So I would say use two bits for each function: one telling whether the
> function was already called on the symbol, and one telling the return value.
> There are three functions as far as I know (resolve_symbol,
> resolve_fl_derived and resolve_fl_derived0) which makes six bits.
> Even if you are concerned about wasted memory, that doesn't consume extra
> memory because of fields alignments.

But then: Will we need to add more procedures to this scheme at some point?

Also, I think giving resolve_symbol a bool return value will be quite a bit of work and may drag along further implications.

To my mind, the patch in comment 6 is still the most effective way for solving this PR, and I don't have much time to invest in this over the coming week. So, if you have some better ideas how to tackle it, feel free to take over. I guess I'm out for now ...
Comment 16 Mikael Morin 2013-08-11 19:12:47 UTC
Created attachment 30633 [details]
patch with bool and flags to store the return value

(In reply to Mikael Morin from comment #14)
> OK, let's use more bool; but then the return value shall be consistent
> across multiple calls.
> So I would say use two bits for each function: one telling whether the
> function was already called on the symbol, and one telling the return value.
> There are three functions as far as I know (resolve_symbol,
> resolve_fl_derived and resolve_fl_derived0) which makes six bits.
> Even if you are concerned about wasted memory, that doesn't consume extra
> memory because of fields alignments.
> 
The attached patch shows what it looks like.
I also took the opportunity to extend your pr51945 change (hunk below) to the whole loop.

@@ -12344,7 +12344,7 @@ resolve_fl_derived0 (gfc_symbol *sym)
 
       if (c->initializer && !sym->attr.vtype
 	  && !gfc_check_assign_symbol (sym, c, c->initializer))
-	return false;
+	continue;
     }
Comment 17 Dominique d'Humieres 2013-08-13 09:38:21 UTC
In what follows "Janus' patch" will refer to
http://gcc.gnu.org/bugzilla/attachment.cgi?id=30629
and "Mikael's patch" to
http://gcc.gnu.org/bugzilla/attachment.cgi?id=30633

Although there are still duplicate errors, both patches regtest cleanly and are a significant improvement. I have seen the following differences between the two patches (I'll attach the full differences):

(1) pr43591, Mikael's patch output the additional error

pr43591.f90:8.77:

     procedure(number_flavor_states), nopass, pointer :: number_flavor_states => NULL()
									     1
Error: Interface 'number_flavor_states' at (1) must be explicit

For both patches the error

pr43591.f90:15.23:

    integer, dimension(physical%number_particles_out(), &
		       1
Error: Expression at (1) must be of INTEGER type, found UNKNOWN

is printed twice.

(2) pr48095, the error

pr48095.f90:7.79:

    procedure(get_area), pointer, pass(this) :: get_special_area => get_my_area
									       1
Error: Interface mismatch in procedure pointer assignment at (1): Type mismatch in argument 'this' (CLASS(rectangle)/TYPE(rectangle))

is printed three times with Janus' patch and only twice with Mikael's one.

(3) pr55983, with Janus' patch, the last error is

pr55983.f90:16.32:

    class(bcd_t), pointer :: bcx, bcy
				1
Error: The pointer component 'bcx' of '__class_solver_mpdata_m_Mpdata_t' at (1) is a type that has not been declared

while with Mikael's patch it is

pr55983.f90:16.37:

    class(bcd_t), pointer :: bcx, bcy
				     1
Error: The pointer component 'bcy' of 'mpdata_t' at (1) is a type that has not been declared

For a clean tree it is

    class(bcd_t), pointer :: bcx, bcy
                                1
Error: The pointer component 'bcx' of 'mpdata_t' at (1) is a type that has not been declared

(4) pr58023, compiling both tests with Janus' patch gives an ICE, while with Mikale's patch the first test gives a second error

pr58023.f90:11.34:

     procedure(mr), pointer :: mr2
				  1
Error: Procedure pointer component 'mr2' with PASS at (1) must have at least one argument

> I also took the opportunity to extend your pr51945 change (hunk below) 
> to the whole loop.

This also fixes pr58023#c0. pr58023#c1 is fixed if I replace the following hunks

@@ -12024,7 +12036,8 @@ resolve_fl_derived0 (gfc_symbol *sym)
 	  gfc_error ("Component '%s' at %L with coarray component "
 		     "shall be a nonpointer, nonallocatable scalar",
 		     c->name, &c->loc);
-	  return false;
+	  retval = false;
+	  continue;
 	}
 
       /* F2008, C448.  */
@@ -12032,7 +12045,8 @@ resolve_fl_derived0 (gfc_symbol *sym)
 	{
 	  gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
 		     "is not an array pointer", c->name, &c->loc);
-	  return false;
+	  retval = false;
+	  continue;
 	}
 
       if (c->attr.proc_pointer && c->ts.interface)

with


@@ -12031,16 +12035,20 @@ resolve_fl_derived0 (gfc_symbol *sym)
 	{
 	  gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
 		     "is not an array pointer", c->name, &c->loc);
-	  return false;
+	  retval = false;
+	  continue;
 	}
 
       if (c->attr.proc_pointer && c->ts.interface)
 	{
 	  gfc_symbol *ifc = c->ts.interface;
 
-	  if (!sym->attr.vtype
-	      && !check_proc_interface (ifc, &c->loc))
-	    return false;
+	  if (!sym->attr.vtype && !check_proc_interface (ifc, &c->loc))
+	    {
+	      c->tb->error = 1;
+	      retval = false;
+	      continue;
+	    }
 
 	  if (ifc->attr.if_source || ifc->attr.intrinsic)
 	    {
Comment 18 Dominique d'Humieres 2013-08-13 09:40:13 UTC
Created attachment 30642 [details]
Differences between the errors printed with patches 30629 and 30633
Comment 19 Dominique d'Humieres 2013-08-13 09:54:32 UTC
Created attachment 30645 [details]
Test showing a spectacular improvement with both patches
Comment 20 Dominique d'Humieres 2013-08-13 14:14:17 UTC
I have run my tests with the patch in comment #17. As expected it fixes  pr58023#c1, but it also remove the duplicate error in pr43591.f90 and

pr43591.f90:15.55:

    integer, dimension(physical%number_particles_out(), &
                                                       1
Error: Expression at (1) must be of INTEGER type, found UNKNOWN

I am a little bit puzzled by this error. I think it is an attempt to emit if for
physical%number_flavor_states(), but the error does not give the right locus (probably due to the continuation line). I don't understand why it is removed by the change and don't know how bad it is to remove it.

My analysis for pr48095 has been to fast: there is no duplicate, but two different errors:

pr48095.f90:7.79:

procedure(get_area), pointer, pass(this) :: get_special_area => get_my_area
                                                                           1
Error: Interface mismatch in procedure pointer assignment at (1): Type mismatch in argument 'this' (CLASS(rectangle)/TYPE(rectangle))
pr48095.f90:7.79:

procedure(get_area), pointer, pass(this) :: get_special_area => get_my_area
                                                                           1
Error: Interface mismatch for procedure-pointer component 'get_special_area' in structure constructor at (1): Type mismatch in argument 'this' (CLASS(rectangle)/TYPE(rectangle))

The locus for the second error should probably at the end of get_special_area.

With the Mikael's patch + the change in comment #17, I have spotted two remaining duplicates: the test in comment #4 and gfortran.dg/spec_expr_6.f90.
Indeed I have probably overlooked other cases (I have no idea on how to do an exhaustive search).
Comment 21 janus 2015-01-15 18:43:48 UTC
Part of the patch in comment #16 was committed as r219676 for PR 58023.