[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2016-01-14 Thread rguenth at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

Richard Biener  changed:

   What|Removed |Added

   Priority|P3  |P4

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-13 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #19 from Mikael Morin  ---
(In reply to Mikael Morin from comment #18)
> Lightly tested so far.

It actually regress heavily.

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-13 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

Mikael Morin  changed:

   What|Removed |Added

  Attachment #36937|0   |1
is obsolete||

--- Comment #18 from Mikael Morin  ---
Created attachment 37024
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=37024=edit
Updated patch

This updated patch basically keeps the new parts from V2 and removes the ones
from V1.
Lightly tested so far.

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-13 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

Mikael Morin  changed:

   What|Removed |Added

  Attachment #37024|0   |1
is obsolete||

--- Comment #20 from Mikael Morin  ---
Created attachment 37025
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=37025=edit
Fixed patch

Much better patch, yet not free of any regression.

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-06 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

Mikael Morin  changed:

   What|Removed |Added

  Attachment #36902|0   |1
is obsolete||

--- Comment #17 from Mikael Morin  ---
Created attachment 36937
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=36937=edit
Updated patch

This patch is just an update, it doesn't work really better than the first one.

I start to understand better this 'ignore_optional' stuff.
In the library, there are several variants of the procedures, with and without
optional arguments.  The correct one is picked during resolution (in
iresolve.c).
So, depending on the one that has been picked, the arguments have to be passed
or ignored.
The case of 'kind' is special, because it is always used (if present) in the
specific procedure name, and should never be passed, even if it was present.

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-05 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #12 from Dominique d'Humieres  ---
> Looks like it's PR68540.

So it should work now?

The statement in fortran/trans-intrinsic.c

  gfc_copy_formal_args_intr (sym, expr->value.function.isym,
 ignore_optional ? expr->value.function.actual
 : NULL);

looks suspicious: if ignore_optional means what indicated by the name and is
true, why passing expr->value.function.actual and NULL otherwise?


--- ../_clean/gcc/fortran/trans-intrinsic.c 2015-12-02 23:00:12.0
+0100
+++ gcc/fortran/trans-intrinsic.c   2015-12-04 12:26:05.0 +0100
@@ -3032,7 +3032,7 @@ gfc_get_symbol_for_expr (gfc_expr * expr
 }

   gfc_copy_formal_args_intr (sym, expr->value.function.isym,
-ignore_optional ? expr->value.function.actual
+!ignore_optional ? expr->value.function.actual
 : NULL);

   return sym;

"fixes" the failure for gfortran.dg/shape_8.f90, but causes

FAIL: gfortran.dg/char_pack_1.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/char_eoshift_1.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/char_pack_2.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/char_eoshift_2.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/cshift_large_1.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/eoshift_large_1.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/nested_reshape.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/optional_dim_2.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/optional_dim_3.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/reshape_4.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/reshape_zerosize_1.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/widechar_intrinsics_10.f90   -g -flto  (test for excess
errors)
FAIL: gfortran.dg/widechar_intrinsics_5.f90   -g -flto  (test for excess
errors)
FAIL: gfortran.dg/zero_sized_1.f90   -g -flto  (test for excess errors)

with -m32/-m64 and

FAIL: gfortran.dg/cshift_large_1.f90   -g -flto  (test for excess errors)
FAIL: gfortran.dg/eoshift_large_1.f90   -g -flto  (test for excess errors)

with -m64 (not run with -m32).

For gfortran.dg/optional_dim_2.f90 the diff between the patched (-) and
unpatched (+) trans-intrinsic.c is

 logical(kind=4) A.12[4];
 struct array1_logical(kind=4) atmp.11;
+integer(kind=8) * D.3471;
 integer(kind=8) D.3470;
 atmp.11.dim[0].lbound = 0;
 atmp.11.dim[0].ubound = 3;
 atmp.11.data = (void * restrict) 
 atmp.11.offset = 0;
-_gfortran_eoshift0_8 (, D.3467, D.3469, 0B, );
+_gfortran_eoshift0_8 (, D.3467, D.3469, 0B, D.3471);

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-05 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #14 from Dominique d'Humieres  ---
> > The statement in fortran/trans-intrinsic.c
> > 
> >   gfc_copy_formal_args_intr (sym, expr->value.function.isym,
> >  ignore_optional ? expr->value.function.actual
> >  : NULL);
> > 
> > looks suspicious: if ignore_optional means what indicated by the name and is
> > true, why passing expr->value.function.actual and NULL otherwise?
> > 
> Seeing how the argument is used would tell you the answer. ;-)

Sorry to be dense, but I don't understand.

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-05 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #13 from Mikael Morin  ---
(In reply to Dominique d'Humieres from comment #12)
> The statement in fortran/trans-intrinsic.c
> 
>   gfc_copy_formal_args_intr (sym, expr->value.function.isym,
>  ignore_optional ? expr->value.function.actual
>  : NULL);
> 
> looks suspicious: if ignore_optional means what indicated by the name and is
> true, why passing expr->value.function.actual and NULL otherwise?
> 
Seeing how the argument is used would tell you the answer. ;-)

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-05 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #15 from Mikael Morin  ---
(In reply to Dominique d'Humieres from comment #14)
> > > The statement in fortran/trans-intrinsic.c
> > > 
> > >   gfc_copy_formal_args_intr (sym, expr->value.function.isym,
> > >  ignore_optional ? expr->value.function.actual
> > >  : NULL);
> > > 
> > > looks suspicious: if ignore_optional means what indicated by the name and 
> > > is
> > > true, why passing expr->value.function.actual and NULL otherwise?
> > > 
> > Seeing how the argument is used would tell you the answer. ;-)
> 
> Sorry to be dense, but I don't understand.

Skipping arguments is dependant of whether the actual argument is present, so
it needs the actual argument list.
Admittedly, I understand what is done, not why it's done.

(In reply to Dominique d'Humieres from comment #12)
> > Looks like it's PR68540.
> 
> So it should work now?
> 
I have yet to find the best way to install isl-0.15 without polluting my
distribution with freestanding unmanaged files.
Then I can come back to this bug (or any other).

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-05 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #16 from Mikael Morin  ---
(In reply to Mikael Morin from comment #15)
> (In reply to Dominique d'Humieres from comment #12)
> > > Looks like it's PR68540.
> > 
> > So it should work now?
> > 
> I have yet to find the best way to install isl-0.15 without polluting my
> distribution with freestanding unmanaged files.
> Then I can come back to this bug (or any other).

Done, bootstrap broken with 0.15 as well. :-(

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-04 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #11 from Mikael Morin  ---
(In reply to Dominique d'Humieres from comment #10)
> >I can't test this right now (bootstrap broken).
> 
> Sorry about that. Anything serious?
> 
Looks like it's PR68540.

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-03 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #5 from Dominique d'Humieres  ---
> I think the problem is that it's actually working.  The optional arguments are
> removed... When they are not present, the procedure declaration also loses 
> them.

Well, it is not how I read

  static integer(kind=4) C.3452 = 4;
...
  D.3451 = 
  D.3453 = 
  _gfortran_shape_4 (, D.3451, D.3453);

There is a third argument D.3453 and its value is 4 (if it's not the KIND, what
is it?).

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-03 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #3 from Dominique d'Humieres  ---
I see the same problem with

program test_count
integer, dimension(2,3) :: a, b
logical, dimension(2,3) :: mask
integer :: i(2), j(3)
a = reshape( (/ 1, 2, 3, 4, 5, 6 /), (/ 2, 3 /))
b = reshape( (/ 0, 7, 3, 4, 5, 8 /), (/ 2, 3 /))
mask = a.ne.b
j=count(mask, 1, kind=4)
i=count(mask, 2)
end program test_count

...
 _gfortran_count_4_l (, D.3452, D.3454);
...
  _gfortran_count_4_l (, D.3463, D.3465, D.3467);
...

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-03 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

Mikael Morin  changed:

   What|Removed |Added

 CC||mikael at gcc dot gnu.org

--- Comment #4 from Mikael Morin  ---
(In reply to Dominique d'Humieres from comment #2)
> Am I correct to understand that it is intended to prevents the emission of
> the optional argument?
I think so.

> If yes, why is it not working (I lost the scent after
> that)?
I think the problem is that it's actually working.  The optional arguments are
removed... When they are not present, the procedure declaration also loses
them.

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-03 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

Dominique d'Humieres  changed:

   What|Removed |Added

 CC||tkoenig at gcc dot gnu.org
  Component|lto |fortran

--- Comment #2 from Dominique d'Humieres  ---
For the test

program test
   implicit none
   integer :: c(2), d(2)
   real, allocatable :: x(:,:)

   allocate(x(2,5))
   c = shape(x)
   d = shape(x,kind=4)
end

the result of the compilation with -fdump-tree-original is

...
{
  struct array2_real(kind=4) * D.3443;
  struct array1_integer(kind=4) parm.1;

  parm.1.dtype = 265;
  parm.1.dim[0].lbound = 1;
  parm.1.dim[0].ubound = 2;
  parm.1.dim[0].stride = 1;
  parm.1.data = (void *) [0];
  parm.1.offset = -1;
  D.3443 = 
  _gfortran_shape_4 (, D.3443);
}
{
  integer(kind=4) * D.3453;
  static integer(kind=4) C.3452 = 4;
  struct array2_real(kind=4) * D.3451;
  struct array1_integer(kind=4) parm.2;

  parm.2.dtype = 265;
  parm.2.dim[0].lbound = 1;
  parm.2.dim[0].ubound = 2;
  parm.2.dim[0].stride = 1;
  parm.2.data = (void *) [0];
  parm.2.offset = -1;
  D.3451 = 
  D.3453 = 
  _gfortran_shape_4 (, D.3451, D.3453);
}
...

and -Wlto-type-mismatch seems right to complain that

_gfortran_shape_4 (, D.3451, D.3453);

does not match

  _gfortran_shape_4 (, D.3443);

I have tried to understand why using the optional 'kind' argument generates a
third argument (not needed as it is reflected by _gfortran_shape_x for kind=x).

Looking at libgfortran/generated/shape_i4.c I see that shape_4 expects only two
arguments. 

Looking at gcc/fortran/trans-intrinsic.c, I see

...
case GFC_ISYM_SHAPE:
case GFC_ISYM_SPREAD:
case GFC_ISYM_YN2:
  /* Ignore absent optional parameters.  */
  return 1;
...

Am I correct to understand that it is intended to prevents the emission of the
optional argument? If yes, why is it not working (I lost the scent after that)?

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-03 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #7 from Dominique d'Humieres  ---
> In this case, the argument _is_ present, so it's not removed in the procedure
> declaration.  This seems to be done on purpose (grep for ignore_optional) but 
> I
> must admit that I don't understand why.

Indeed I have seen 'ignore_optional', but I did not understand what it was
supposed to do (as in "don't emit it").

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-03 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #6 from Mikael Morin  ---
(In reply to Dominique d'Humieres from comment #5)
> > I think the problem is that it's actually working.  The optional arguments 
> > are
> > removed... When they are not present, the procedure declaration also loses 
> > them.
> 
> Well, it is not how I read
> 
>   static integer(kind=4) C.3452 = 4;
> ...
>   D.3451 = 
>   D.3453 = 
>   _gfortran_shape_4 (, D.3451, D.3453);
> 
> There is a third argument D.3453 and its value is 4 (if it's not the KIND,
> what is it?).

In this case, the argument _is_ present, so it's not removed in the procedure
declaration.  This seems to be done on purpose (grep for ignore_optional) but I
must admit that I don't understand why.

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-03 Thread hubicka at ucw dot cz
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #9 from Jan Hubicka  ---
> > Well, it is not how I read
> > 
> >   static integer(kind=4) C.3452 = 4;
> > ...
> >   D.3451 = 
> >   D.3453 = 
> >   _gfortran_shape_4 (, D.3451, D.3453);
> > 
> > There is a third argument D.3453 and its value is 4 (if it's not the KIND,
> > what is it?).
> 
> In this case, the argument _is_ present, so it's not removed in the procedure

Yep, the problem is that _gfortran_shape_4 is declared with both the optional
parameter
and without.  This should not happen.
Ideally gfortran should produce just one declaration per translation unit and
that needs
to include the optional param.

Honza

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-03 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #10 from Dominique d'Humieres  ---
> Created attachment 36902 [details]
> Make the intrinsic procedure declarations less context-dependant
>
>I can't test this right now (bootstrap broken).

Sorry about that. Anything serious?

> It basically unconditionally clears the ignore_optional flag (and removes it).
> So that optional arguments are always passed.

This make LTO happy but causes several regressions on the tests for
(MIN|MAX)(VAL|LOC).

I have looked at the failures for gfortran.dg/scalar_mask_2.f90 and I think
they come from

< _gfortran_smaxloc0_4_r4 (, D.3514, 0B, D.3516);
---
> _gfortran_smaxloc0_4_r4 (, D.3511, );

'<' with the patch '>' without it.

[Bug fortran/68560] [6 Regression] The test gfortran.dg/shape_8.f90 now fails when compiled with -flto

2015-12-03 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68560

--- Comment #8 from Mikael Morin  ---
Created attachment 36902
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=36902=edit
Make the intrinsic procedure declarations less context-dependant

I can't test this right now (bootstrap broken).

It basically unconditionally clears the ignore_optional flag (and removes it).
So that optional arguments are always passed.