summaryrefslogtreecommitdiff
path: root/libgomp/testsuite/libgomp.fortran/examples-4/e.55.1.f90
diff options
context:
space:
mode:
Diffstat (limited to 'libgomp/testsuite/libgomp.fortran/examples-4/e.55.1.f90')
-rw-r--r--libgomp/testsuite/libgomp.fortran/examples-4/e.55.1.f9070
1 files changed, 70 insertions, 0 deletions
diff --git a/libgomp/testsuite/libgomp.fortran/examples-4/e.55.1.f90 b/libgomp/testsuite/libgomp.fortran/examples-4/e.55.1.f90
new file mode 100644
index 00000000000..0dd00b4ba8c
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/examples-4/e.55.1.f90
@@ -0,0 +1,70 @@
+! { dg-do run }
+
+module e_55_1_mod
+ integer, parameter :: N = 10000000, CHUNKSZ = 100000
+ real :: Y(N), Z(N)
+end module
+
+subroutine init ()
+ use e_55_1_mod, only : Y, Z, N
+ integer :: i
+ do i = 1, N
+ Y(i) = 0.1 * i
+ Z(i) = Y(i)
+ end do
+end subroutine
+
+subroutine check ()
+ use e_55_1_mod, only : Y, Z, N
+ real :: err
+ real, parameter :: EPS = 0.00001
+ integer :: i
+ do i = 1, N
+ if (Y(i) == 0.0) then
+ err = Z(i)
+ else if (Z(i) == 0.0) then
+ err = Y(i)
+ else
+ err = (Y(i) - Z(i)) / Z(i)
+ end if
+ if (err > EPS .or. err < -EPS) call abort
+ end do
+end subroutine
+
+real function F (z)
+ !$omp declare target
+ real, intent(in) :: z
+ F = -z
+end function
+
+subroutine pipedF ()
+ use e_55_1_mod, only: Z, N, CHUNKSZ
+ integer :: C, i
+ real :: F
+ do C = 1, N, CHUNKSZ
+ !$omp task
+ !$omp target map(Z(C:C+CHUNKSZ-1))
+ !$omp parallel do
+ do i = C, C+CHUNKSZ-1
+ Z(i) = F (Z(i))
+ end do
+ !$omp end target
+ !$omp end task
+ end do
+end subroutine
+
+subroutine pipedF_ref ()
+ use e_55_1_mod, only: Y, N
+ integer :: i
+ real :: F
+ do i = 1, N
+ Y(i) = F (Y(i))
+ end do
+end subroutine
+
+program e_55_1
+ call init ()
+ call pipedF ()
+ call pipedF_ref ()
+ call check ()
+end program