[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-06 Thread janus at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #1 from janus at gcc dot gnu.org ---
Reduced test case:


module m
  type dt
integer, allocatable :: h(:)
  end type
end module m

  use m
  call foo (4)
contains
  subroutine foo (n)
integer :: n
type (dt) :: x(2:n)
if (lbound (x, 1) /= 2 .or. ubound (x, 1) /= 4) STOP 11
  end subroutine
end



 type (dt) :: x(2:n)
   1
Warning: No location in expression near (1)



I have no idea what this error message is trying to tell me ... :(

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-06 Thread janus at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

janus at gcc dot gnu.org changed:

   What|Removed |Added

   Keywords||diagnostic
 CC||tkoenig at gcc dot gnu.org

--- Comment #2 from janus at gcc dot gnu.org ---
(In reply to janus from comment #1)
>
>  type (dt) :: x(2:n)
>1
> Warning: No location in expression near (1)
> 
> 
> I have no idea what this error message is trying to tell me ... :(

In any case, it comes from "check_locus_expr" (in frontend-passes.c), which was
added by Thomas in r243520. However that commit is already more than a year
old, so something else must have triggered this warning to appear recently.

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-06 Thread rguenth at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

Richard Biener  changed:

   What|Removed |Added

   Priority|P3  |P4
   Target Milestone|--- |9.0

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-06 Thread tkoenig at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #3 from Thomas Koenig  ---
The idea of the warning is to ensure that we have
Location information everywhere, and that patches
Which do not correctly set the location should cause
something visible during testing. We do not have this for
release.

We should take care to always regression test libgomp.fortran
as well...

--- Comment #4 from Thomas Koenig  ---
The idea of the warning is to ensure that we have
Location information everywhere, and that patches
Which do not correctly set the location should cause
something visible during testing. We do not have this for
release.

We should take care to always regression test libgomp.fortran
as well...

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-06 Thread tkoenig at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #3 from Thomas Koenig  ---
The idea of the warning is to ensure that we have
Location information everywhere, and that patches
Which do not correctly set the location should cause
something visible during testing. We do not have this for
release.

We should take care to always regression test libgomp.fortran
as well...

--- Comment #4 from Thomas Koenig  ---
The idea of the warning is to ensure that we have
Location information everywhere, and that patches
Which do not correctly set the location should cause
something visible during testing. We do not have this for
release.

We should take care to always regression test libgomp.fortran
as well...

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-06 Thread janus at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #5 from janus at gcc dot gnu.org ---
(In reply to Thomas Koenig from comment #4)
> The idea of the warning is to ensure that we have
> Location information everywhere, and that patches
> Which do not correctly set the location should cause
> something visible during testing. We do not have this for
> release.

Thanks for the explanation. Makes sense.

Do you have any idea what might have caused the regression?


> We should take care to always regression test libgomp.fortran
> as well...

Yes, I finally got into this habit, after repeatedly breaking libgomp tests
with my patches without noticing it.

I also tried to document how to do this at the bottom of this wiki page:

https://gcc.gnu.org/wiki/TestCaseWriting

It took me a while to figure out how to actually run the Fortran subset of the
libgomp suite (which is not very well documented, or I'm too stupid to find
it).

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-06 Thread ebotcazou at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

Eric Botcazou  changed:

   What|Removed |Added

 CC||ebotcazou at gcc dot gnu.org

--- Comment #6 from Eric Botcazou  ---
> It took me a while to figure out how to actually run the Fortran subset of
> the libgomp suite (which is not very well documented, or I'm too stupid to
> find it).

It is run automatically now by typing "make -k check-fortran" at top level.

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-06 Thread janus at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #7 from janus at gcc dot gnu.org ---
(In reply to Eric Botcazou from comment #6)
> It is run automatically now by typing "make -k check-fortran" at top level.

Ah, thanks for the remark (wasn't aware of that). Nice!

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-08 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

Dominique d'Humieres  changed:

   What|Removed |Added

 Status|UNCONFIRMED |NEW
   Last reconfirmed||2018-07-08
 CC||foreese at gcc dot gnu.org
 Ever confirmed|0   |1

--- Comment #8 from Dominique d'Humieres  ---
Caused/exposed by revision r262442.

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-08 Thread janus at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #9 from janus at gcc dot gnu.org ---
(In reply to Dominique d'Humieres from comment #8)
> Caused/exposed by revision r262442.

Thanks for the info, Dominique.


The following patch seems to be sufficient to fix the regression:

Index: expr.c
===
--- expr.c  (revision 262446)
+++ expr.c  (working copy)
@@ -4648,6 +4648,8 @@ gfc_generate_initializer (gfc_typespec *ts, bool g
  if (val == false)
return NULL;
}
+ if (!ctor->expr->where.nextc || !ctor->expr->where.lb)
+   ctor->expr->where = init->where;
}

   gfc_constructor_append (&init->value.constructor, ctor);

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-09 Thread janus at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #10 from janus at gcc dot gnu.org ---
(In reply to janus from comment #9)
> The following patch seems to be sufficient to fix the regression:


... however, it lacks a safety check for the existence of the ctor expression.
This variant regtests cleanly:


Index: gcc/fortran/expr.c
===
--- gcc/fortran/expr.c  (revision 262509)
+++ gcc/fortran/expr.c  (working copy)
@@ -4650,6 +4650,10 @@ gfc_generate_initializer (gfc_typespec *ts, bool g
}
}

+  /* Make sure that locus is set.  */
+  if (ctor->expr && (!ctor->expr->where.nextc || !ctor->expr->where.lb))
+   ctor->expr->where = init->where;
+
   gfc_constructor_append (&init->value.constructor, ctor);
 }

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-09 Thread tkoenig at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #11 from Thomas Koenig  ---
(In reply to janus from comment #10)
> (In reply to janus from comment #9)
> > The following patch seems to be sufficient to fix the regression:
> 
> 
> ... however, it lacks a safety check for the existence of the ctor
> expression. This variant regtests cleanly:
> 
> 
> Index: gcc/fortran/expr.c
> ===
> --- gcc/fortran/expr.c(revision 262509)
> +++ gcc/fortran/expr.c(working copy)
> @@ -4650,6 +4650,10 @@ gfc_generate_initializer (gfc_typespec *ts, bool g
>   }
>   }
>  
> +  /* Make sure that locus is set.  */
> +  if (ctor->expr && (!ctor->expr->where.nextc || !ctor->expr->where.lb))
> + ctor->expr->where = init->where;
> +
>gfc_constructor_append (&init->value.constructor, ctor);
>  }

If possible, I would prefer to set the locus where it is generated,
not conditionally later.

Unfortunately, I cannot currently look into this due to PR 86450 :-(

If I had a bootstrapping gcc, I would probably look at

  /* Fetch or generate an initializer for the component.  */
  tmp = component_initializer (comp, generate);

and see if the locus is set correctly at that point, then
(possibly) go back to component_initializer to see where this is
missing.

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-10 Thread foreese at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #12 from Fritz Reese  ---
(In reply to Thomas Koenig from comment #11)
> (In reply to janus from comment #10)
...
> 
> If possible, I would prefer to set the locus where it is generated,
> not conditionally later.
> 
> Unfortunately, I cannot currently look into this due to PR 86450 :-(
> 
> If I had a bootstrapping gcc, I would probably look at
> 
>   /* Fetch or generate an initializer for the component.  */
>   tmp = component_initializer (comp, generate);
> 
> and see if the locus is set correctly at that point, then
> (possibly) go back to component_initializer to see where this is
> missing.

I agree. I traced the issue and it appears locus info is not set for
gfc_components which are created from a module definition, so c->loc is empty.
Given that, this line is erroneous:

> static gfc_expr *
> component_initializer (gfc_component *c, bool generate)
> [...]
>  init = gfc_get_null_expr (&c->loc);

Before r262442 the locus for the NULL expression was originally copied from the
derived type to which the component belonged. (This is less than ideal when the
message actually refers to the component, which is why this behavior was
"fixed" in r262442.)

If we set the component's locus when it is loaded from a module, the following
patch fixes the issue and retains sane location information for the component
and its initializer:

diff --git a/gcc/fortran/module.c b/gcc/fortran/module.c
index b120501beb7..27d68f6b1b5 100644
--- a/gcc/fortran/module.c
+++ b/gcc/fortran/module.c
@@ -2848,6 +2848,8 @@ mio_component (gfc_component *c, int vtype)
   if (c->attr.proc_pointer)
 mio_typebound_proc (&c->tb);

+  c->loc = gfc_current_locus;
+
   mio_rparen ();
 }

However if we prefer not to set the component's locus for whatever reason, the
following alternative patch also fixes the issue, where the component's
initializer has its locus set to that of the derived type declaration:

diff --git a/gcc/fortran/expr.c b/gcc/fortran/expr.c
index 6a7e09589a7..c63b41c36e4 100644
--- a/gcc/fortran/expr.c
+++ b/gcc/fortran/expr.c
@@ -,7 +,7 @@ comp_pointer (gfc_component *comp)
Only generate an initializer if generate is true.  */

 static gfc_expr *
-component_initializer (gfc_component *c, bool generate)
+component_initializer (gfc_typespec *derived, gfc_component *c, bool generate)
 {
   gfc_expr *init = NULL;

@@ -4453,7 +4453,10 @@ component_initializer (gfc_component *c, bool generate)
  do not already have an initializer.  */
   if (comp_allocatable (c) || (generate && comp_pointer (c) &&
!c->initializer))
 {
-  init = gfc_get_null_expr (&c->loc);
+  if (c->loc.nextc && c->loc.lb)
+   init = gfc_get_null_expr (&c->loc);
+  else
+   init = gfc_get_null_expr (&derived->declared_at);
   init->ts = c->ts;
   return init;
 }
@@ -4588,7 +4591,7 @@ gfc_generate_initializer (gfc_typespec *ts, bool
generate)
   gfc_constructor *ctor = gfc_constructor_get();

   /* Fetch or generate an initializer for the component.  */
-  tmp = component_initializer (comp, generate);
+  tmp = component_initializer (ts->u.derived, comp, generate);
   if (tmp)
{
  /* Save the component ref for STRUCTUREs and UNIONs.  */


I am currently running regression tests to verify these patches. If both pass
and I have not missed something obvious I would prefer adding location info to
the component when loading from a module (the first patch).

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-16 Thread janus at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #13 from janus at gcc dot gnu.org ---
(In reply to Fritz Reese from comment #12)
> If we set the component's locus when it is loaded from a module, the
> following patch fixes the issue and retains sane location information for
> the component and its initializer:
> 
> diff --git a/gcc/fortran/module.c b/gcc/fortran/module.c
> index b120501beb7..27d68f6b1b5 100644
> --- a/gcc/fortran/module.c
> +++ b/gcc/fortran/module.c
> @@ -2848,6 +2848,8 @@ mio_component (gfc_component *c, int vtype)
>if (c->attr.proc_pointer)
>  mio_typebound_proc (&c->tb);
>  
> +  c->loc = gfc_current_locus;
> +
>mio_rparen ();
>  }
>  
> [..]
> 
> I am currently running regression tests to verify these patches. If both
> pass and I have not missed something obvious I would prefer adding location
> info to the component when loading from a module (the first patch).

I agree that this is probably the best way to fix it. If the patch regtests
well, it's ok for trunk from my side. Thanks for having a look!

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-16 Thread foreese at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #14 from Fritz Reese  ---
Author: foreese
Date: Mon Jul 16 18:16:00 2018
New Revision: 262743

URL: https://gcc.gnu.org/viewcvs?rev=262743&root=gcc&view=rev
Log:
2018-07-16  Fritz Reese  

gcc/fortran/ChangeLog:

PR fortran/86417
* module.c (mio_component): Set component->loc when loading from
module.


Modified:
trunk/gcc/fortran/ChangeLog
trunk/gcc/fortran/module.c

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-16 Thread foreese at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

Fritz Reese  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #15 from Fritz Reese  ---
(In reply to janus from comment #13)
> (In reply to Fritz Reese from comment #12)
> > If we set the component's locus when it is loaded from a module, the
> > following patch fixes the issue and retains sane location information for
> > the component and its initializer:
> > 
> > diff --git a/gcc/fortran/module.c b/gcc/fortran/module.c
> > index b120501beb7..27d68f6b1b5 100644
> > --- a/gcc/fortran/module.c
> > +++ b/gcc/fortran/module.c
> > @@ -2848,6 +2848,8 @@ mio_component (gfc_component *c, int vtype)
> >if (c->attr.proc_pointer)
> >  mio_typebound_proc (&c->tb);
> >  
> > +  c->loc = gfc_current_locus;
> > +
> >mio_rparen ();
> >  }
> >  
> > [..]
> > 
> > I am currently running regression tests to verify these patches. If both
> > pass and I have not missed something obvious I would prefer adding location
> > info to the component when loading from a module (the first patch).
> 
> I agree that this is probably the best way to fix it. If the patch regtests
> well, it's ok for trunk from my side. Thanks for having a look!

Thanks for the confirmation. I have committed to trunk (without a new testcase,
as alloc-comp-3.f90 exposes the regression).

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-16 Thread foreese at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #16 from Fritz Reese  ---
Author: foreese
Date: Mon Jul 16 18:59:44 2018
New Revision: 262746

URL: https://gcc.gnu.org/viewcvs?rev=262746&root=gcc&view=rev
Log:
2018-07-16  Fritz Reese  

Backport r262442 and r262743.

gcc/fortran/ChangeLog:

Backport from trunk:

PR fortran/86417
* module.c (mio_component): Set component->loc when loading from
module.

PR fortran/83183
PR fortran/86325
* expr.c (class_allocatable, class_pointer, comp_allocatable,
comp_pointer): New helpers.
(component_initializer): Generate EXPR_NULL for allocatable or pointer
components. Do not generate initializers for components within
BT_CLASS.
Do not assign to comp->initializer.
(gfc_generate_initializer): Use new helpers; move code to generate
EXPR_NULL for class allocatable components into
component_initializer().

gcc/testsuite/ChangeLog:

Backport from trunk:

PR fortran/83183
PR fortran/86325
* gfortran.dg/init_flag_18.f90: New testcase.
* gfortran.dg/init_flag_19.f03: New testcase.


Added:
branches/gcc-8-branch/gcc/testsuite/gfortran.dg/init_flag_18.f90
  - copied unchanged from r262442,
trunk/gcc/testsuite/gfortran.dg/init_flag_18.f90
branches/gcc-8-branch/gcc/testsuite/gfortran.dg/init_flag_19.f03
  - copied unchanged from r262442,
trunk/gcc/testsuite/gfortran.dg/init_flag_19.f03
Modified:
branches/gcc-8-branch/   (props changed)
branches/gcc-8-branch/gcc/fortran/ChangeLog
branches/gcc-8-branch/gcc/fortran/expr.c
branches/gcc-8-branch/gcc/fortran/module.c
branches/gcc-8-branch/gcc/testsuite/ChangeLog

Propchange: branches/gcc-8-branch/
('svn:mergeinfo' modified)

[Bug fortran/86417] [9 Regression] FAIL: libgomp.fortran/alloc-comp-3.f90 -O0 (test for excess errors)

2018-07-16 Thread foreese at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86417

--- Comment #17 from Fritz Reese  ---
Author: foreese
Date: Mon Jul 16 22:25:54 2018
New Revision: 262751

URL: https://gcc.gnu.org/viewcvs?rev=262751&root=gcc&view=rev
Log:
2018-07-16  Fritz Reese  

gcc/testsuite/ChangeLog:

Backport from trunk:

PR fortran/83183
PR fortran/86325
* gfortran.dg/init_flag_18.f90: New testcase.
* gfortran.dg/init_flag_19.f03: New testcase.

gcc/fortran/ChangeLog:

Backport from trunk:

PR fortran/86417
* module.c (mio_component): Set component->loc when loading from
module.

PR fortran/83183
PR fortran/86325
* expr.c (class_allocatable, class_pointer, comp_allocatable,
comp_pointer): New helpers.
(component_initializer): Generate EXPR_NULL for allocatable or pointer
components. Do not generate initializers for components within
BT_CLASS.
Do not assign to comp->initializer.
(gfc_generate_initializer): Use new helpers; move code to generate
EXPR_NULL for class allocatable components into
component_initializer().


Added:
branches/gcc-7-branch/gcc/testsuite/gfortran.dg/init_flag_18.f90
  - copied unchanged from r262746,
branches/gcc-8-branch/gcc/testsuite/gfortran.dg/init_flag_18.f90
branches/gcc-7-branch/gcc/testsuite/gfortran.dg/init_flag_19.f03
  - copied unchanged from r262746,
branches/gcc-8-branch/gcc/testsuite/gfortran.dg/init_flag_19.f03
Modified:
branches/gcc-7-branch/   (props changed)
branches/gcc-7-branch/gcc/fortran/ChangeLog
branches/gcc-7-branch/gcc/fortran/expr.c
branches/gcc-7-branch/gcc/fortran/module.c
branches/gcc-7-branch/gcc/testsuite/ChangeLog

Propchange: branches/gcc-7-branch/
('svn:mergeinfo' modified)