summaryrefslogtreecommitdiff
path: root/libgomp/testsuite/libgomp.fortran/examples-4/e.53.4.f90
diff options
context:
space:
mode:
authorkyukhin <kyukhin@138bc75d-0d04-0410-961f-82ee72b054a4>2014-11-13 13:56:22 +0000
committerkyukhin <kyukhin@138bc75d-0d04-0410-961f-82ee72b054a4>2014-11-13 13:56:22 +0000
commit235252169de1e457e96d4fcd0e58a2638dc84b67 (patch)
treed2c1d75d58f000bd59c8eac757bb91fc0f5c3b0c /libgomp/testsuite/libgomp.fortran/examples-4/e.53.4.f90
parent38e21583d174a96a85786dd8d63d465e9e9e3391 (diff)
downloadgcc-235252169de1e457e96d4fcd0e58a2638dc84b67.tar.gz
[PATCH 7/7] OpenMP 4.0 offloading infrastructure: testsuite.
libgomp/ * testsuite/lib/libgomp.exp (check_effective_target_offload_device): New. * testsuite/libgomp.c++/c++.exp: Include tests from subdirectories. * testsuite/libgomp.c++/examples-4/e.51.5.C: New test. * testsuite/libgomp.c++/examples-4/e.53.2.C: Ditto. * testsuite/libgomp.c/examples-4/e.50.1.c: Ditto. * testsuite/libgomp.c/examples-4/e.50.2.c: Ditto. * testsuite/libgomp.c/examples-4/e.50.3.c: Ditto. * testsuite/libgomp.c/examples-4/e.50.4.c: Ditto. * testsuite/libgomp.c/examples-4/e.50.5.c: Ditto. * testsuite/libgomp.c/examples-4/e.51.1.c: Ditto. * testsuite/libgomp.c/examples-4/e.51.2.c: Ditto. * testsuite/libgomp.c/examples-4/e.51.3.c: Ditto. * testsuite/libgomp.c/examples-4/e.51.4.c: Ditto. * testsuite/libgomp.c/examples-4/e.51.6.c: Ditto. * testsuite/libgomp.c/examples-4/e.51.7.c: Ditto. * testsuite/libgomp.c/examples-4/e.52.1.c: Ditto. * testsuite/libgomp.c/examples-4/e.52.2.c: Ditto. * testsuite/libgomp.c/examples-4/e.53.1.c: Ditto. * testsuite/libgomp.c/examples-4/e.53.3.c: Ditto. * testsuite/libgomp.c/examples-4/e.53.4.c: Ditto. * testsuite/libgomp.c/examples-4/e.53.5.c: Ditto. * testsuite/libgomp.c/examples-4/e.54.2.c: Ditto. * testsuite/libgomp.c/examples-4/e.54.3.c: Ditto. * testsuite/libgomp.c/examples-4/e.54.4.c: Ditto. * testsuite/libgomp.c/examples-4/e.54.5.c: Ditto. * testsuite/libgomp.c/examples-4/e.54.6.c: Ditto. * testsuite/libgomp.c/examples-4/e.55.1.c: Ditto. * testsuite/libgomp.c/examples-4/e.55.2.c: Ditto. * testsuite/libgomp.c/examples-4/e.56.3.c: Ditto. * testsuite/libgomp.c/examples-4/e.56.4.c: Ditto. * testsuite/libgomp.c/examples-4/e.57.1.c: Ditto. * testsuite/libgomp.c/examples-4/e.57.2.c: Ditto. * testsuite/libgomp.c/examples-4/e.57.3.c: Ditto. * testsuite/libgomp.c/target-7.c: Fix test. * testsuite/libgomp.fortran/examples-4/e.50.1.f90: New test. * testsuite/libgomp.fortran/examples-4/e.50.2.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.50.3.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.50.4.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.50.5.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.51.1.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.51.2.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.51.3.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.51.4.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.51.5.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.51.6.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.51.7.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.52.1.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.52.2.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.53.1.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.53.2.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.53.3.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.53.4.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.53.5.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.54.2.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.54.3.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.54.4.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.54.5.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.54.6.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.55.1.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.55.2.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.56.3.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.56.4.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.57.1.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.57.2.f90: Ditto. * testsuite/libgomp.fortran/examples-4/e.57.3.f90: Ditto. git-svn-id: svn+ssh://gcc.gnu.org/svn/gcc/trunk@217494 138bc75d-0d04-0410-961f-82ee72b054a4
Diffstat (limited to 'libgomp/testsuite/libgomp.fortran/examples-4/e.53.4.f90')
-rw-r--r--libgomp/testsuite/libgomp.fortran/examples-4/e.53.4.f9068
1 files changed, 68 insertions, 0 deletions
diff --git a/libgomp/testsuite/libgomp.fortran/examples-4/e.53.4.f90 b/libgomp/testsuite/libgomp.fortran/examples-4/e.53.4.f90
new file mode 100644
index 00000000000..41d251aae37
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/examples-4/e.53.4.f90
@@ -0,0 +1,68 @@
+! { dg-do run }
+
+module e_53_4_mod
+ !$omp declare target (N, Q)
+ integer, parameter :: N = 10
+ real :: Q(N,N)
+contains
+ real function Pfun (i, k)
+ !$omp declare target
+ integer, intent(in) :: i, k
+ Pfun = (Q(i,k) * Q(k,i))
+ end function
+end module
+
+real function accum (k) result (tmp)
+ use e_53_4_mod
+ integer :: i, k
+ tmp = 0.0e0
+ !$omp target
+ !$omp parallel do reduction(+:tmp)
+ do i = 1, N
+ tmp = tmp + Pfun (k, i)
+ end do
+ !$omp end target
+end function
+
+real function accum_ref (k) result (tmp)
+ use e_53_4_mod
+ integer :: i, k
+ tmp = 0.0e0
+ do i = 1, N
+ tmp = tmp + Pfun (k, i)
+ end do
+end function
+
+subroutine init ()
+ use e_53_4_mod
+ integer :: i, j
+ do i = 1, N
+ do j = 1, N
+ Q(i,j) = 0.001 * i * j
+ end do
+ end do
+end subroutine
+
+subroutine check (a, b)
+ real :: a, b, err
+ real, parameter :: EPS = 0.00001
+ if (b == 0.0) then
+ err = a
+ else if (a == 0.0) then
+ err = b
+ else
+ err = (a - b) / b
+ end if
+ if (err > EPS .or. err < -EPS) call abort
+end subroutine
+
+program e_53_4
+ use e_53_4_mod
+ integer :: i
+ real :: accum, accum_ref
+ call init ()
+ !$omp target update to(Q)
+ do i = 1, N
+ call check (accum (i), accum_ref (i))
+ end do
+end program