This is the mail archive of the gcc-patches@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

[patch,fortran] Add test to gfortran.dg (gave an ICE with -ftree-optimize) (PR30092)


This test case makes probably only sense with -ftree-optimize one SSE
systems. Assuming that Tobias S.'s patch -ftree-optimize will be checked
in, I left out any dg-options.

When gimple was changed, this broke the sqrt(:) vectorization on AMD64.

As suggested by Thomas:
"could write this into a test case for gfortran.dg? If it broke once, we
should at make sure it doesn't break again."

Tobias

2006-12-08  Tobias Burnus  <burnus@net-b.de>

    * gfortran.dg/array_2.f90: Added sqrt test.
Index: gcc/testsuite/gfortran.dg/do_3.f90
===================================================================
--- gcc/testsuite/gfortran.dg/array_2.f90	(Revision 0)
+++ gcc/testsuite/gfortran.dg/array_2.f90	(Revision 0)
@@ -0,0 +1,24 @@
+! { dg-do run }
+! PR tree-optimization/30092
+! This caused once an ICE due to tree changes
+program test
+  implicit none
+  integer, parameter :: N = 30
+  real, dimension(N) :: rho, pre, cs
+  real               :: gamma
+  gamma = 2.1314
+  rho = 5.0
+  pre = 3.0
+  call EOS(N, rho, pre, cs, gamma)
+  if (abs(CS(1) - sqrt(gamma*pre(1)/rho(1))) > epsilon(cs)) &
+     call abort()
+contains
+      SUBROUTINE EOS(NODES, DENS, PRES, CS, CGAMMA)
+      IMPLICIT NONE
+      INTEGER NODES
+      REAL CGAMMA
+      REAL, DIMENSION(NODES) :: DENS, PRES, CS
+      REAL, PARAMETER :: RGAS = 8.314
+      CS(:NODES) = SQRT(CGAMMA*PRES(:NODES)/DENS(:NODES))
+      END SUBROUTINE EOS
+end program test

Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]