1! { dg-do compile }
2! { dg-options "-O3 -ffast-math" }
3
4! This tests only for compile-time failure, which formerly occurred
5! when statements were emitted out of order, failing verify_ssa.
6
7MODULE xc_cs1
8  INTEGER, PARAMETER :: dp=KIND(0.0D0)
9  REAL(KIND=dp), PARAMETER :: a = 0.04918_dp, &
10                              c = 0.2533_dp, &
11                              d = 0.349_dp
12CONTAINS
13  SUBROUTINE cs1_u_2 ( rho, grho, r13, e_rho_rho, e_rho_ndrho, e_ndrho_ndrho,&
14       npoints, error)
15    REAL(KIND=dp), DIMENSION(*), &
16      INTENT(INOUT)                          :: e_rho_rho, e_rho_ndrho, &
17                                                e_ndrho_ndrho
18    DO ip = 1, npoints
19      IF ( rho(ip) > eps_rho ) THEN
20         oc = 1.0_dp/(r*r*r3*r3 + c*g*g)
21         d2rF4 = c4p*f13*f23*g**4*r3/r * (193*d*r**5*r3*r3+90*d*d*r**5*r3 &
22                 -88*g*g*c*r**3*r3-100*d*d*c*g*g*r*r*r3*r3 &
23                 +104*r**6)*od**3*oc**4
24         e_rho_rho(ip) = e_rho_rho(ip) + d2F1 + d2rF2 + d2F3 + d2rF4
25      END IF
26    END DO
27  END SUBROUTINE cs1_u_2
28END MODULE xc_cs1
29