udr6.f90 1.8 KB

12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970
  1. ! { dg-do run }
  2. module m
  3. interface operator(.add.)
  4. module procedure do_add
  5. end interface
  6. type dt
  7. real :: r = 0.0
  8. end type
  9. contains
  10. elemental function do_add(x, y)
  11. type (dt), intent (in) :: x, y
  12. type (dt) :: do_add
  13. do_add%r = x%r + y%r
  14. end function
  15. elemental subroutine dp_add(x, y)
  16. double precision, intent (inout) :: x
  17. double precision, intent (in) :: y
  18. x = x + y
  19. end subroutine
  20. elemental subroutine dp_init(x)
  21. double precision, intent (out) :: x
  22. x = 0.0
  23. end subroutine
  24. end module
  25. program udr6
  26. use m, only : operator(.add.), dt, dp_add, dp_init
  27. type(dt), allocatable :: xdt(:)
  28. type(dt) :: one
  29. real :: r
  30. integer (kind = 4), allocatable, dimension(:) :: i4
  31. integer (kind = 8), allocatable, dimension(:,:) :: i8
  32. integer :: i
  33. real (kind = 4), allocatable :: r4(:,:)
  34. double precision, allocatable :: dp(:)
  35. !$omp declare reduction(.add.:dt:omp_out=omp_out.add.omp_in)
  36. !$omp declare reduction(foo:integer(4),integer(kind=8),real (kind = 4) &
  37. !$omp & :omp_out = omp_out + omp_in) initializer (omp_priv = 0)
  38. !$omp declare reduction(foo:double precision:dp_add (omp_out, omp_in)) &
  39. !$omp & initializer (dp_init (omp_priv))
  40. one%r = 1.0
  41. allocate (xdt(4), i4 (3), i8(-5:-2,2:3), r4(2:5,1:1), dp(7))
  42. r = 0.0
  43. i4 = 0
  44. i8 = 0
  45. r4 = 0.0
  46. do i = 1, 7
  47. call dp_init (dp(i))
  48. end do
  49. !$omp parallel reduction(.add.: xdt) reduction(+: r) &
  50. !$omp & reduction(foo: i4, i8, r4, dp) private(i)
  51. do i = 1, 4
  52. xdt(i) = xdt(i).add.one
  53. end do
  54. r = r + 1.0
  55. i4 = i4 + 1
  56. i8 = i8 + 1
  57. r4 = r4 + 1.0
  58. do i = 1, 7
  59. call dp_add (dp(i), 1.0d0)
  60. end do
  61. !$omp end parallel
  62. if (any (xdt%r .ne. r)) call abort
  63. if (any (i4.ne.r).or.any(i8.ne.r)) call abort
  64. if (any(r4.ne.r).or.any(dp.ne.r)) call abort
  65. deallocate (xdt, i4, i8, r4, dp)
  66. end program udr6