e.53.5.f90 1.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081
  1. ! { dg-do run { target vect_simd_clones } }
  2. ! { dg-options "-O2" }
  3. ! { dg-additional-options "-msse2" { target sse2_runtime } }
  4. ! { dg-additional-options "-mavx" { target avx_runtime } }
  5. module e_53_5_mod
  6. !$omp declare target (N, Q)
  7. integer, parameter :: N = 10000, M = 1024
  8. real :: Q(N,N)
  9. contains
  10. real function Pfun (k, i)
  11. !$omp declare simd(Pfun) uniform(i) linear(k) notinbranch
  12. !$omp declare target
  13. integer, value, intent(in) :: i, k
  14. Pfun = (Q(k,i) * Q(i,k))
  15. end function
  16. end module
  17. real function accum () result (tmp)
  18. use e_53_5_mod
  19. real :: tmp1
  20. integer :: i
  21. tmp = 0.0e0
  22. !$omp target
  23. !$omp parallel do private(tmp1) reduction(+:tmp)
  24. do i = 1, N
  25. tmp1 = 0.0e0
  26. !$omp simd reduction(+:tmp1)
  27. do k = 1, M
  28. tmp1 = tmp1 + Pfun (k, i)
  29. end do
  30. tmp = tmp + tmp1
  31. end do
  32. !$omp end target
  33. end function
  34. real function accum_ref () result (tmp)
  35. use e_53_5_mod
  36. real :: tmp1
  37. integer :: i
  38. tmp = 0.0e0
  39. do i = 1, N
  40. tmp1 = 0.0e0
  41. do k = 1, M
  42. tmp1 = tmp1 + Pfun (k, i)
  43. end do
  44. tmp = tmp + tmp1
  45. end do
  46. end function
  47. subroutine init ()
  48. use e_53_5_mod
  49. integer :: i, j
  50. do i = 1, N
  51. do j = 1, N
  52. Q(i,j) = 0.001 * i * j
  53. end do
  54. end do
  55. end subroutine
  56. subroutine check (a, b)
  57. real :: a, b, err
  58. real, parameter :: EPS = 0.00001
  59. if (b == 0.0) then
  60. err = a
  61. else if (a == 0.0) then
  62. err = b
  63. else
  64. err = (a - b) / b
  65. end if
  66. if (err > EPS .or. err < -EPS) call abort
  67. end subroutine
  68. program e_53_5
  69. use e_53_5_mod
  70. real :: accum, accum_ref, d
  71. call init ()
  72. !$omp target update to(Q)
  73. call check (accum (), accum_ref ())
  74. end program