Add support for ARMv8-R architecture
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / udr10.f90
blobb64b4f48800c5bcf6c12a2e8addbb690cedd380d
1 ! { dg-do run }
3 module udr10m
4 type dt
5 integer :: x = 0
6 end type
7 !$omp declare reduction(.add.:dt:omp_out=omp_out.add.omp_in)
8 !$omp declare reduction(+:dt:omp_out=omp_out+omp_in)
9 interface operator(+)
10 module procedure addme
11 end interface
12 interface operator(.add.)
13 module procedure addme
14 end interface
15 contains
16 type(dt) function addme (x, y)
17 type (dt), intent (in) :: x, y
18 addme%x = x%x + y%x
19 end function addme
20 end module udr10m
21 program udr10
22 use udr10m, only : operator(.localadd.) => operator(.add.), &
23 & operator(+), dl => dt
24 type(dl) :: j, k
25 integer :: i
26 !$omp parallel do reduction(+:j) reduction(.localadd.:k)
27 do i = 1, 100
28 j = j .localadd. dl(i)
29 k = k + dl(i * 2)
30 end do
31 if (j%x /= 5050 .or. k%x /= 10100) call abort
32 end