aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/libgomp/testsuite/libgomp.fortran/udr10.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc-4.9/libgomp/testsuite/libgomp.fortran/udr10.f90')
-rw-r--r--gcc-4.9/libgomp/testsuite/libgomp.fortran/udr10.f9032
1 files changed, 32 insertions, 0 deletions
diff --git a/gcc-4.9/libgomp/testsuite/libgomp.fortran/udr10.f90 b/gcc-4.9/libgomp/testsuite/libgomp.fortran/udr10.f90
new file mode 100644
index 000000000..b64b4f488
--- /dev/null
+++ b/gcc-4.9/libgomp/testsuite/libgomp.fortran/udr10.f90
@@ -0,0 +1,32 @@
+! { dg-do run }
+
+module udr10m
+ type dt
+ integer :: x = 0
+ end type
+!$omp declare reduction(.add.:dt:omp_out=omp_out.add.omp_in)
+!$omp declare reduction(+:dt:omp_out=omp_out+omp_in)
+ interface operator(+)
+ module procedure addme
+ end interface
+ interface operator(.add.)
+ module procedure addme
+ end interface
+contains
+ type(dt) function addme (x, y)
+ type (dt), intent (in) :: x, y
+ addme%x = x%x + y%x
+ end function addme
+end module udr10m
+program udr10
+ use udr10m, only : operator(.localadd.) => operator(.add.), &
+& operator(+), dl => dt
+ type(dl) :: j, k
+ integer :: i
+!$omp parallel do reduction(+:j) reduction(.localadd.:k)
+ do i = 1, 100
+ j = j .localadd. dl(i)
+ k = k + dl(i * 2)
+ end do
+ if (j%x /= 5050 .or. k%x /= 10100) call abort
+end