Rebase.
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / udr11.f90
blob61fb196105d5057b2e209f5260056527bbadbfd4
1 ! { dg-do run }
3 module udr11
4 type dt
5 integer :: x = 0
6 end type
7 end module udr11
8 use udr11, only : dt
9 !$omp declare reduction(+:dt:omp_out%x=omp_out%x+omp_in%x)
10 !$omp declare reduction(-:dt:omp_out%x=omp_out%x+omp_in%x)
11 !$omp declare reduction(*:dt:omp_out%x=omp_out%x+omp_in%x)
12 !$omp declare reduction(.and.:dt:omp_out%x=omp_out%x+omp_in%x)
13 !$omp declare reduction(.or.:dt:omp_out%x=omp_out%x+3*omp_in%x)
14 !$omp declare reduction(.eqv.:dt:omp_out%x=omp_out%x+omp_in%x)
15 !$omp declare reduction(.neqv.:dt:omp_out%x=omp_out%x+omp_in%x)
16 !$omp declare reduction(min:dt:omp_out%x=omp_out%x+omp_in%x)
17 !$omp declare reduction(max:dt:omp_out%x=omp_out%x+omp_in%x)
18 !$omp declare reduction(iand:dt:omp_out%x=omp_out%x+omp_in%x)
19 !$omp declare reduction(ior:dt:omp_out%x=omp_out%x+omp_in%x)
20 !$omp declare reduction(ieor:dt:omp_out%x=omp_out%x+omp_in%x)
21 interface operator(.and.)
22 function addme1 (x, y)
23 use udr11, only : dt
24 type (dt), intent (in) :: x, y
25 type(dt) :: addme1
26 end function addme1
27 end interface
28 interface operator(.or.)
29 function addme2 (x, y)
30 use udr11, only : dt
31 type (dt), intent (in) :: x, y
32 type(dt) :: addme2
33 end function addme2
34 end interface
35 interface operator(.eqv.)
36 function addme3 (x, y)
37 use udr11, only : dt
38 type (dt), intent (in) :: x, y
39 type(dt) :: addme3
40 end function addme3
41 end interface
42 interface operator(.neqv.)
43 function addme4 (x, y)
44 use udr11, only : dt
45 type (dt), intent (in) :: x, y
46 type(dt) :: addme4
47 end function addme4
48 end interface
49 interface operator(+)
50 function addme5 (x, y)
51 use udr11, only : dt
52 type (dt), intent (in) :: x, y
53 type(dt) :: addme5
54 end function addme5
55 end interface
56 interface operator(-)
57 function addme6 (x, y)
58 use udr11, only : dt
59 type (dt), intent (in) :: x, y
60 type(dt) :: addme6
61 end function addme6
62 end interface
63 interface operator(*)
64 function addme7 (x, y)
65 use udr11, only : dt
66 type (dt), intent (in) :: x, y
67 type(dt) :: addme7
68 end function addme7
69 end interface
70 type(dt) :: j, k, l, m, n, o, p, q, r, s, t, u
71 integer :: i
72 !$omp parallel do reduction(.and.:j) reduction(.or.:k) &
73 !$omp & reduction(.eqv.:l) reduction(.neqv.:m) &
74 !$omp & reduction(min:n) reduction(max:o) &
75 !$omp & reduction(iand:p) reduction(ior:q) reduction (ieor:r) &
76 !$omp & reduction(+:s) reduction(-:t) reduction(*:u)
77 do i = 1, 100
78 j%x = j%x + i
79 k%x = k%x + 2 * i
80 l%x = l%x + 3 * i
81 m%x = m%x + i
82 n%x = n%x + 2 * i
83 o%x = o%x + 3 * i
84 p%x = p%x + i
85 q%x = q%x + 2 * i
86 r%x = r%x + 3 * i
87 s%x = s%x + i
88 t%x = t%x + 2 * i
89 u%x = u%x + 3 * i
90 end do
91 if (j%x /= 5050 .or. k%x /= 30300 .or. l%x /= 15150) call abort
92 if (m%x /= 5050 .or. n%x /= 10100 .or. o%x /= 15150) call abort
93 if (p%x /= 5050 .or. q%x /= 10100 .or. r%x /= 15150) call abort
94 if (s%x /= 5050 .or. t%x /= 10100 .or. u%x /= 15150) call abort
95 end