Update concepts branch to revision 131834
[official-gcc.git] / gcc / testsuite / gfortran.dg / array_2.f90
blobd182f044a7a5e5b1b869f06ab6a1e2e6f22444fa
1 ! { dg-do run }
2 ! PR tree-optimization/30092
3 ! This caused once an ICE due to internal tree changes
4 program test
5 implicit none
6 integer, parameter :: N = 30
7 real, dimension(N) :: rho, pre, cs
8 real :: gamma
9 gamma = 2.1314
10 rho = 5.0
11 pre = 3.0
12 call EOS(N, rho, pre, cs, gamma)
13 if (abs(CS(1) - sqrt(gamma*pre(1)/rho(1))) > epsilon(cs)) &
14 call abort()
15 contains
16 SUBROUTINE EOS(NODES, DENS, PRES, CS, CGAMMA)
17 IMPLICIT NONE
18 INTEGER NODES
19 REAL CGAMMA
20 REAL, DIMENSION(NODES) :: DENS, PRES, CS
21 REAL, PARAMETER :: RGAS = 8.314
22 CS(:NODES) = SQRT(CGAMMA*PRES(:NODES)/DENS(:NODES))
23 END SUBROUTINE EOS
24 end program test