summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/array_2.f90
diff options
context:
space:
mode:
authorLorry <lorry@roadtrain.codethink.co.uk>2012-01-09 13:47:42 +0000
committerLorry <lorry@roadtrain.codethink.co.uk>2012-01-09 13:47:42 +0000
commitb4a5df67f1382a33f4535eb1b10600ca52d294d3 (patch)
treed4571b191c2cfc0f5045bd27b54f8a48e70787a8 /gcc/testsuite/gfortran.dg/array_2.f90
downloadgcc-tarball-b4a5df67f1382a33f4535eb1b10600ca52d294d3.tar.gz
Tarball conversion
Diffstat (limited to 'gcc/testsuite/gfortran.dg/array_2.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/array_2.f9024
1 files changed, 24 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/array_2.f90 b/gcc/testsuite/gfortran.dg/array_2.f90
new file mode 100644
index 0000000000..d182f044a7
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/array_2.f90
@@ -0,0 +1,24 @@
+! { dg-do run }
+! PR tree-optimization/30092
+! This caused once an ICE due to internal 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