Add testcases for middle-end/53852 and middle-end/67518

2015-11-06  Joost VandeVondele  <vondele@gnu.gcc.org>

	PR middle-end/53852
	PR middle-end/67518
	* gfortran.dg/PR67518.f90: New test.
	* gfortran.dg/PR53852.f90: New test.

From-SVN: r229839
This commit is contained in:
Joost VandeVondele 2015-11-06 09:51:12 +00:00
parent 8ba66467b9
commit 5c661a4468
3 changed files with 89 additions and 0 deletions

View file

@ -1,3 +1,10 @@
2015-11-06 Joost VandeVondele <vondele@gnu.gcc.org>
PR middle-end/53852
PR middle-end/67518
* gfortran.dg/PR67518.f90: New test.
* gfortran.dg/PR53852.f90: New test.
2015-11-05 Cesar Philippidis <cesar@codesourcery.com>
Tom de Vries <tom@codesourcery.com>
Nathan Sidwell <nathan@codesourcery.com>

View file

@ -0,0 +1,37 @@
! { dg-do compile }
! { dg-options "-floop-nest-optimize -O2 -ffast-math" }
! PR53852 : compile time / memory hog
SUBROUTINE build_d_tensor_gks(d5f,v,d5)
INTEGER, PARAMETER :: dp=8
REAL(KIND=dp), DIMENSION(3, 3, 3, 3, 3), &
INTENT(OUT) :: d5f
REAL(KIND=dp), DIMENSION(3), INTENT(IN) :: v
REAL(KIND=dp), INTENT(IN) :: d5
INTEGER :: k1, k2, k3, k4, k5
REAL(KIND=dp) :: w
d5f = 0.0_dp
DO k1=1,3
DO k2=1,3
DO k3=1,3
DO k4=1,3
DO k5=1,3
d5f(k5,k4,k3,k2,k1)=d5f(k5,k4,k3,k2,k1)+ &
v(k1)*v(k2)*v(k3)*v(k4)*v(k5)*d5
ENDDO
w=v(k1)*v(k2)*v(k3)*d4
d5f(k1,k2,k3,k4,k4)=d5f(k1,k2,k3,k4,k4)+w
d5f(k1,k2,k4,k3,k4)=d5f(k1,k2,k4,k3,k4)+w
d5f(k1,k4,k2,k3,k4)=d5f(k1,k4,k2,k3,k4)+w
d5f(k4,k1,k2,k3,k4)=d5f(k4,k1,k2,k3,k4)+w
d5f(k1,k2,k4,k4,k3)=d5f(k1,k2,k4,k4,k3)+w
d5f(k1,k4,k2,k4,k3)=d5f(k1,k4,k2,k4,k3)+w
d5f(k4,k1,k2,k4,k3)=d5f(k4,k1,k2,k4,k3)+w
d5f(k1,k4,k4,k2,k3)=d5f(k1,k4,k4,k2,k3)+w
d5f(k4,k1,k4,k2,k3)=d5f(k4,k1,k4,k2,k3)+w
d5f(k4,k4,k1,k2,k3)=d5f(k4,k4,k1,k2,k3)+w
ENDDO
ENDDO
ENDDO
ENDDO
END SUBROUTINE build_d_tensor_gks

View file

@ -0,0 +1,45 @@
! { dg-do compile }
! { dg-options "-floop-nest-optimize -O2 -ffast-math" }
! PR67518 : isl: position out of bounds
MODULE ao_util
INTEGER, PARAMETER :: dp=8
CONTAINS
FUNCTION exp_radius(l,alpha,threshold,prefactor,epsin) RESULT(radius)
REAL(KIND=dp), INTENT(IN) :: alpha, threshold, prefactor
REAL(KIND=dp), INTENT(IN), OPTIONAL :: epsin
DO
IF (iter.gt.maxiter) THEN
CALL stop_program(routineN,moduleN,1,"exceeded")
ENDIF
ENDDO
CALL stop_program(routineN,moduleN,1,"exceeded")
END FUNCTION exp_radius
FUNCTION exp_radius_very_extended(la_min,la_max,lb_min,lb_max,pab,o1,o2,ra,rb,rp,&
zetp,eps,prefactor,cutoff,epsin) RESULT(radius)
REAL(KIND=dp), DIMENSION(:, :), &
OPTIONAL, POINTER :: pab
REAL(KIND=dp), INTENT(IN) :: ra(3), rb(3), rp(3), zetp, &
eps, prefactor, cutoff
REAL(KIND=dp) :: bini, binj, coef(0:20), &
epsin_local, polycoef(0:60), &
rad_b, s1, s2
IF (PRESENT(pab)) THEN
ENDIF
DO lxa=0,la_max
DO lxb=0,lb_max
coef(0:la_max+lb_max)=0.0_dp
DO i=0,lxa
DO j=0,lxb
coef(lxa+lxb-i-j)=coef(lxa+lxb-i-j) + bini*binj*s1*s2
ENDDO
ENDDO
DO i=0,lxa+lxb
polycoef(i)=MAX(polycoef(i),coef(i))
ENDDO
ENDDO
ENDDO
DO i=0,la_max+lb_max
radius=MAX(radius,exp_radius(i,zetp,eps,polycoef(i),epsin_local) )
ENDDO
END FUNCTION exp_radius_very_extended
END MODULE ao_util