1! { dg-do run }
2
3module udr2
4  type dt
5    integer :: x = 7
6    integer :: y = 9
7  end type
8end module udr2
9  use udr2, only : dt
10!$omp declare reduction (foo : integer : omp_out = omp_out + omp_in)
11  integer :: i, j(2:4,3:5)
12!$omp declare reduction (bar : integer : &
13!$omp & omp_out = omp_out + iand (omp_in, -4)) initializer (omp_priv = 3)
14  interface operator (+)
15    function notdefined(x, y)
16      use udr2, only : dt
17      type(dt), intent (in) :: x, y
18      type(dt) :: notdefined
19    end function
20  end interface
21  type (dt) :: d(2:4,3:5)
22!$omp declare reduction (+ : dt : omp_out%x = omp_out%x &
23!$omp & + iand (omp_in%x, -8))
24!$omp declare reduction (foo : dt : omp_out%x = iand (omp_in%x, -8) &
25!$omp & + omp_out%x) initializer (omp_priv = dt (5, 21))
26  j = 0
27!$omp parallel do reduction (foo : j)
28  do i = 1, 100
29    j = j + i
30  end do
31  if (any(j .ne. 5050)) stop 1
32  j = 3
33!$omp parallel do reduction (bar : j)
34  do i = 1, 100
35    j = j + 4 * i
36  end do
37  if (any(j .ne. (5050 * 4 + 3))) stop 2
38!$omp parallel do reduction (+ : d)
39  do i = 1, 100
40    if (any(d%y .ne. 9)) stop 3
41    d%x = d%x + 8 * i
42  end do
43  if (any(d%x .ne. (5050 * 8 + 7)) .or. any(d%y .ne. 9)) stop 4
44  d = dt (5, 21)
45!$omp parallel do reduction (foo : d)
46  do i = 1, 100
47    if (any(d%y .ne. 21)) stop 5
48    d%x = d%x + 8 * i
49  end do
50  if (any(d%x .ne. (5050 * 8 + 5)) .or. any(d%y .ne. 21)) stop 6
51end
52