gcc/libgomp/testsuite/libgomp.fortran/target-simd.f90
Tobias Burnus 01509e2f04 libgomp/testsuite – use 'stop' and 'dg-do run'
libgomp/
        * testsuite/libgomp.fortran/target-simd.f90: Use stop not abort.
        * testsuite/libgomp.fortran/use_device_ptr-optional-1.f90:
        Ditto; add 'dg-do run' for torture testing.
        * testsuite/libgomp.fortran/lastprivate1.f90:  Add 'dg-do run'.
        * testsuite/libgomp.fortran/lastprivate2.f90: Ditto.
        * testsuite/libgomp.fortran/nestedfn4.f90: Ditto.
        * testsuite/libgomp.fortran/pr25219.f90: Ditto.
        * testsuite/libgomp.fortran/pr28390.f: Ditto.
        * testsuite/libgomp.fortran/pr35130.f90: Ditto.
        * testsuite/libgomp.fortran/pr90779.f90: Ditto.
        * testsuite/libgomp.fortran/task2.f90: Ditto.
        * testsuite/libgomp.fortran/taskgroup1.f90: Ditto.
        * testsuite/libgomp.fortran/taskloop1.f90: Ditto.
        * testsuite/libgomp.fortran/use_device_addr-1.f90: Ditto.
        * testsuite/libgomp.fortran/use_device_addr-2.f90: Ditto.
        * testsuite/libgomp.fortran/workshare1.f90: Ditto.
        * testsuite/libgomp.fortran/workshare2.f90: Ditto.

From-SVN: r277606
2019-10-30 11:33:58 +01:00

27 lines
479 B
Fortran

! { dg-do run }
program test
implicit none
real, allocatable :: a(:), b(:)
integer :: i
a = [(i, i = 1, 100)]
allocate(b, mold=a)
b = 0
!$omp target simd map(to:a) map(from:b)
do i = 1, size(a)
b(i) = 5.0 * a(i)
end do
if (any (b - 5.0 *a > 10.0*epsilon(a))) stop 1
!$omp target simd map(to:a) map(from:b)
do i = 1, size(a)
b(i) = 2.0 * a(i)
end do
!$omp end target simd
if (any (b - 2.0 *a > 10.0*epsilon(a))) stop 2
end program test