[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2013-01-09 Thread richard.guenther at gmail dot com


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716



--- Comment #49 from richard.guenther at gmail dot com  2013-01-09 08:52:21 UTC ---

On Tue, Jan 8, 2013 at 8:52 PM, dominiq at lps dot ens.fr

 wrote:

>

> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

>

> --- Comment #48 from Dominique d'Humieres  
> 2013-01-08 19:52:39 UTC ---

> From comment #40:

>

>> with -ffast-math, so for example

>>

>>   if (x != 0)

>> tem = y / x;

>>   else

>> tem = 0.;

>>   ... do sth with tem ...

>>

>> will execute y / x unconditionally based on the fact that it cannot trap.

>

> This optimization generates an exception trapped when using -ffpe-trap=invalid

> along with -ffast-math.

> This unfortunately prevents any debugging based -ffpe-trap=invalid for

> miscompilations occurring with -ffast-math.



Well - that's maybe unfortunate but expected.  You can't have both ;)



> One thing I hope, though I am not

> sure about it, is that the above block is still compiled as

>

> tem=y/x

> if (x==0) tem=0.



Yes, it's basically turned into an unconditional divide plus a conditional move

based on the fact that we cannot vectorize non-straight-line-code (so

it's really

only a vectorization enabler).



> My original report was for '-O3 -funsafe-math-optimizations 
> -ffinite-math-only'

> without -ffpe-trap=invalid. The segmentation fault resulted from the fact that

> some variables were used to access a table and were out of bound when the

> miscompilation generated some NAN (see comment #13).



Yes, that's another common issue - with FP indexing even slight

rounding differences can cause bogus accesses (consider producing

a[0.99] instead of a[1.0]).  That mostly happens with FP loop induction

variables that are also used for indexing (a really bad practice the frontend

should warn about - at least when -funsafe-math-optimizations is in effect).



Richard.



> --

> Configure bugmail: http://gcc.gnu.org/bugzilla/userprefs.cgi?tab=email

> --- You are receiving this mail because: ---

> You are on the CC list for the bug.


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2013-01-08 Thread dominiq at lps dot ens.fr


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716



--- Comment #48 from Dominique d'Humieres  
2013-01-08 19:52:39 UTC ---

>From comment #40:



> with -ffast-math, so for example

>

>   if (x != 0)

> tem = y / x;

>   else

> tem = 0.;

>   ... do sth with tem ...

>

> will execute y / x unconditionally based on the fact that it cannot trap.



This optimization generates an exception trapped when using -ffpe-trap=invalid

along with -ffast-math.

This unfortunately prevents any debugging based -ffpe-trap=invalid for

miscompilations occurring with -ffast-math. One thing I hope, though I am not

sure about it, is that the above block is still compiled as



tem=y/x

if (x==0) tem=0.



My original report was for '-O3 -funsafe-math-optimizations -ffinite-math-only'

without -ffpe-trap=invalid. The segmentation fault resulted from the fact that

some variables were used to access a table and were out of bound when the

miscompilation generated some NAN (see comment #13).


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2013-01-08 Thread ubizjak at gmail dot com


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716



--- Comment #47 from Uros Bizjak  2013-01-08 19:23:41 
UTC ---

(In reply to comment #44)

> Can't reproduce on x86_64-linux with current trunk at -O3 -g -ffast-math, both

> with LRA and when LRA is disabled.  From what I understood, this bug used to 
> be

> present on darwin, but went away two years ago, then it got reopened for

> x86_64-linux in July and apparently doesn't reproduce anymore either.  So, is

> this broken anywhere now?



Sorry for late answer, the NaN is still generated with current mainline, as can

be proved with:



"-g -O3 -ffast-math -ffpe-trap=invalid"



$ ./a.out

 MAIN : FIN S2

 MAIN : FIN S1

 MAIN : FIN S00011

 MAIN : FIN S00022



Program received signal SIGFPE: Floating-point exception - erroneous arithmetic

operation.



Backtrace for this error:

#0  0x7F9A9AF66FD7

#1  0x7F9A9AF675A4

#2  0x346B2359AF

#3  0x40AAA6 in s00017_ at doduc.f90:1852

#4  0x41B9E9 in MAIN__ at doduc.f90:186

Floating point exception



*However*, --ffast-math implies -fno-signaling-nans, and this contradicts with

-ffpe-trap=invalid.



Going a bit further:



"-g -O3 -ffast-math -fsignaling-nans -ffpe-trap=invalid"



works as expected, without FP exceptions.



So, as far as I'm concerned, "--fast-math -ffpe-trap=invalid" combination of

options (and the whole issue with NaNs on x86_64 as dubiously raised in comment

#34) is invalid.


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2013-01-08 Thread dominiq at lps dot ens.fr


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716



Dominique d'Humieres  changed:



   What|Removed |Added



 Status|WAITING |RESOLVED

 Resolution||WORKSFORME



--- Comment #46 from Dominique d'Humieres  
2013-01-08 18:25:29 UTC ---

Let me close this PR as WORKSFORME. If the problem resurface, please open a new

PR.


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-12-18 Thread jakub at gcc dot gnu.org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716



--- Comment #45 from Jakub Jelinek  2012-12-18 
10:23:59 UTC ---

I've bisected this and the bug went away (or has gone latent) with

http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=189915

There is a huge number of changes in *.optimized dumps, mainly D.N DECL_UID

numbers but also SSA_NAME versions, if I abstract from those, the only real

change is in a comparison:

-  x_15 = MIN_EXPR ;

+  x_382 = MIN_EXPR ;

...

-  x_89 = MIN_EXPR ;

+  x_95 = MIN_EXPR ;

   x_320 = aaa11.v0011;

-  x_384 = MAX_EXPR ;

-  aaa13.dt = x_384;

-  if (prephitmp.1593_1033 > 2)

+  x_15 = MAX_EXPR ;

+  aaa13.dt = x_15;

+  if (prephitmp.1593_1034 > 2)

...

   :

-  if (x_342 < x_384)

+  if (x_15 > x_342)



(x_342 is the same thing in both cases, the < vs. > is probably the result of

canonicalizing the comparison based on SSA_NAME versions).

Anyway, is it really worth it to have this open as P1 on questionable testcase

(well, questionable is mainly whether the testcase doesn't assume IEEE 754

semantics to make -ffast-math invalid for it) where the problem is just latent

(and unclear whether it is a compiler issue at all)?


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-12-18 Thread jakub at gcc dot gnu.org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716



Jakub Jelinek  changed:



   What|Removed |Added



 CC||jakub at gcc dot gnu.org



--- Comment #44 from Jakub Jelinek  2012-12-18 
09:14:13 UTC ---

Can't reproduce on x86_64-linux with current trunk at -O3 -g -ffast-math, both

with LRA and when LRA is disabled.  From what I understood, this bug used to be

present on darwin, but went away two years ago, then it got reopened for

x86_64-linux in July and apparently doesn't reproduce anymore either.  So, is

this broken anywhere now?


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-12-07 Thread rguenth at gcc dot gnu.org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716



--- Comment #43 from Richard Biener  2012-12-07 
14:28:56 UTC ---

(In reply to comment #42)

> > Re-adjust target milestone.  Please somebody revisit the regression status

> > and fill in known-to-work/fail fields.  ISTR it only fails on darwin.

> 

> (1) doduc.f90 is correctly compiled on x86_64-apple-darwin10 (r194291) with 
> the

> options I have tried (typically -fprotect-parens -Ofast -funroll-loops

> -ftree-loop-linear -fomit-frame-pointer -fwhole-program -flto, no valgrind

> error with -O3 -ffast-math, no error with -fsanitize=address).

> 

> (2) Per comment #30, this PR has been reopened for x86_64-unknown-linux-gnu.

> 

> (3) Per comment #40:

> 

> > tree if-conversion happily executes both arms of the conditional

> > unconditionally with -ffast-math, ...

> 

> so compiling with -ffpe-trap=invalid traps for results discarded later.



-ffpe-trap=invalid -ffast-math is a non-sensical flag combination.  You

tell the compiler nothing will ever trap and then enable traps!  So seeing

errors with that tells you nothing ...


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-12-07 Thread dominiq at lps dot ens.fr


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716



--- Comment #42 from Dominique d'Humieres  
2012-12-07 13:40:17 UTC ---

> Re-adjust target milestone.  Please somebody revisit the regression status

> and fill in known-to-work/fail fields.  ISTR it only fails on darwin.



(1) doduc.f90 is correctly compiled on x86_64-apple-darwin10 (r194291) with the

options I have tried (typically -fprotect-parens -Ofast -funroll-loops

-ftree-loop-linear -fomit-frame-pointer -fwhole-program -flto, no valgrind

error with -O3 -ffast-math, no error with -fsanitize=address).



(2) Per comment #30, this PR has been reopened for x86_64-unknown-linux-gnu.



(3) Per comment #40:



> tree if-conversion happily executes both arms of the conditional

> unconditionally with -ffast-math, ...



so compiling with -ffpe-trap=invalid traps for results discarded later.


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-12-07 Thread rguenth at gcc dot gnu.org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716



Richard Biener  changed:



   What|Removed |Added



 Status|REOPENED|WAITING

   Target Milestone|4.6.0   |4.6.4



--- Comment #41 from Richard Biener  2012-12-07 
09:21:12 UTC ---

Re-adjust target milestone.  Please somebody revisit the regression status

and fill in known-to-work/fail fields.  ISTR it only fails on darwin.


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-07-23 Thread rguenth at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

--- Comment #40 from Richard Guenther  2012-07-23 
08:12:55 UTC ---
tree if-conversion happily executes both arms of the conditional
unconditionally
with -ffast-math, so for example

  if (x != 0)
tem = y / x;
  else
tem = 0.;
  ... do sth with tem ...

will execute y / x unconditionally based on the fact that it cannot trap.
So simply generation of NaNs is not what you should check for, but
"usage" of 'tem' with NaN in the above should be (it shouldn't be used
if x is zero).


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-07-22 Thread dominiq at lps dot ens.fr
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

--- Comment #39 from Dominique d'Humieres  
2012-07-22 10:47:42 UTC ---
> If I compile with -fno-tree-loop-if-convert the exception occurs 
> somewhere else:

It occurs in s00018 in the loop between lines 3782 to 3796

 DO j = 1 , n1
dtpar = V0012
IF ( i.EQ.NIV .AND. j.EQ.ISLni ) THEN
   k1 = 2
   DO k = 1 , k1
  dtpa = V0012
  IF ( DABS(DTMi(k)).GT.eps )   &
 & dtpa = 2.*sens*DABS(TMI(k)/DTMi(k))
  dtpar = DMIN1(dtpar,dtpa)
   ENDDO
ELSEIF ( DABS(DTGai(i,j)).GT.eps ) THEN
   dtpar = sens*DABS(TGAi(i,j)/DTGai(i,j))
ENDIF
DTTemp = DMIN1(DTTemp,dtpar)
 ENDDO

Before the loop i=2, n1=2, NIV=0, ISLni=0, eps=1.0e-8, sens=0.01,
DTTemp=0.05, DTGai(2,1)=3.4750524086054519, DTGai(2,2)=2.8245839253949421,
TGAi(2,1)=905.00, and TGAi(2,1)=1040.0.  So
(i.EQ.NIV .AND. j.EQ.ISLni) is false, DTGai(2,:)>eps and dtpar>20.0>DTTemp,
hence the loop does nothing and should not generate any "Floating-point
exception" as it does.

If I read correctly the assembly bellow, the loop

   k1 = 2
   DO k = 1 , k1
  dtpa = V0012
  IF ( DABS(DTMi(k)).GT.eps )   &
 & dtpa = 2.*sens*DABS(TMI(k)/DTMi(k))
  dtpar = DMIN1(dtpar,dtpa)
   ENDDO

is unrolled and moved outside the 'DO j = 1 , n1' loop when s00018.f90 is 
compiled with -O2 -ffpe-trap=invalid -fno-trapping-math. The worst part of 
the optimization and the cause of the floating-point exception seems that 
the test 'IF ( DABS(DTMi(k)).GT.eps )' is removed (or delayed, even if I
replace eps 
with 1.0) while both TMI and DTMI are filled with zeroes.

Note that if I replace

  IF ( DABS(DTMi(k)).GT.eps )   &
 & dtpa = 2.*sens*DABS(TMI(k)/DTMi(k))

with

  dtpa = 2.*sens*DABS(TMI(k))/max(DABS(DTMi(k)),eps)

there is no exception.

IMO computing TMI(k)/DTMi(k) without the IF is over-agressive: if
DABS(DTMi(k)).LT.eps, dtpa will have to be recomputed. In addition, if the 
k loop is moved outside the j loop, it should at least protected by 
IF ( i.EQ.NIV), or better by
IF ( i.EQ.NIV .AND. ISLni.GE.1 .AND. ISLni.LE.n1).
Also since the ELSEIF depends on j and the IF is taken at most once,
moving the k loop outside the j loop seems dubious.

Note that the exception is (should be) harmless as it occurs in a dead 
branch.

L29:
movl36404(%r9,%rdi,4), %ecx# aaa77.nasl, n1
movsd%xmm9, 936(%r11)# x, aaa11.dtphy
movsd856(%r11), %xmm8# aaa11.v22202, sens
movl$1, 396(%rsp)#, j
testl%ecx, %ecx# n1
jleL41#,
movsd19416(%r9), %xmm7# aaa77.dtmi, D.2813
movapd%xmm8, %xmm11# sens, D.2817
movl$0, %edx#, tmp908
movsd19400(%r9), %xmm0# aaa77.tmi, x
addsd%xmm8, %xmm11# sens, D.2817
movapd%xmm7, %xmm10# D.2813, D.2814
movq_aaa13_@GOTPCREL(%rip), %rax#,
divsd%xmm7, %xmm0# D.2813, x
andpd%xmm1, %xmm10# tmp1323, D.2814
movsd19424(%r9), %xmm12# aaa77.dtmi, D.2813
movsd19408(%r9), %xmm7# aaa77.tmi, x
movsd944(%r11), %xmm6# aaa11.dttemp, x
movl240(%rax), %esi# aaa13.niv, pretmp.160
movl244(%rax), %r14d# aaa13.islni, D.2806
xorl%eax, %eax# pretmp.165
divsd%xmm12, %xmm7# D.2813, x
andpd%xmm1, %xmm0# tmp1323, x
mulsd%xmm11, %xmm0# D.2817, x
ucomisd%xmm0, %xmm2# x, x
seta%al#, pretmp.165
ucomisd%xmm3, %xmm10# tmp1324, D.2814
cmovbe%edx, %eax# pretmp.165,, tmp908, pretmp.165
xorl%edx, %edx#
ucomisd%xmm2, %xmm2# x, x
setp%dl#,
addl$1, %ecx#,
movl%ecx, 12(%rsp)#, %sfp
xorl%ecx, %ecx#
movl%edx, 336(%rsp)#, %sfp
leaq30032(%r9,%rdi,8), %rdx#, ivtmp.264
andpd%xmm1, %xmm7# tmp1323, x
mulsd%xmm11, %xmm7# D.2817, x
movapd%xmm3, %xmm11# tmp1324,
cmpltsd%xmm10, %xmm11#, D.2814,
movapd%xmm11, %xmm10#, tmp923
andpd%xmm11, %xmm0# tmp923, tmp924
movapd%xmm2, %xmm11# x, x
andnpd%xmm2, %xmm10# x, tmp921
orpd%xmm0, %xmm10# tmp924, tmp921
ucomisd%xmm10, %xmm10# tmp921, tmp921
setp%cl#,
orl336(%rsp), %eax# %sfp, pretmp.165
movl%ecx, 364(%rsp)#, %sfp
movl%eax, 336(%rsp)# pretmp.165, %sfp
jeL34#,
movapd%xmm10, %xmm11# tmp921, x
L34:
movapd%xmm3, %xmm0# tmp1324,
andpd%xmm1, %xmm12# tmp1323, D.2814
xorl%eax, %eax#
cmpltsd%xmm12, %xmm0#, D.2814,
movapd%xmm1, %xmm10# tmp1323, tmp1385
movl12(%rsp

[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-07-21 Thread dominiq at lps dot ens.fr
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

--- Comment #38 from Dominique d'Humieres  
2012-07-21 14:43:10 UTC ---
> No, the first NaN was born exactly at this instruction.  Please note 0 / 0
> which is the definition of NaN.

AFAIU the loop around line 1852, the only possibility for 0/0 is yy==qsec==0,
but since 0.1<=y, the line 1852 should not be accessed.

If I compile doduc.f90 with '-O3 -ffast-math -ffpe-trap=invalid' I get the
"Floating-point exception" with trunk and 4.4. If I compile with
-fno-tree-loop-if-convert the exception occurs somewhere else:

#3  0x1306e
#4  0x10001d17c
#5  0x10001eca8

versus

#3  0x1a863
#4  0x10001d11e
#5  0x10001ec98

!-(poor backtrace on darwin).


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-07-21 Thread ubizjak at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

--- Comment #37 from Uros Bizjak  2012-07-21 13:51:59 
UTC ---
(In reply to comment #36)
> > To me, it looks like invalid test. Any fortraners here to share their 
> > opinion?
> 
> Please read comments #23 and #24. One problem with NaN is that they propagate
> until something trap them. When did you get a successful compilation?

No, the first NaN was born exactly at this instruction.  Please note 0 / 0
which is the definition of NaN.


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-07-21 Thread dominiq at lps dot ens.fr
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

--- Comment #36 from Dominique d'Humieres  
2012-07-21 13:40:09 UTC ---
> To me, it looks like invalid test. Any fortraners here to share their opinion?

Please read comments #23 and #24. One problem with NaN is that they propagate
until something trap them. When did you get a successful compilation?


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-07-21 Thread ubizjak at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

--- Comment #35 from Uros Bizjak  2012-07-21 12:35:17 
UTC ---
Actually, exception happens at:

Starting program: /home/uros/pb11/lin/source/a.out 
 MAIN : FIN S2
 MAIN : FIN S1
 MAIN : FIN S00011
 MAIN : FIN S00022

Program received signal SIGFPE, Arithmetic exception.
s00017 () at doduc.f90:1852
1852 IF ( yy.GE.y ) qsec = qsec*y/yy

(gdb) bt
#0  s00017 () at doduc.f90:1852
#1  0x0041ba3a in doduc () at doduc.f90:186
#2  0x00400ba7 in main (argc=argc@entry=1, argv=0x7fffe163) at
doduc.f90:199
#3  0x003c02e21735 in __libc_start_main (main=0x400b80 , argc=1,
ubp_av=0x7fffdde8, init=, 
fini=, rtld_fini=, stack_end=0x7fffddd8)
at libc-start.c:226
#4  0x00400bd1 in _start ()

(gdb) disass $pc-20,+30
Dump of assembler code from 0x40a1f4 to 0x40a212:
   0x0040a1f4 :   push   %rsp
   0x0040a1f5 :   fisub  0x41(%rsi)
   0x0040a1f8 :   mulps  %xmm1,%xmm0
   0x0040a1fb :   maxpd  %xmm7,%xmm0
   0x0040a1ff :   mulpd  %xmm0,%xmm1
   0x0040a203 :   cmplepd %xmm3,%xmm0
=> 0x0040a208 :   divpd  %xmm3,%xmm1
   0x0040a20c :   andpd  %xmm0,%xmm1
   0x0040a210 :   andnpd %xmm2,%xmm0
End of assembler dump.

(gdb) i r xmm3 xmm1
xmm3   ( (0x0, 0x0, 0x0, 0x2), (0x0, 0x6), (0x0, 0x0, 0x0, 0x0, 0x0,
0x0, 0x0, 0x0, 0xc4, 0x6b, 0x1b, 0xef, 0xc0, 0x60, 0x1b, 0x40), (0x0, 0x0, 0x0,
0x0, 0x6bc4, 0xef1b, 0x60c0, 0x401b), (0x0, 0x0, 0xef1b6bc4, 0x401b60c0), (0x0,
0x401b60c0ef1b6bc4), 0x401b60c0ef1b6bc4 )
xmm1   ( (0x0, 0x0, 0x0, 0xfffe), (0x0, 0xfffe), (0x0,
0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0xea, 0x1e, 0x50, 0xb1, 0x21, 0xbd, 0x2,
0xc0), (0x0, 0x0, 0x0, 0x0, 0x1eea, 0xb150, 0xbd21, 0xc002), (0x0, 0x0,
0xb1501eea, 0xc002bd21), (0x0, 0xc002bd21b1501eea),
0xc002bd21b1501eea )


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-07-21 Thread ubizjak at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

--- Comment #34 from Uros Bizjak  2012-07-21 12:16:42 
UTC ---
Maybe no problem with gcc at all:

Compile doduc.f90 with -g -O3 -ffast-math -ffpe-trap=invalid

Starting program: /home/uros/pb11/lin/source/a.out 
 MAIN : FIN S2
 MAIN : FIN S1
 MAIN : FIN S00011
 MAIN : FIN S00022

Program received signal SIGFPE, Arithmetic exception.
0x00402a71 in s00018 (i12=0, i21=0, iorg=0) at doduc.f90:3789
3789 & dtpa = 2.*sens*DABS(TMI(k)/DTMi(k))

(gdb) disass

   0x00402a4f <+431>:   movsd  0x229e61(%rip),%xmm3# 0x62c8b8

   0x00402a57 <+439>:   movsd  %xmm3,0x100(%rsp)
   0x00402a60 <+448>:   movsd  0x21c790(%rip),%xmm3# 0x61f1f8

   0x00402a68 <+456>:   movsd  0x100(%rsp),%xmm6
=> 0x00402a71 <+465>:   divsd  %xmm3,%xmm0
   0x00402a75 <+469>:   addsd  %xmm6,%xmm6
   0x00402a79 <+473>:   andpd  %xmm1,%xmm3
   0x00402a7d <+477>:   andpd  %xmm1,%xmm0

(gdb) i r xmm3 xmm0

xmm3 0
xmm0 0

To me, it looks like invalid test. Any fortraners here to share their opinion?


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-07-21 Thread ubizjak at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

--- Comment #33 from Uros Bizjak  2012-07-21 11:31:18 
UTC ---
The NaN is generated as a mask for DFmode ABS_EXPR:

(insn 124 123 125 (set (reg:V2DF 508)
(mem/u/c:V2DF (symbol_ref/u:DI ("*.LC13") [flags 0x2]) [5 S16 A128]))
doduc.f90:5376 -1
 (expr_list:REG_EQUAL (const_vector:V2DF [
(const_double:DF +QNaN [+QNaN])
(const_double:DF 0.0 [0x0.0p+0])
])
(nil)))

or V2DFmode ABS_EXPR:

(insn 1648 1647 1649 (set (reg:V2DF 4657)
(mem/u/c:V2DF (symbol_ref/u:DI ("*.LC138") [flags 0x2]) [5 S16 A128]))
doduc.f90:1851 -1
 (expr_list:REG_EQUAL (const_vector:V2DF [
(const_double:DF +QNaN [+QNaN])
(const_double:DF +QNaN [+QNaN])
])
(nil)))

Probably, some mixup happens somewhere in RTL optimization passes.


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-07-21 Thread ubizjak at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

--- Comment #32 from Uros Bizjak  2012-07-21 10:49:31 
UTC ---
gcc version 4.8.0 20120720 (experimental) [trunk revision 189718] (GCC)

==2822== Memcheck, a memory error detector
==2822== Copyright (C) 2002-2011, and GNU GPL'd, by Julian Seward et al.
==2822== Using Valgrind-3.7.0 and LibVEX; rerun with -h for copyright info
==2822== Command: ./a.out
==2822== 
 MAIN : FIN S2
 MAIN : FIN S1
 MAIN : FIN S00011
 MAIN : FIN S00022
 TEMPS = 33. , NITERA :  1
 TEMPS = 34.00031044 , NITERA :186
 TEMPS = 35.00497388 , NITERA :955
 TEMPS = 36.7615 , NITERA :   1512
 TEMPS = 37.00012624 , NITERA :   1765
 TEMPS = 38.00060760 , NITERA :   2044
 TEMPS = 39.00312223 , NITERA :   2327
 TEMPS = 40.00168143 , NITERA :   2607
 TEMPS = 45.00187475 , NITERA :   4017
 TEMPS = 50.00261983 , NITERA :   5492
 TEMPS = 55.00263522 , NITERA :   6981
 TEMPS = 60.00087007 , NITERA :   8679
==2822== Invalid read of size 8
==2822==at 0x4040E8: s00061_ (doduc.f90:568)
==2822==by 0x412AD3: s00013_ (doduc.f90:1150)
==2822==by 0x41B9D4: MAIN__ (doduc.f90:182)
==2822==by 0x400B4C: main (doduc.f90:199)
==2822==  Address 0x3fefff770 is not stack'd, malloc'd or (recently) free'd
==2822==

I can reproduce it here with Rev. 189737; it also crashes without running
valgrind.

It crashes (on x86-64 openSUSE Factory) with
  -O3 -ffast-math [-g]

It does not crash with either of the following added:
  -fno-fast-math
  -fno-inline-functions
  -fno-predictive-commoning
  -fno-tree-vectorize

  -fno-protect-parens  (implied by -Ofast)

Nor does it crash with:
  -O2 -ftree-vectorize -finline-functions -ffpredictive-commoning -ffast-math
  -m32 -O3 -ffast-math


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-07-21 Thread ubizjak at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

Uros Bizjak  changed:

   What|Removed |Added

 CC||ubizjak at gmail dot com

--- Comment #31 from Uros Bizjak  2012-07-21 10:44:26 
UTC ---
*** Bug 54034 has been marked as a duplicate of this bug. ***


[Bug tree-optimization/43716] [4.6/4.7/4.8 Regression] Revision 158105 miscompiles doduc.f90

2012-07-21 Thread ubizjak at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43716

Uros Bizjak  changed:

   What|Removed |Added

 Status|RESOLVED|REOPENED
 Resolution|FIXED   |
Summary|[4.6 Regression] Revision   |[4.6/4.7/4.8 Regression]
   |158105 miscompiles  |Revision 158105 miscompiles
   |doduc.f90   |doduc.f90

--- Comment #30 from Uros Bizjak  2012-07-21 10:42:22 
UTC ---
This still happens with:

gcc version 4.8.0 20120720 (experimental) [trunk revision 189718] (GCC)

on x86_64-unknown-linux-gnu.