diff options
Diffstat (limited to 'libgomp/testsuite/libgomp.fortran/allocatable1.f90')
-rw-r--r-- | libgomp/testsuite/libgomp.fortran/allocatable1.f90 | 20 |
1 files changed, 10 insertions, 10 deletions
diff --git a/libgomp/testsuite/libgomp.fortran/allocatable1.f90 b/libgomp/testsuite/libgomp.fortran/allocatable1.f90 index 1efe2ab..b9fd2ee 100644 --- a/libgomp/testsuite/libgomp.fortran/allocatable1.f90 +++ b/libgomp/testsuite/libgomp.fortran/allocatable1.f90 @@ -7,7 +7,7 @@ logical :: k, l b(:, :) = 16 l = .false. - if (allocated (a)) call abort + if (allocated (a)) STOP 1 !$omp parallel private (a, b) reduction (.or.:l) l = l.or.allocated (a) allocate (a(3, 6)) @@ -18,18 +18,18 @@ deallocate (a) l = l.or.allocated (a) !$omp end parallel - if (allocated (a).or.l) call abort + if (allocated (a).or.l) STOP 2 allocate (a(6, 3)) a(:, :) = 3 - if (.not.allocated (a)) call abort + if (.not.allocated (a)) STOP 3 l = l.or.size(a).ne.18.or.size(a,1).ne.6.or.size(a,2).ne.3 - if (l) call abort + if (l) STOP 4 !$omp parallel private (a, b) reduction (.or.:l) l = l.or..not.allocated (a) a(3, 2) = 1 b(3, 2) = 1 !$omp end parallel - if (l.or..not.allocated (a)) call abort + if (l.or..not.allocated (a)) STOP 5 !$omp parallel firstprivate (a, b) reduction (.or.:l) l = l.or..not.allocated (a) l = l.or.size(a).ne.18.or.size(a,1).ne.6.or.size(a,2).ne.3 @@ -41,7 +41,7 @@ a(:, :) = omp_get_thread_num () b(:, :) = omp_get_thread_num () !$omp end parallel - if (any (a.ne.3).or.any (b.ne.16).or.l) call abort + if (any (a.ne.3).or.any (b.ne.16).or.l) STOP 6 k = .true. !$omp parallel do firstprivate (a, b, k) lastprivate (a, b) & !$omp & reduction (.or.:l) @@ -59,9 +59,9 @@ a(:, :) = i + 2 b(:, :) = i end do - if (any (a.ne.38).or.any (b.ne.36).or.l) call abort + if (any (a.ne.38).or.any (b.ne.36).or.l) STOP 7 deallocate (a) - if (allocated (a)) call abort + if (allocated (a)) STOP 8 allocate (a (0:1, 0:3)) a(:, :) = 0 !$omp parallel do reduction (+:a) reduction (.or.:l) & @@ -72,10 +72,10 @@ a(modulo (i, 2), i / 2) = a(modulo (i, 2), i / 2) + i a(i / 4, modulo (i, 4)) = a(i / 4, modulo (i, 4)) + i end do - if (l) call abort + if (l) STOP 9 do i = 0, 1 do j = 0, 3 - if (a(i, j) .ne. (5*i + 3*j)) call abort + if (a(i, j) .ne. (5*i + 3*j)) STOP 10 end do end do end |