Commit c425e66b by Tobias Burnus Committed by Tobias Burnus

libgomp/testsuite – use 'stop'

	libgomp/
	* testsuite/libgomp.fortran/: Replace 'STOP' by 'stop'.

From-SVN: r277609
parent 3c56d8d8
...@@ -42,12 +42,12 @@ ...@@ -42,12 +42,12 @@
end do end do
call foo (p, q, c_loc (r(1)), s) call foo (p, q, c_loc (r(1)), s)
do i = 1, 1024 do i = 1, 1024
if (p(i) /= i * i + 3 * i + 2) STOP 1 if (p(i) /= i * i + 3 * i + 2) stop 1
p(i) = i p(i) = i
end do end do
call bar (p, q, c_loc (r(1)), s) call bar (p, q, c_loc (r(1)), s)
do i = 1, 1024 do i = 1, 1024
if (p(i) /= i * i + 3 * i + 2) STOP 2 if (p(i) /= i * i + 3 * i + 2) stop 2
end do end do
! Attempt to create 64-byte aligned allocatable ! Attempt to create 64-byte aligned allocatable
do i = 1, 64 do i = 1, 64
...@@ -65,7 +65,7 @@ ...@@ -65,7 +65,7 @@
end do end do
call baz (p, c) call baz (p, c)
do i = 1, 1024 do i = 1, 1024
if (p(i) /= i * i + 5 * i + 2) STOP 3 if (p(i) /= i * i + 5 * i + 2) stop 3
end do end do
end if end if
end end
......
...@@ -22,19 +22,19 @@ contains ...@@ -22,19 +22,19 @@ contains
type (dl), intent (in) :: obj type (dl), intent (in) :: obj
integer, intent (in) :: val, cl1, cu1, cl2, cu2 integer, intent (in) :: val, cl1, cu1, cl2, cu2
logical, intent (in) :: c, f logical, intent (in) :: c, f
if ((c .neqv. allocated (obj%c)) .or. (f .neqv. allocated (obj%f))) STOP 1 if ((c .neqv. allocated (obj%c)) .or. (f .neqv. allocated (obj%f))) stop 1
if (c) then if (c) then
if (lbound (obj%c, 1) /= cl1 .or. ubound (obj%c, 1) /= cu1) STOP 2 if (lbound (obj%c, 1) /= cl1 .or. ubound (obj%c, 1) /= cu1) stop 2
if (lbound (obj%c, 2) /= cl2 .or. ubound (obj%c, 2) /= cu2) STOP 3 if (lbound (obj%c, 2) /= cl2 .or. ubound (obj%c, 2) /= cu2) stop 3
end if end if
if (val /= 0) then if (val /= 0) then
if (obj%a /= val .or. obj%b /= val) STOP 4 if (obj%a /= val .or. obj%b /= val) stop 4
if (obj%d /= val .or. obj%e /= val) STOP 5 if (obj%d /= val .or. obj%e /= val) stop 5
if (c) then if (c) then
if (any (obj%c /= val)) STOP 6 if (any (obj%c /= val)) stop 6
end if end if
if (f) then if (f) then
if (obj%f /= val) STOP 7 if (obj%f /= val) stop 7
end if end if
end if end if
end subroutine ver_dl end subroutine ver_dl
...@@ -43,9 +43,9 @@ contains ...@@ -43,9 +43,9 @@ contains
integer, intent (in) :: val, hl, hu, cl1, cu1, cl2, cu2 integer, intent (in) :: val, hl, hu, cl1, cu1, cl2, cu2
logical, intent (in) :: h, k, c, f logical, intent (in) :: h, k, c, f
integer :: i, j integer :: i, j
if ((h .neqv. allocated (obj%h)) .or. (k .neqv. allocated (obj%k))) STOP 8 if ((h .neqv. allocated (obj%h)) .or. (k .neqv. allocated (obj%k))) stop 8
if (h) then if (h) then
if (lbound (obj%h, 1) /= hl .or. ubound (obj%h, 1) /= hu) STOP 9 if (lbound (obj%h, 1) /= hl .or. ubound (obj%h, 1) /= hu) stop 9
do i = hl, hu do i = hl, hu
call ver_dl (obj%h(i), val, c, cl1, cu1, cl2, cu2, f) call ver_dl (obj%h(i), val, c, cl1, cu1, cl2, cu2, f)
end do end do
...@@ -57,7 +57,7 @@ contains ...@@ -57,7 +57,7 @@ contains
end do end do
if (k) call ver_dl (obj%k, val, c, cl1, cu1, cl2, cu2, f) if (k) call ver_dl (obj%k, val, c, cl1, cu1, cl2, cu2, f)
if (val /= 0) then if (val /= 0) then
if (obj%g /= val .or. obj%i /= val) STOP 10 if (obj%g /= val .or. obj%i /= val) stop 10
end if end if
end subroutine ver_dt end subroutine ver_dt
subroutine alloc_dl (obj, val, c, cl1, cu1, cl2, cu2, f) subroutine alloc_dl (obj, val, c, cl1, cu1, cl2, cu2, f)
......
...@@ -22,19 +22,19 @@ contains ...@@ -22,19 +22,19 @@ contains
type (dl), intent (in) :: obj type (dl), intent (in) :: obj
integer, intent (in) :: val, cl1, cu1, cl2, cu2 integer, intent (in) :: val, cl1, cu1, cl2, cu2
logical, intent (in) :: c, f logical, intent (in) :: c, f
if ((c .neqv. allocated (obj%c)) .or. (f .neqv. allocated (obj%f))) STOP 1 if ((c .neqv. allocated (obj%c)) .or. (f .neqv. allocated (obj%f))) stop 1
if (c) then if (c) then
if (lbound (obj%c, 1) /= cl1 .or. ubound (obj%c, 1) /= cu1) STOP 2 if (lbound (obj%c, 1) /= cl1 .or. ubound (obj%c, 1) /= cu1) stop 2
if (lbound (obj%c, 2) /= cl2 .or. ubound (obj%c, 2) /= cu2) STOP 3 if (lbound (obj%c, 2) /= cl2 .or. ubound (obj%c, 2) /= cu2) stop 3
end if end if
if (val /= 0) then if (val /= 0) then
if (obj%a /= val .or. obj%b /= val) STOP 4 if (obj%a /= val .or. obj%b /= val) stop 4
if (obj%d /= val .or. obj%e /= val) STOP 5 if (obj%d /= val .or. obj%e /= val) stop 5
if (c) then if (c) then
if (any (obj%c /= val)) STOP 6 if (any (obj%c /= val)) stop 6
end if end if
if (f) then if (f) then
if (obj%f /= val) STOP 7 if (obj%f /= val) stop 7
end if end if
end if end if
end subroutine ver_dl end subroutine ver_dl
...@@ -43,9 +43,9 @@ contains ...@@ -43,9 +43,9 @@ contains
integer, intent (in) :: val, hl, hu, cl1, cu1, cl2, cu2 integer, intent (in) :: val, hl, hu, cl1, cu1, cl2, cu2
logical, intent (in) :: h, k, c, f logical, intent (in) :: h, k, c, f
integer :: i, j integer :: i, j
if ((h .neqv. allocated (obj%h)) .or. (k .neqv. allocated (obj%k))) STOP 8 if ((h .neqv. allocated (obj%h)) .or. (k .neqv. allocated (obj%k))) stop 8
if (h) then if (h) then
if (lbound (obj%h, 1) /= hl .or. ubound (obj%h, 1) /= hu) STOP 9 if (lbound (obj%h, 1) /= hl .or. ubound (obj%h, 1) /= hu) stop 9
do i = hl, hu do i = hl, hu
call ver_dl (obj%h(i), val, c, cl1, cu1, cl2, cu2, f) call ver_dl (obj%h(i), val, c, cl1, cu1, cl2, cu2, f)
end do end do
...@@ -57,7 +57,7 @@ contains ...@@ -57,7 +57,7 @@ contains
end do end do
if (k) call ver_dl (obj%k, val, c, cl1, cu1, cl2, cu2, f) if (k) call ver_dl (obj%k, val, c, cl1, cu1, cl2, cu2, f)
if (val /= 0) then if (val /= 0) then
if (obj%g /= val .or. obj%i /= val) STOP 10 if (obj%g /= val .or. obj%i /= val) stop 10
end if end if
end subroutine ver_dt end subroutine ver_dt
subroutine alloc_dl (obj, val, c, cl1, cu1, cl2, cu2, f) subroutine alloc_dl (obj, val, c, cl1, cu1, cl2, cu2, f)
...@@ -122,20 +122,20 @@ contains ...@@ -122,20 +122,20 @@ contains
logical, parameter :: T = .true. logical, parameter :: T = .true.
logical :: l logical :: l
!$omp parallel private (x, y, z) !$omp parallel private (x, y, z)
if (allocated (x) .or. allocated (y) .or. allocated (z)) STOP 11 if (allocated (x) .or. allocated (y) .or. allocated (z)) stop 11
!$omp end parallel !$omp end parallel
!$omp parallel firstprivate (x, y, z) !$omp parallel firstprivate (x, y, z)
if (allocated (x) .or. allocated (y) .or. allocated (z)) STOP 12 if (allocated (x) .or. allocated (y) .or. allocated (z)) stop 12
!$omp end parallel !$omp end parallel
l = F l = F
!$omp parallel sections lastprivate (x, y, z) firstprivate (l) !$omp parallel sections lastprivate (x, y, z) firstprivate (l)
!$omp section !$omp section
if (.not. l) then if (.not. l) then
if (allocated (x) .or. allocated (y) .or. allocated (z)) STOP 13 if (allocated (x) .or. allocated (y) .or. allocated (z)) stop 13
end if end if
!$omp section !$omp section
if (.not. l) then if (.not. l) then
if (allocated (x) .or. allocated (y) .or. allocated (z)) STOP 14 if (allocated (x) .or. allocated (y) .or. allocated (z)) stop 14
end if end if
allocate (x, y, z(-3:-3,2:3)) allocate (x, y, z(-3:-3,2:3))
call alloc_dt (x, 5, F, 0, 0, T, T, -1, -1, -1, -1, T) call alloc_dt (x, 5, F, 0, 0, T, T, -1, -1, -1, -1, T)
...@@ -148,10 +148,10 @@ contains ...@@ -148,10 +148,10 @@ contains
call ver_dt (z(-3,3), 23, T, 0, 1, T, T, 2, 2, 2, 2, F) call ver_dt (z(-3,3), 23, T, 0, 1, T, T, 2, 2, 2, 2, F)
!$omp section !$omp section
!$omp end parallel sections !$omp end parallel sections
if (.not.allocated (x) .or. .not.allocated (y)) STOP 15 if (.not.allocated (x) .or. .not.allocated (y)) stop 15
if (.not.allocated (z)) STOP 16 if (.not.allocated (z)) stop 16
if (lbound (z, 1) /= -3 .or. ubound (z, 1) /= -3) STOP 17 if (lbound (z, 1) /= -3 .or. ubound (z, 1) /= -3) stop 17
if (lbound (z, 2) /= 2 .or. ubound (z, 2) /= 3) STOP 18 if (lbound (z, 2) /= 2 .or. ubound (z, 2) /= 3) stop 18
call ver_dt (x, 5, F, 0, 0, T, T, -1, -1, -1, -1, T) call ver_dt (x, 5, F, 0, 0, T, T, -1, -1, -1, -1, T)
call ver_dt (y, 23, T, 0, 1, T, T, 2, 2, 2, 2, F) call ver_dt (y, 23, T, 0, 1, T, T, 2, 2, 2, 2, F)
call ver_dt (z(-3,2), 5, F, 0, 0, T, T, -1, -1, -1, -1, T) call ver_dt (z(-3,2), 5, F, 0, 0, T, T, -1, -1, -1, -1, T)
......
...@@ -22,19 +22,19 @@ contains ...@@ -22,19 +22,19 @@ contains
type (dl), intent (in) :: obj type (dl), intent (in) :: obj
integer, intent (in) :: val, cl1, cu1, cl2, cu2 integer, intent (in) :: val, cl1, cu1, cl2, cu2
logical, intent (in) :: c, f logical, intent (in) :: c, f
if ((c .neqv. allocated (obj%c)) .or. (f .neqv. allocated (obj%f))) STOP 1 if ((c .neqv. allocated (obj%c)) .or. (f .neqv. allocated (obj%f))) stop 1
if (c) then if (c) then
if (lbound (obj%c, 1) /= cl1 .or. ubound (obj%c, 1) /= cu1) STOP 2 if (lbound (obj%c, 1) /= cl1 .or. ubound (obj%c, 1) /= cu1) stop 2
if (lbound (obj%c, 2) /= cl2 .or. ubound (obj%c, 2) /= cu2) STOP 3 if (lbound (obj%c, 2) /= cl2 .or. ubound (obj%c, 2) /= cu2) stop 3
end if end if
if (val /= 0) then if (val /= 0) then
if (obj%a /= val .or. obj%b /= val) STOP 4 if (obj%a /= val .or. obj%b /= val) stop 4
if (obj%d /= val .or. obj%e /= val) STOP 5 if (obj%d /= val .or. obj%e /= val) stop 5
if (c) then if (c) then
if (any (obj%c /= val)) STOP 6 if (any (obj%c /= val)) stop 6
end if end if
if (f) then if (f) then
if (obj%f /= val) STOP 7 if (obj%f /= val) stop 7
end if end if
end if end if
end subroutine ver_dl end subroutine ver_dl
...@@ -43,9 +43,9 @@ contains ...@@ -43,9 +43,9 @@ contains
integer, intent (in) :: val, hl, hu, cl1, cu1, cl2, cu2 integer, intent (in) :: val, hl, hu, cl1, cu1, cl2, cu2
logical, intent (in) :: h, k, c, f logical, intent (in) :: h, k, c, f
integer :: i, j integer :: i, j
if ((h .neqv. allocated (obj%h)) .or. (k .neqv. allocated (obj%k))) STOP 8 if ((h .neqv. allocated (obj%h)) .or. (k .neqv. allocated (obj%k))) stop 8
if (h) then if (h) then
if (lbound (obj%h, 1) /= hl .or. ubound (obj%h, 1) /= hu) STOP 9 if (lbound (obj%h, 1) /= hl .or. ubound (obj%h, 1) /= hu) stop 9
do i = hl, hu do i = hl, hu
call ver_dl (obj%h(i), val, c, cl1, cu1, cl2, cu2, f) call ver_dl (obj%h(i), val, c, cl1, cu1, cl2, cu2, f)
end do end do
...@@ -57,7 +57,7 @@ contains ...@@ -57,7 +57,7 @@ contains
end do end do
if (k) call ver_dl (obj%k, val, c, cl1, cu1, cl2, cu2, f) if (k) call ver_dl (obj%k, val, c, cl1, cu1, cl2, cu2, f)
if (val /= 0) then if (val /= 0) then
if (obj%g /= val .or. obj%i /= val) STOP 10 if (obj%g /= val .or. obj%i /= val) stop 10
end if end if
end subroutine ver_dt end subroutine ver_dt
subroutine alloc_dl (obj, val, c, cl1, cu1, cl2, cu2, f) subroutine alloc_dl (obj, val, c, cl1, cu1, cl2, cu2, f)
...@@ -124,27 +124,27 @@ contains ...@@ -124,27 +124,27 @@ contains
logical, parameter :: F = .false. logical, parameter :: F = .false.
logical, parameter :: T = .true. logical, parameter :: T = .true.
logical :: l logical :: l
if (lbound (x, 1) /= 2 .or. ubound (x, 1) /= 4) STOP 11 if (lbound (x, 1) /= 2 .or. ubound (x, 1) /= 4) stop 11
if (lbound (y, 1) /= 3 .or. ubound (y, 1) /= 4) STOP 12 if (lbound (y, 1) /= 3 .or. ubound (y, 1) /= 4) stop 12
call ver_dt (x(2), 0, F, 0, 0, F, F, 0, 0, 0, 0, F) call ver_dt (x(2), 0, F, 0, 0, F, F, 0, 0, 0, 0, F)
call ver_dt (x(n), 0, F, 0, 0, F, F, 0, 0, 0, 0, F) call ver_dt (x(n), 0, F, 0, 0, F, F, 0, 0, 0, 0, F)
call ver_dt (y(3), 0, F, 0, 0, F, F, 0, 0, 0, 0, F) call ver_dt (y(3), 0, F, 0, 0, F, F, 0, 0, 0, 0, F)
call ver_dt (y(4), 0, F, 0, 0, F, F, 0, 0, 0, 0, F) call ver_dt (y(4), 0, F, 0, 0, F, F, 0, 0, 0, 0, F)
!$omp parallel private (z) !$omp parallel private (z)
if (allocated (z)) STOP 13 if (allocated (z)) stop 13
!$omp end parallel !$omp end parallel
!$omp parallel firstprivate (z) !$omp parallel firstprivate (z)
if (allocated (z)) STOP 14 if (allocated (z)) stop 14
!$omp end parallel !$omp end parallel
l = F l = F
!$omp parallel sections lastprivate (z) firstprivate (l) !$omp parallel sections lastprivate (z) firstprivate (l)
!$omp section !$omp section
if (.not. l) then if (.not. l) then
if (allocated (z)) STOP 15 if (allocated (z)) stop 15
end if end if
!$omp section !$omp section
if (.not. l) then if (.not. l) then
if (allocated (z)) STOP 16 if (allocated (z)) stop 16
end if end if
allocate (z(-3:-3,2:3)) allocate (z(-3:-3,2:3))
call alloc_dt (z(-3,2), 5, F, 0, 0, T, T, -1, -1, -1, -1, T) call alloc_dt (z(-3,2), 5, F, 0, 0, T, T, -1, -1, -1, -1, T)
...@@ -153,9 +153,9 @@ contains ...@@ -153,9 +153,9 @@ contains
call ver_dt (z(-3,3), 23, T, 0, 1, T, T, 2, 2, 2, 2, F) call ver_dt (z(-3,3), 23, T, 0, 1, T, T, 2, 2, 2, 2, F)
!$omp section !$omp section
!$omp end parallel sections !$omp end parallel sections
if (.not.allocated (z)) STOP 17 if (.not.allocated (z)) stop 17
if (lbound (z, 1) /= -3 .or. ubound (z, 1) /= -3) STOP 18 if (lbound (z, 1) /= -3 .or. ubound (z, 1) /= -3) stop 18
if (lbound (z, 2) /= 2 .or. ubound (z, 2) /= 3) STOP 19 if (lbound (z, 2) /= 2 .or. ubound (z, 2) /= 3) stop 19
call ver_dt (z(-3,2), 5, F, 0, 0, T, T, -1, -1, -1, -1, T) call ver_dt (z(-3,2), 5, F, 0, 0, T, T, -1, -1, -1, -1, T)
call ver_dt (z(-3,3), 23, T, 0, 1, T, T, 2, 2, 2, 2, F) call ver_dt (z(-3,3), 23, T, 0, 1, T, T, 2, 2, 2, 2, F)
call ver_dt (x(n - 1), 0, F, 0, 0, F, F, 0, 0, 0, 0, F) call ver_dt (x(n - 1), 0, F, 0, 0, F, F, 0, 0, 0, 0, F)
...@@ -203,8 +203,8 @@ contains ...@@ -203,8 +203,8 @@ contains
call alloc_dt (z(-3,2), 5, T, 1, 2, F, T, 2, 3, -2, -2, F) call alloc_dt (z(-3,2), 5, T, 1, 2, F, T, 2, 3, -2, -2, F)
call alloc_dt (z(-3,3), 15, F, 0, 0, T, T, 2, 2, 2, 2, T) call alloc_dt (z(-3,3), 15, F, 0, 0, T, T, 2, 2, 2, 2, T)
!$omp parallel firstprivate (x, y, z) !$omp parallel firstprivate (x, y, z)
if (lbound (x, 1) /= 2 .or. ubound (x, 1) /= 4) STOP 20 if (lbound (x, 1) /= 2 .or. ubound (x, 1) /= 4) stop 20
if (lbound (y, 1) /= 3 .or. ubound (y, 1) /= 4) STOP 21 if (lbound (y, 1) /= 3 .or. ubound (y, 1) /= 4) stop 21
call ver_dt (x(n - 1), 5, T, 1, 2, F, T, 2, 3, -2, -2, F) call ver_dt (x(n - 1), 5, T, 1, 2, F, T, 2, 3, -2, -2, F)
call alloc_dt (x(n - 1), 4, T, -3, -1, T, T, -1, -1, 2, 3, T) call alloc_dt (x(n - 1), 4, T, -3, -1, T, T, -1, -1, 2, 3, T)
call ver_dt (x(n - 1), 4, T, -3, -1, T, T, -1, -1, 2, 3, T) call ver_dt (x(n - 1), 4, T, -3, -1, T, T, -1, -1, 2, 3, T)
......
...@@ -7,7 +7,7 @@ ...@@ -7,7 +7,7 @@
logical :: k, l logical :: k, l
b(:, :) = 16 b(:, :) = 16
l = .false. l = .false.
if (allocated (a)) STOP 1 if (allocated (a)) stop 1
!$omp parallel private (a, b) reduction (.or.:l) !$omp parallel private (a, b) reduction (.or.:l)
l = l.or.allocated (a) l = l.or.allocated (a)
allocate (a(3, 6)) allocate (a(3, 6))
...@@ -18,18 +18,18 @@ ...@@ -18,18 +18,18 @@
deallocate (a) deallocate (a)
l = l.or.allocated (a) l = l.or.allocated (a)
!$omp end parallel !$omp end parallel
if (allocated (a).or.l) STOP 2 if (allocated (a).or.l) stop 2
allocate (a(6, 3)) allocate (a(6, 3))
a(:, :) = 3 a(:, :) = 3
if (.not.allocated (a)) STOP 3 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 l = l.or.size(a).ne.18.or.size(a,1).ne.6.or.size(a,2).ne.3
if (l) STOP 4 if (l) stop 4
!$omp parallel private (a, b) reduction (.or.:l) !$omp parallel private (a, b) reduction (.or.:l)
l = l.or..not.allocated (a) l = l.or..not.allocated (a)
a(3, 2) = 1 a(3, 2) = 1
b(3, 2) = 1 b(3, 2) = 1
!$omp end parallel !$omp end parallel
if (l.or..not.allocated (a)) STOP 5 if (l.or..not.allocated (a)) stop 5
!$omp parallel firstprivate (a, b) reduction (.or.:l) !$omp parallel firstprivate (a, b) reduction (.or.:l)
l = l.or..not.allocated (a) 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 l = l.or.size(a).ne.18.or.size(a,1).ne.6.or.size(a,2).ne.3
...@@ -41,7 +41,7 @@ ...@@ -41,7 +41,7 @@
a(:, :) = omp_get_thread_num () a(:, :) = omp_get_thread_num ()
b(:, :) = omp_get_thread_num () b(:, :) = omp_get_thread_num ()
!$omp end parallel !$omp end parallel
if (any (a.ne.3).or.any (b.ne.16).or.l) STOP 6 if (any (a.ne.3).or.any (b.ne.16).or.l) stop 6
k = .true. k = .true.
!$omp parallel do firstprivate (a, b, k) lastprivate (a, b) & !$omp parallel do firstprivate (a, b, k) lastprivate (a, b) &
!$omp & reduction (.or.:l) !$omp & reduction (.or.:l)
...@@ -59,9 +59,9 @@ ...@@ -59,9 +59,9 @@
a(:, :) = i + 2 a(:, :) = i + 2
b(:, :) = i b(:, :) = i
end do end do
if (any (a.ne.38).or.any (b.ne.36).or.l) STOP 7 if (any (a.ne.38).or.any (b.ne.36).or.l) stop 7
deallocate (a) deallocate (a)
if (allocated (a)) STOP 8 if (allocated (a)) stop 8
allocate (a (0:1, 0:3)) allocate (a (0:1, 0:3))
a(:, :) = 0 a(:, :) = 0
!$omp parallel do reduction (+:a) reduction (.or.:l) & !$omp parallel do reduction (+:a) reduction (.or.:l) &
...@@ -72,10 +72,10 @@ ...@@ -72,10 +72,10 @@
a(modulo (i, 2), i / 2) = a(modulo (i, 2), i / 2) + i 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 a(i / 4, modulo (i, 4)) = a(i / 4, modulo (i, 4)) + i
end do end do
if (l) STOP 9 if (l) stop 9
do i = 0, 1 do i = 0, 1
do j = 0, 3 do j = 0, 3
if (a(i, j) .ne. (5*i + 3*j)) STOP 10 if (a(i, j) .ne. (5*i + 3*j)) stop 10
end do end do
end do end do
end end
...@@ -4,109 +4,109 @@ ...@@ -4,109 +4,109 @@
integer :: i integer :: i
!$omp declare reduction (foo : integer : omp_out = omp_out + omp_in) & !$omp declare reduction (foo : integer : omp_out = omp_out + omp_in) &
!$omp & initializer (omp_priv = 0) !$omp & initializer (omp_priv = 0)
if (allocated (a) .or. allocated (b) .or. allocated (c)) STOP 1 if (allocated (a) .or. allocated (b) .or. allocated (c)) stop 1
allocate (a, b(6:9), c(3, 8:9)) allocate (a, b(6:9), c(3, 8:9))
a = 0 a = 0
b = 0 b = 0
c = 0 c = 0
if (.not.allocated (a)) STOP 2 if (.not.allocated (a)) stop 2
if (.not.allocated (b) .or. size (b) /= 4) STOP 3 if (.not.allocated (b) .or. size (b) /= 4) stop 3
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 4 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 4
if (.not.allocated (c) .or. size (c) /= 6) STOP 5 if (.not.allocated (c) .or. size (c) /= 6) stop 5
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 6 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 6
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 7 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 7
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 8 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 8
!$omp parallel do reduction (+:a, b, c) !$omp parallel do reduction (+:a, b, c)
do i = 1, 10 do i = 1, 10
if (.not.allocated (a)) STOP 9 if (.not.allocated (a)) stop 9
if (.not.allocated (b) .or. size (b) /= 4) STOP 10 if (.not.allocated (b) .or. size (b) /= 4) stop 10
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 11 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 11
if (.not.allocated (c) .or. size (c) /= 6) STOP 12 if (.not.allocated (c) .or. size (c) /= 6) stop 12
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 13 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 13
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 14 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 14
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 15 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 15
a = a + i a = a + i
b = b + 2 * i b = b + 2 * i
c = c + 3 * i c = c + 3 * i
end do end do
if (.not.allocated (a)) STOP 16 if (.not.allocated (a)) stop 16
if (.not.allocated (b) .or. size (b) /= 4) STOP 17 if (.not.allocated (b) .or. size (b) /= 4) stop 17
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 18 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 18
if (.not.allocated (c) .or. size (c) /= 6) STOP 19 if (.not.allocated (c) .or. size (c) /= 6) stop 19
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 20 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 20
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 21 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 21
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 22 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 22
if (a /= 55 .or. any (b /= 110) .or. any (c /= 165)) STOP 23 if (a /= 55 .or. any (b /= 110) .or. any (c /= 165)) stop 23
a = 0 a = 0
b = 0 b = 0
c = 0 c = 0
!$omp parallel do reduction (foo : a, b, c) !$omp parallel do reduction (foo : a, b, c)
do i = 1, 10 do i = 1, 10
if (.not.allocated (a)) STOP 24 if (.not.allocated (a)) stop 24
if (.not.allocated (b) .or. size (b) /= 4) STOP 25 if (.not.allocated (b) .or. size (b) /= 4) stop 25
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 26 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 26
if (.not.allocated (c) .or. size (c) /= 6) STOP 27 if (.not.allocated (c) .or. size (c) /= 6) stop 27
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 28 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 28
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 29 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 29
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 30 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 30
a = a + i a = a + i
b = b + 2 * i b = b + 2 * i
c = c + 3 * i c = c + 3 * i
end do end do
if (.not.allocated (a)) STOP 31 if (.not.allocated (a)) stop 31
if (.not.allocated (b) .or. size (b) /= 4) STOP 32 if (.not.allocated (b) .or. size (b) /= 4) stop 32
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 33 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 33
if (.not.allocated (c) .or. size (c) /= 6) STOP 34 if (.not.allocated (c) .or. size (c) /= 6) stop 34
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 35 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 35
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 36 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 36
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 37 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 37
if (a /= 55 .or. any (b /= 110) .or. any (c /= 165)) STOP 38 if (a /= 55 .or. any (b /= 110) .or. any (c /= 165)) stop 38
a = 0 a = 0
b = 0 b = 0
c = 0 c = 0
!$omp simd reduction (+:a, b, c) !$omp simd reduction (+:a, b, c)
do i = 1, 10 do i = 1, 10
if (.not.allocated (a)) STOP 39 if (.not.allocated (a)) stop 39
if (.not.allocated (b) .or. size (b) /= 4) STOP 40 if (.not.allocated (b) .or. size (b) /= 4) stop 40
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 41 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 41
if (.not.allocated (c) .or. size (c) /= 6) STOP 42 if (.not.allocated (c) .or. size (c) /= 6) stop 42
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 43 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 43
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 44 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 44
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 45 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 45
a = a + i a = a + i
b = b + 2 * i b = b + 2 * i
c = c + 3 * i c = c + 3 * i
end do end do
if (.not.allocated (a)) STOP 46 if (.not.allocated (a)) stop 46
if (.not.allocated (b) .or. size (b) /= 4) STOP 47 if (.not.allocated (b) .or. size (b) /= 4) stop 47
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 48 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 48
if (.not.allocated (c) .or. size (c) /= 6) STOP 49 if (.not.allocated (c) .or. size (c) /= 6) stop 49
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 50 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 50
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 51 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 51
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 52 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 52
if (a /= 55 .or. any (b /= 110) .or. any (c /= 165)) STOP 53 if (a /= 55 .or. any (b /= 110) .or. any (c /= 165)) stop 53
a = 0 a = 0
b = 0 b = 0
c = 0 c = 0
!$omp simd reduction (foo : a, b, c) !$omp simd reduction (foo : a, b, c)
do i = 1, 10 do i = 1, 10
if (.not.allocated (a)) STOP 54 if (.not.allocated (a)) stop 54
if (.not.allocated (b) .or. size (b) /= 4) STOP 55 if (.not.allocated (b) .or. size (b) /= 4) stop 55
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 56 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 56
if (.not.allocated (c) .or. size (c) /= 6) STOP 57 if (.not.allocated (c) .or. size (c) /= 6) stop 57
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 58 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 58
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 59 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 59
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 60 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 60
a = a + i a = a + i
b = b + 2 * i b = b + 2 * i
c = c + 3 * i c = c + 3 * i
end do end do
if (.not.allocated (a)) STOP 61 if (.not.allocated (a)) stop 61
if (.not.allocated (b) .or. size (b) /= 4) STOP 62 if (.not.allocated (b) .or. size (b) /= 4) stop 62
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 63 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 63
if (.not.allocated (c) .or. size (c) /= 6) STOP 64 if (.not.allocated (c) .or. size (c) /= 6) stop 64
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 65 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 65
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 66 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 66
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 67 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 67
if (a /= 55 .or. any (b /= 110) .or. any (c /= 165)) STOP 68 if (a /= 55 .or. any (b /= 110) .or. any (c /= 165)) stop 68
end end
...@@ -5,68 +5,68 @@ ...@@ -5,68 +5,68 @@
integer, allocatable, save :: a, b(:), c(:,:) integer, allocatable, save :: a, b(:), c(:,:)
integer :: p integer :: p
!$omp threadprivate (a, b, c) !$omp threadprivate (a, b, c)
if (allocated (a) .or. allocated (b) .or. allocated (c)) STOP 1 if (allocated (a) .or. allocated (b) .or. allocated (c)) stop 1
call omp_set_dynamic (.false.) call omp_set_dynamic (.false.)
call omp_set_num_threads (4) call omp_set_num_threads (4)
!$omp parallel num_threads (4) !$omp parallel num_threads (4)
if (allocated (a) .or. allocated (b) .or. allocated (c)) STOP 2 if (allocated (a) .or. allocated (b) .or. allocated (c)) stop 2
!$omp end parallel !$omp end parallel
allocate (a, b(6:9), c(3, 8:9)) allocate (a, b(6:9), c(3, 8:9))
a = 4 a = 4
b = 5 b = 5
c = 6 c = 6
if (.not.allocated (a)) STOP 3 if (.not.allocated (a)) stop 3
if (.not.allocated (b) .or. size (b) /= 4) STOP 4 if (.not.allocated (b) .or. size (b) /= 4) stop 4
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 5 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 5
if (.not.allocated (c) .or. size (c) /= 6) STOP 6 if (.not.allocated (c) .or. size (c) /= 6) stop 6
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 7 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 7
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 8 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 8
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 9 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 9
!$omp parallel num_threads (4) copyin (a, b, c) private (p) !$omp parallel num_threads (4) copyin (a, b, c) private (p)
p = omp_get_thread_num () p = omp_get_thread_num ()
if (.not.allocated (a)) STOP 10 if (.not.allocated (a)) stop 10
if (.not.allocated (b) .or. size (b) /= 4) STOP 11 if (.not.allocated (b) .or. size (b) /= 4) stop 11
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 12 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 12
if (.not.allocated (c) .or. size (c) /= 6) STOP 13 if (.not.allocated (c) .or. size (c) /= 6) stop 13
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 14 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 14
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 15 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 15
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 16 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 16
if (a /= 4 .or. any (b /= 5) .or. any (c /= 6)) STOP 17 if (a /= 4 .or. any (b /= 5) .or. any (c /= 6)) stop 17
deallocate (a, b, c) deallocate (a, b, c)
if (allocated (a) .or. allocated (b) .or. allocated (c)) STOP 18 if (allocated (a) .or. allocated (b) .or. allocated (c)) stop 18
allocate (a, b(p:9), c(3, p:7)) allocate (a, b(p:9), c(3, p:7))
a = p a = p
b = p b = p
c = p c = p
if (.not.allocated (a)) STOP 19 if (.not.allocated (a)) stop 19
if (.not.allocated (b) .or. size (b) /= (10 - p)) STOP 20 if (.not.allocated (b) .or. size (b) /= (10 - p)) stop 20
if (lbound (b, 1) /= p .or. ubound (b, 1) /= 9) STOP 21 if (lbound (b, 1) /= p .or. ubound (b, 1) /= 9) stop 21
if (.not.allocated (c) .or. size (c) /= (3 * (8 - p))) STOP 22 if (.not.allocated (c) .or. size (c) /= (3 * (8 - p))) stop 22
if (size (c, 1) /= 3 .or. size (c, 2) /= (8 - p)) STOP 23 if (size (c, 1) /= 3 .or. size (c, 2) /= (8 - p)) stop 23
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 24 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 24
if (lbound (c, 2) /= p .or. ubound (c, 2) /= 7) STOP 25 if (lbound (c, 2) /= p .or. ubound (c, 2) /= 7) stop 25
if (a /= p .or. any (b /= p) .or. any (c /= p)) STOP 26 if (a /= p .or. any (b /= p) .or. any (c /= p)) stop 26
!$omp end parallel !$omp end parallel
!$omp parallel num_threads (4) copyin (a, b, c) !$omp parallel num_threads (4) copyin (a, b, c)
if (.not.allocated (a)) STOP 27 if (.not.allocated (a)) stop 27
if (.not.allocated (b) .or. size (b) /= 10) STOP 28 if (.not.allocated (b) .or. size (b) /= 10) stop 28
if (lbound (b, 1) /= 0 .or. ubound (b, 1) /= 9) STOP 29 if (lbound (b, 1) /= 0 .or. ubound (b, 1) /= 9) stop 29
if (.not.allocated (c) .or. size (c) /= 24) STOP 30 if (.not.allocated (c) .or. size (c) /= 24) stop 30
if (size (c, 1) /= 3 .or. size (c, 2) /= 8) STOP 31 if (size (c, 1) /= 3 .or. size (c, 2) /= 8) stop 31
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 32 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 32
if (lbound (c, 2) /= 0 .or. ubound (c, 2) /= 7) STOP 33 if (lbound (c, 2) /= 0 .or. ubound (c, 2) /= 7) stop 33
if (a /= 0 .or. any (b /= 0) .or. any (c /= 0)) STOP 34 if (a /= 0 .or. any (b /= 0) .or. any (c /= 0)) stop 34
!$omp end parallel !$omp end parallel
deallocate (a, b, c) deallocate (a, b, c)
if (allocated (a) .or. allocated (b) .or. allocated (c)) STOP 35 if (allocated (a) .or. allocated (b) .or. allocated (c)) stop 35
!$omp parallel num_threads (4) copyin (a, b, c) !$omp parallel num_threads (4) copyin (a, b, c)
if (allocated (a) .or. allocated (b) .or. allocated (c)) STOP 36 if (allocated (a) .or. allocated (b) .or. allocated (c)) stop 36
!$omp end parallel !$omp end parallel
end end
...@@ -2,11 +2,11 @@ ...@@ -2,11 +2,11 @@
integer, allocatable :: a, b(:), c(:,:) integer, allocatable :: a, b(:), c(:,:)
logical :: l logical :: l
if (allocated (a) .or. allocated (b) .or. allocated (c)) STOP 1 if (allocated (a) .or. allocated (b) .or. allocated (c)) stop 1
!$omp parallel private (a, b, c, l) !$omp parallel private (a, b, c, l)
l = .false. l = .false.
if (allocated (a) .or. allocated (b) .or. allocated (c)) STOP 2 if (allocated (a) .or. allocated (b) .or. allocated (c)) stop 2
!$omp single !$omp single
allocate (a, b(6:9), c(3, 8:9)) allocate (a, b(6:9), c(3, 8:9))
...@@ -15,60 +15,60 @@ ...@@ -15,60 +15,60 @@
c = 6 c = 6
!$omp end single copyprivate (a, b, c) !$omp end single copyprivate (a, b, c)
if (.not.allocated (a)) STOP 3 if (.not.allocated (a)) stop 3
if (.not.allocated (b) .or. size (b) /= 4) STOP 4 if (.not.allocated (b) .or. size (b) /= 4) stop 4
if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) STOP 5 if (lbound (b, 1) /= 6 .or. ubound (b, 1) /= 9) stop 5
if (.not.allocated (c) .or. size (c) /= 6) STOP 6 if (.not.allocated (c) .or. size (c) /= 6) stop 6
if (size (c, 1) /= 3 .or. size (c, 2) /= 2) STOP 7 if (size (c, 1) /= 3 .or. size (c, 2) /= 2) stop 7
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 8 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 8
if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) STOP 9 if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 9) stop 9
if (a /= 4 .or. any (b /= 5) .or. any (c /= 6)) STOP 10 if (a /= 4 .or. any (b /= 5) .or. any (c /= 6)) stop 10
!$omp single !$omp single
deallocate (a, b, c) deallocate (a, b, c)
if (allocated (a) .or. allocated (b) .or. allocated (c)) STOP 11 if (allocated (a) .or. allocated (b) .or. allocated (c)) stop 11
allocate (a, b(0:4), c(3, 2:7)) allocate (a, b(0:4), c(3, 2:7))
a = 1 a = 1
b = 2 b = 2
c = 3 c = 3
!$omp end single copyprivate (a, b, c) !$omp end single copyprivate (a, b, c)
if (.not.allocated (a)) STOP 12 if (.not.allocated (a)) stop 12
if (.not.allocated (b) .or. size (b) /= 5) STOP 13 if (.not.allocated (b) .or. size (b) /= 5) stop 13
if (lbound (b, 1) /= 0 .or. ubound (b, 1) /= 4) STOP 14 if (lbound (b, 1) /= 0 .or. ubound (b, 1) /= 4) stop 14
if (.not.allocated (c) .or. size (c) /= 18) STOP 15 if (.not.allocated (c) .or. size (c) /= 18) stop 15
if (size (c, 1) /= 3 .or. size (c, 2) /= 6) STOP 16 if (size (c, 1) /= 3 .or. size (c, 2) /= 6) stop 16
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 17 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 17
if (lbound (c, 2) /= 2 .or. ubound (c, 2) /= 7) STOP 18 if (lbound (c, 2) /= 2 .or. ubound (c, 2) /= 7) stop 18
if (a /= 1 .or. any (b /= 2) .or. any (c /= 3)) STOP 19 if (a /= 1 .or. any (b /= 2) .or. any (c /= 3)) stop 19
!$omp single !$omp single
l = .true. l = .true.
deallocate (a, b, c) deallocate (a, b, c)
if (allocated (a) .or. allocated (b) .or. allocated (c)) STOP 20 if (allocated (a) .or. allocated (b) .or. allocated (c)) stop 20
allocate (a, b(2:6), c(3:5, 3:8)) allocate (a, b(2:6), c(3:5, 3:8))
a = 7 a = 7
b = 8 b = 8
c = 9 c = 9
!$omp end single copyprivate (a, b, c) !$omp end single copyprivate (a, b, c)
if (.not.allocated (a)) STOP 21 if (.not.allocated (a)) stop 21
if (.not.allocated (b) .or. size (b) /= 5) STOP 22 if (.not.allocated (b) .or. size (b) /= 5) stop 22
if (l) then if (l) then
if (lbound (b, 1) /= 2 .or. ubound (b, 1) /= 6) STOP 23 if (lbound (b, 1) /= 2 .or. ubound (b, 1) /= 6) stop 23
else else
if (lbound (b, 1) /= 0 .or. ubound (b, 1) /= 4) STOP 24 if (lbound (b, 1) /= 0 .or. ubound (b, 1) /= 4) stop 24
end if end if
if (.not.allocated (c) .or. size (c) /= 18) STOP 25 if (.not.allocated (c) .or. size (c) /= 18) stop 25
if (size (c, 1) /= 3 .or. size (c, 2) /= 6) STOP 26 if (size (c, 1) /= 3 .or. size (c, 2) /= 6) stop 26
if (l) then if (l) then
if (lbound (c, 1) /= 3 .or. ubound (c, 1) /= 5) STOP 27 if (lbound (c, 1) /= 3 .or. ubound (c, 1) /= 5) stop 27
if (lbound (c, 2) /= 3 .or. ubound (c, 2) /= 8) STOP 28 if (lbound (c, 2) /= 3 .or. ubound (c, 2) /= 8) stop 28
else else
if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) STOP 29 if (lbound (c, 1) /= 1 .or. ubound (c, 1) /= 3) stop 29
if (lbound (c, 2) /= 2 .or. ubound (c, 2) /= 7) STOP 30 if (lbound (c, 2) /= 2 .or. ubound (c, 2) /= 7) stop 30
end if end if
if (a /= 7 .or. any (b /= 8) .or. any (c /= 9)) STOP 31 if (a /= 7 .or. any (b /= 8) .or. any (c /= 9)) stop 31
!$omp end parallel !$omp end parallel
end end
...@@ -7,7 +7,7 @@ ...@@ -7,7 +7,7 @@
integer :: n integer :: n
logical :: l logical :: l
!$omp threadprivate (a) !$omp threadprivate (a)
if (allocated (a)) STOP 1 if (allocated (a)) stop 1
call omp_set_dynamic (.false.) call omp_set_dynamic (.false.)
l = .false. l = .false.
!$omp parallel num_threads (4) reduction(.or.:l) !$omp parallel num_threads (4) reduction(.or.:l)
...@@ -16,7 +16,7 @@ ...@@ -16,7 +16,7 @@
l = l.or..not.allocated (a) l = l.or..not.allocated (a)
l = l.or.size(a).ne.12.or.size(a,1).ne.3.or.size(a,2).ne.4 l = l.or.size(a).ne.12.or.size(a,1).ne.3.or.size(a,2).ne.4
!$omp end parallel !$omp end parallel
if (l.or.any(a.ne.6)) STOP 1 if (l.or.any(a.ne.6)) stop 1
!$omp parallel num_threads (4) copyin (a) reduction(.or.:l) private (b) !$omp parallel num_threads (4) copyin (a) reduction(.or.:l) private (b)
l = l.or.allocated (b) l = l.or.allocated (b)
l = l.or..not.allocated (a) l = l.or..not.allocated (a)
...@@ -37,11 +37,11 @@ ...@@ -37,11 +37,11 @@
deallocate (b) deallocate (b)
l = l.or.allocated (b) l = l.or.allocated (b)
!$omp end parallel !$omp end parallel
if (n.lt.0 .or. n.ge.4) STOP 2 if (n.lt.0 .or. n.ge.4) stop 2
if (l.or.any(a.ne.(n + 36))) STOP 3 if (l.or.any(a.ne.(n + 36))) stop 3
!$omp parallel num_threads (4) reduction(.or.:l) !$omp parallel num_threads (4) reduction(.or.:l)
deallocate (a) deallocate (a)
l = l.or.allocated (a) l = l.or.allocated (a)
!$omp end parallel !$omp end parallel
if (l.or.allocated (a)) STOP 4 if (l.or.allocated (a)) stop 4
end end
...@@ -4,7 +4,7 @@ ...@@ -4,7 +4,7 @@
integer :: i integer :: i
logical :: l logical :: l
l = .false. l = .false.
if (allocated (a)) STOP 1 if (allocated (a)) stop 1
!$omp parallel private (a) reduction (.or.:l) !$omp parallel private (a) reduction (.or.:l)
allocate (a (-7:-5)) allocate (a (-7:-5))
l = l.or..not.allocated (a) l = l.or..not.allocated (a)
...@@ -18,5 +18,5 @@ ...@@ -18,5 +18,5 @@
l = l.or.any (a.ne.0) l = l.or.any (a.ne.0)
deallocate (a) deallocate (a)
!$omp end parallel !$omp end parallel
if (l.or.allocated (a)) STOP 2 if (l.or.allocated (a)) stop 2
end end
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
logical :: k, l logical :: k, l
b(:, :) = 16 b(:, :) = 16
l = .false. l = .false.
if (allocated (a)) STOP 1 if (allocated (a)) stop 1
!$omp task private (a, b) shared (l) !$omp task private (a, b) shared (l)
l = l.or.allocated (a) l = l.or.allocated (a)
allocate (a(3, 6)) allocate (a(3, 6))
...@@ -18,19 +18,19 @@ ...@@ -18,19 +18,19 @@
l = l.or.allocated (a) l = l.or.allocated (a)
!$omp end task !$omp end task
!$omp taskwait !$omp taskwait
if (allocated (a).or.l) STOP 2 if (allocated (a).or.l) stop 2
allocate (a(6, 3)) allocate (a(6, 3))
a(:, :) = 3 a(:, :) = 3
if (.not.allocated (a)) STOP 3 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 l = l.or.size(a).ne.18.or.size(a,1).ne.6.or.size(a,2).ne.3
if (l) STOP 4 if (l) stop 4
!$omp task private (a, b) shared (l) !$omp task private (a, b) shared (l)
l = l.or..not.allocated (a) l = l.or..not.allocated (a)
a(3, 2) = 1 a(3, 2) = 1
b(3, 2) = 1 b(3, 2) = 1
!$omp end task !$omp end task
!$omp taskwait !$omp taskwait
if (l.or..not.allocated (a)) STOP 5 if (l.or..not.allocated (a)) stop 5
!$omp task firstprivate (a, b) shared (l) !$omp task firstprivate (a, b) shared (l)
l = l.or..not.allocated (a) 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 l = l.or.size(a).ne.18.or.size(a,1).ne.6.or.size(a,2).ne.3
...@@ -43,5 +43,5 @@ ...@@ -43,5 +43,5 @@
b(:, :) = 8 b(:, :) = 8
!$omp end task !$omp end task
!$omp taskwait !$omp taskwait
if (any (a.ne.3).or.any (b.ne.16).or.l) STOP 6 if (any (a.ne.3).or.any (b.ne.16).or.l) stop 6
end end
...@@ -12,6 +12,6 @@ program pr42866 ...@@ -12,6 +12,6 @@ program pr42866
a = a + 2 a = a + 2
!$omp end sections !$omp end sections
!$omp end parallel !$omp end parallel
if (any (a.ne.3)) STOP 1 if (any (a.ne.3)) stop 1
deallocate (a) deallocate (a)
end end
...@@ -25,10 +25,10 @@ ...@@ -25,10 +25,10 @@
else if (i .gt. 1 .and. i .lt. 9) then else if (i .gt. 1 .and. i .lt. 9) then
j = 7 j = 7
end if end if
if (c(i) .ne. j) STOP 1 if (c(i) .ne. j) stop 1
j = 179 - modulo (i, 11) j = 179 - modulo (i, 11)
if (i .gt. 1 .and. i .lt. 9) j = i if (i .gt. 1 .and. i .lt. 9) j = i
if (d(i) .ne. j) STOP 2 if (d(i) .ne. j) stop 2
end do end do
deallocate (a, b, c, d) deallocate (a, b, c, d)
end end
......
...@@ -12,5 +12,5 @@ ...@@ -12,5 +12,5 @@
deallocate (a) deallocate (a)
l = l .or. allocated (a) l = l .or. allocated (a)
!$omp end parallel !$omp end parallel
if (l) STOP 1 if (l) stop 1
end end
...@@ -5,10 +5,10 @@ ...@@ -5,10 +5,10 @@
integer, save, allocatable :: a(:, :) integer, save, allocatable :: a(:, :)
logical :: l logical :: l
!$omp threadprivate (a) !$omp threadprivate (a)
if (allocated (a)) STOP 1 if (allocated (a)) stop 1
l = .false. l = .false.
!$omp parallel copyin (a) num_threads (4) reduction(.or.:l) !$omp parallel copyin (a) num_threads (4) reduction(.or.:l)
l = l.or.allocated (a) l = l.or.allocated (a)
!$omp end parallel !$omp end parallel
if (l.or.allocated (a)) STOP 2 if (l.or.allocated (a)) stop 2
end end
...@@ -12,12 +12,12 @@ program associate1 ...@@ -12,12 +12,12 @@ program associate1
!$omp parallel private(v, a) default(none) !$omp parallel private(v, a) default(none)
v = -1 v = -1
a = 2.5 a = 2.5
if (v /= -1 .or. u /= 15) STOP 1 if (v /= -1 .or. u /= 15) stop 1
if (a(2,1) /= 2.5 .or. b /= 3.5) STOP 2 if (a(2,1) /= 2.5 .or. b /= 3.5) stop 2
associate(u => v, b => a(2, 1)) associate(u => v, b => a(2, 1))
if (u /= -1 .or. b /= 2.5) STOP 3 if (u /= -1 .or. b /= 2.5) stop 3
end associate end associate
if (u /= 15 .or. b /= 3.5) STOP 4 if (u /= 15 .or. b /= 3.5) stop 4
!$omp end parallel !$omp end parallel
end associate end associate
end program end program
...@@ -20,12 +20,12 @@ program associate2 ...@@ -20,12 +20,12 @@ program associate2
!$omp parallel private(v, a) default(none) !$omp parallel private(v, a) default(none)
v = -1 v = -1
forall (k = 1:3, l = 1:3) a(k, l)%a(:,:) = 2.5 forall (k = 1:3, l = 1:3) a(k, l)%a(:,:) = 2.5
if (v(3) /= -1 .or. u(3) /= 15) STOP 1 if (v(3) /= -1 .or. u(3) /= 15) stop 1
if (a(2,1)%a(1,2) /= 2.5 .or. b(1,2) /= 3.5) STOP 2 if (a(2,1)%a(1,2) /= 2.5 .or. b(1,2) /= 3.5) stop 2
associate(u => v, b => a(2, 1)%a) associate(u => v, b => a(2, 1)%a)
if (u(3) /= -1 .or. b(1,2) /= 2.5) STOP 3 if (u(3) /= -1 .or. b(1,2) /= 2.5) stop 3
end associate end associate
if (u(3) /= 15 .or. b(1,2) /= 3.5) STOP 4 if (u(3) /= 15 .or. b(1,2) /= 3.5) stop 4
!$omp end parallel !$omp end parallel
end associate end associate
forall (k = 1:3, l = 1:3) a(k, l)%c(:,:)%i = 7 forall (k = 1:3, l = 1:3) a(k, l)%c(:,:)%i = 7
...@@ -35,12 +35,12 @@ program associate2 ...@@ -35,12 +35,12 @@ program associate2
associate(d => a(i, j)%c(2,:)%i) associate(d => a(i, j)%c(2,:)%i)
!$omp parallel private(a) default(none) !$omp parallel private(a) default(none)
forall (k = 1:3, l = 1:3) a(k, l)%c(:,:)%i = 15 forall (k = 1:3, l = 1:3) a(k, l)%c(:,:)%i = 15
if (a(1,2)%c(2,1)%i /= 15 .or. d(1) /= 9) STOP 5 if (a(1,2)%c(2,1)%i /= 15 .or. d(1) /= 9) stop 5
if (a(1,2)%c(2,2)%i /= 15 .or. d(2) /= 7) STOP 6 if (a(1,2)%c(2,2)%i /= 15 .or. d(2) /= 7) stop 6
associate(d => a(2,1)%c(2,:)%i) associate(d => a(2,1)%c(2,:)%i)
if (d(1) /= 15 .or. d(2) /= 15) STOP 7 if (d(1) /= 15 .or. d(2) /= 15) stop 7
end associate end associate
if (d(1) /= 9 .or. d(2) /= 7) STOP 8 if (d(1) /= 9 .or. d(2) /= 7) stop 8
!$omp end parallel !$omp end parallel
end associate end associate
end program end program
...@@ -16,5 +16,5 @@ ...@@ -16,5 +16,5 @@
if (j.eq.1) k = 7 if (j.eq.1) k = 7
end do end do
end associate end associate
if (any (v%f(:).ne.21.) .or. i.ne.7) STOP 1 if (any (v%f(:).ne.21.) .or. i.ne.7) stop 1
end end
...@@ -17,13 +17,13 @@ program main ...@@ -17,13 +17,13 @@ program main
i = 41 i = 41
read (20,*, asynchronous="yes") i read (20,*, asynchronous="yes") i
wait (20) wait (20)
if (i .ne. 1) STOP 1 if (i .ne. 1) stop 1
write (*,*) ' ' write (*,*) ' '
backspace (20) backspace (20)
i = 42 i = 42
read (20,*, asynchronous="yes") i read (20,*, asynchronous="yes") i
close (20) close (20)
if (i .ne. 1) STOP 2 if (i .ne. 1) stop 2
! PR libfortran/20125 ! PR libfortran/20125
open (20, status='scratch', asynchronous="yes") open (20, status='scratch', asynchronous="yes")
...@@ -31,14 +31,14 @@ program main ...@@ -31,14 +31,14 @@ program main
backspace (20) backspace (20)
read (20,*, asynchronous="yes") i read (20,*, asynchronous="yes") i
wait (20) wait (20)
if (i .ne. 7) STOP 3 if (i .ne. 7) stop 3
close (20) close (20)
open (20, status='scratch', form='unformatted') open (20, status='scratch', form='unformatted')
write (20) 8 write (20) 8
backspace (20) backspace (20)
read (20) i read (20) i
if (i .ne. 8) STOP 4 if (i .ne. 8) stop 4
close (20) close (20)
! PR libfortran/20471 ! PR libfortran/20471
...@@ -52,7 +52,7 @@ program main ...@@ -52,7 +52,7 @@ program main
read (3) (y(n),n=1,10) read (3) (y(n),n=1,10)
do n = 1, 10 do n = 1, 10
if (abs(x(n)-y(n)) > 0.00001) STOP 5 if (abs(x(n)-y(n)) > 0.00001) stop 5
end do end do
close (3) close (3)
...@@ -69,7 +69,7 @@ program main ...@@ -69,7 +69,7 @@ program main
nr = nr + 1 nr = nr + 1
goto 20 goto 20
30 continue 30 continue
if (nr .ne. 5) STOP 6 if (nr .ne. 5) stop 6
do i = 1, nr+1 do i = 1, nr+1
backspace (3) backspace (3)
...@@ -77,14 +77,14 @@ program main ...@@ -77,14 +77,14 @@ program main
do i = 1, nr do i = 1, nr
read(3,end=70,err=90) n, (x(n),n=1,10) read(3,end=70,err=90) n, (x(n),n=1,10)
if (abs(x(1) - i) .gt. 0.001) STOP 7 if (abs(x(1) - i) .gt. 0.001) stop 7
end do end do
close (3) close (3)
stop stop
70 continue 70 continue
STOP 8 stop 8
90 continue 90 continue
STOP 9 stop 9
end program end program
...@@ -20,20 +20,20 @@ close(99) ...@@ -20,20 +20,20 @@ close(99)
! Test character kind ! Test character kind
open(99, file="test.dat") open(99, file="test.dat")
read (99,*, iostat=stat) cvar read (99,*, iostat=stat) cvar
if (stat /= 0 .or. cvar /= "1") STOP 1 if (stat /= 0 .or. cvar /= "1") stop 1
read (99,*, iostat=stat) cvar read (99,*, iostat=stat) cvar
if (stat /= 0 .or. cvar /= "2") STOP 2 if (stat /= 0 .or. cvar /= "2") stop 2
read (99,*, iostat=stat) cvar ! << FAILS: stat /= 0 read (99,*, iostat=stat) cvar ! << FAILS: stat /= 0
if (stat /= 0 .or. cvar /= "3") STOP 3 ! << aborts here if (stat /= 0 .or. cvar /= "3") stop 3 ! << aborts here
! Test real kind ! Test real kind
rewind(99) rewind(99)
read (99,*, iostat=stat) var read (99,*, iostat=stat) var
if (stat /= 0 .or. var /= 1.0) STOP 4 if (stat /= 0 .or. var /= 1.0) stop 4
read (99,*, iostat=stat) var read (99,*, iostat=stat) var
if (stat /= 0 .or. var /= 2.0) STOP 5 if (stat /= 0 .or. var /= 2.0) stop 5
read (99,*, iostat=stat) var ! << FAILS: stat /= 0 read (99,*, iostat=stat) var ! << FAILS: stat /= 0
if (stat /= 0 .or. var /= 3.0) STOP 6 if (stat /= 0 .or. var /= 3.0) stop 6
close(99, status="delete") close(99, status="delete")
! Test real kind with exponents ! Test real kind with exponents
...@@ -45,11 +45,11 @@ close(99) ...@@ -45,11 +45,11 @@ close(99)
open(99, file="test.dat") open(99, file="test.dat")
read (99,*, iostat=stat) var read (99,*, iostat=stat) var
if (stat /= 0) STOP 7 if (stat /= 0) stop 7
read (99,*, iostat=stat) var read (99,*, iostat=stat) var
if (stat /= 0) STOP 8 if (stat /= 0) stop 8
read (99,*) var ! << FAILS: stat /= 0 read (99,*) var ! << FAILS: stat /= 0
if (stat /= 0) STOP 9 if (stat /= 0) stop 9
close(99, status="delete") close(99, status="delete")
! Test logical kind ! Test logical kind
...@@ -61,11 +61,11 @@ close(99) ...@@ -61,11 +61,11 @@ close(99)
open(99, file="test.dat") open(99, file="test.dat")
read (99,*, iostat=stat) lvar read (99,*, iostat=stat) lvar
if (stat /= 0 .or. (.not.lvar)) STOP 10 if (stat /= 0 .or. (.not.lvar)) stop 10
read (99,*, iostat=stat) lvar read (99,*, iostat=stat) lvar
if (stat /= 0 .or. lvar) STOP 11 if (stat /= 0 .or. lvar) stop 11
read (99,*) lvar ! << FAILS: stat /= 0 read (99,*) lvar ! << FAILS: stat /= 0
if (stat /= 0 .or. (.not.lvar)) STOP 12 if (stat /= 0 .or. (.not.lvar)) stop 12
close(99, status="delete") close(99, status="delete")
! Test combinations of Inf and Nan ! Test combinations of Inf and Nan
...@@ -77,11 +77,11 @@ close(99) ...@@ -77,11 +77,11 @@ close(99)
open(99, file="test.dat") open(99, file="test.dat")
read (99,*, iostat=stat) var read (99,*, iostat=stat) var
if (stat /= 0) STOP 13 if (stat /= 0) stop 13
read (99,*, iostat=stat) var read (99,*, iostat=stat) var
if (stat /= 0) STOP 14 if (stat /= 0) stop 14
read (99,*) var ! << FAILS: stat /= 0 read (99,*) var ! << FAILS: stat /= 0
if (stat /= 0) STOP 1! << aborts here if (stat /= 0) stop 1! << aborts here
close(99, status="delete") close(99, status="delete")
open(99, file="test.dat", access="stream", form="unformatted", status="new") open(99, file="test.dat", access="stream", form="unformatted", status="new")
...@@ -92,11 +92,11 @@ close(99) ...@@ -92,11 +92,11 @@ close(99)
open(99, file="test.dat") open(99, file="test.dat")
read (99,*, iostat=stat) var read (99,*, iostat=stat) var
if (stat /= 0) STOP 15 if (stat /= 0) stop 15
read (99,*, iostat=stat) var read (99,*, iostat=stat) var
if (stat /= 0) STOP 16 if (stat /= 0) stop 16
read (99,*) var ! << FAILS: stat /= 0 read (99,*) var ! << FAILS: stat /= 0
if (stat /= 0) STOP 2! << aborts here if (stat /= 0) stop 2! << aborts here
close(99, status="delete") close(99, status="delete")
open(99, file="test.dat", access="stream", form="unformatted", status="new") open(99, file="test.dat", access="stream", form="unformatted", status="new")
...@@ -107,11 +107,11 @@ close(99) ...@@ -107,11 +107,11 @@ close(99)
open(99, file="test.dat") open(99, file="test.dat")
read (99,*, iostat=stat) var read (99,*, iostat=stat) var
if (stat /= 0) STOP 17 if (stat /= 0) stop 17
read (99,*, iostat=stat) var read (99,*, iostat=stat) var
if (stat /= 0) STOP 18 if (stat /= 0) stop 18
read (99,*) var ! << FAILS: stat /= 0 read (99,*) var ! << FAILS: stat /= 0
if (stat /= 0) STOP 3! << aborts here if (stat /= 0) stop 3! << aborts here
close(99, status="delete") close(99, status="delete")
! Test complex kind ! Test complex kind
...@@ -123,10 +123,10 @@ close(99) ...@@ -123,10 +123,10 @@ close(99)
open(99, file="test.dat") open(99, file="test.dat")
read (99,*, iostat=stat) cval read (99,*, iostat=stat) cval
if (stat /= 0 .or. cval /= cmplx(1,2)) STOP 19 if (stat /= 0 .or. cval /= cmplx(1,2)) stop 19
read (99,*, iostat=stat) cval read (99,*, iostat=stat) cval
if (stat /= 0 .or. cval /= cmplx(2,3)) STOP 20 if (stat /= 0 .or. cval /= cmplx(2,3)) stop 20
read (99,*, iostat=stat) cval ! << FAILS: stat /= 0, value is okay read (99,*, iostat=stat) cval ! << FAILS: stat /= 0, value is okay
if (stat /= 0 .or. cval /= cmplx(4,5)) STOP 21 if (stat /= 0 .or. cval /= cmplx(4,5)) stop 21
close(99, status="delete") close(99, status="delete")
end end
...@@ -17,12 +17,12 @@ program flush_1 ...@@ -17,12 +17,12 @@ program flush_1
write (10, *) 42 write (10, *) 42
flush(unit=10, iostat=ios) flush(unit=10, iostat=ios)
if (ios /= 0) STOP 1 if (ios /= 0) stop 1
write (10, *) 42 write (10, *) 42
flush (unit=10, err=20) flush (unit=10, err=20)
goto 30 goto 30
20 STOP 2 20 stop 2
30 continue 30 continue
call flush(10) call flush(10)
......
...@@ -16,7 +16,7 @@ program newunit_1 ...@@ -16,7 +16,7 @@ program newunit_1
rewind(myunit) rewind(myunit)
rewind(myunit2) rewind(myunit2)
read(myunit2,'(a)') str read(myunit2,'(a)') str
if (str.ne." abcdefghijklmnop") STOP 1 if (str.ne." abcdefghijklmnop") stop 1
close(myunit) close(myunit)
close(myunit2, status="delete") close(myunit2, status="delete")
end program newunit_1 end program newunit_1
...@@ -8,7 +8,7 @@ ...@@ -8,7 +8,7 @@
!$omp do !$omp do
do i = 0, 999 do i = 0, 999
!$omp cancel do !$omp cancel do
if (omp_get_cancellation ()) STOP 1 if (omp_get_cancellation ()) stop 1
enddo enddo
!$omp endparallel !$omp endparallel
end end
...@@ -22,7 +22,7 @@ contains ...@@ -22,7 +22,7 @@ contains
!$omp do !$omp do
do i = 0, 999 do i = 0, 999
!$omp cancel do if (x(1)) !$omp cancel do if (x(1))
STOP 1 stop 1
end do end do
!$omp do !$omp do
do i = 0, 999 do i = 0, 999
...@@ -47,7 +47,7 @@ contains ...@@ -47,7 +47,7 @@ contains
end do end do
!$omp end do !$omp end do
!$omp end parallel !$omp end parallel
if (v.ne.3000.or.w.ne.0) STOP 2 if (v.ne.3000.or.w.ne.0) stop 2
!$omp parallel num_threads (32) shared (v, w) !$omp parallel num_threads (32) shared (v, w)
! None of these cancel directives should actually cancel anything, ! None of these cancel directives should actually cancel anything,
! but the compiler shouldn't know that and thus should use cancellable ! but the compiler shouldn't know that and thus should use cancellable
...@@ -56,7 +56,7 @@ contains ...@@ -56,7 +56,7 @@ contains
!$omp do !$omp do
do i = 0, 999 do i = 0, 999
!$omp cancel do if (x(1)) !$omp cancel do if (x(1))
STOP 3 stop 3
end do end do
!$omp cancel parallel if (omp_get_thread_num ().eq.2.and.x(5)) !$omp cancel parallel if (omp_get_thread_num ().eq.2.and.x(5))
!$omp do !$omp do
...@@ -85,6 +85,6 @@ contains ...@@ -85,6 +85,6 @@ contains
!$omp end do !$omp end do
!$omp cancel parallel if (omp_get_thread_num ().eq.5.and.x(5)) !$omp cancel parallel if (omp_get_thread_num ().eq.5.and.x(5))
!$omp end parallel !$omp end parallel
if (v.ne.6000.or.w.ne.0) STOP 4 if (v.ne.6000.or.w.ne.0) stop 4
end subroutine end subroutine
end end
...@@ -5,6 +5,6 @@ ...@@ -5,6 +5,6 @@
!$omp parallel num_threads(32) !$omp parallel num_threads(32)
!$omp cancel parallel !$omp cancel parallel
if (omp_get_cancellation ()) STOP 1 if (omp_get_cancellation ()) stop 1
!$omp end parallel !$omp end parallel
end end
...@@ -7,16 +7,16 @@ ...@@ -7,16 +7,16 @@
!$omp parallel num_threads(32) !$omp parallel num_threads(32)
!$omp sections !$omp sections
!$omp cancel sections !$omp cancel sections
STOP 1 stop 1
!$omp section !$omp section
!$omp cancel sections !$omp cancel sections
STOP 2 stop 2
!$omp section !$omp section
!$omp cancel sections !$omp cancel sections
STOP 3 stop 3
!$omp section !$omp section
!$omp cancel sections !$omp cancel sections
STOP 4 stop 4
!$omp end sections !$omp end sections
!$omp end parallel !$omp end parallel
end if end if
......
...@@ -8,7 +8,7 @@ ...@@ -8,7 +8,7 @@
!$omp taskgroup !$omp taskgroup
!$omp task !$omp task
!$omp cancel taskgroup !$omp cancel taskgroup
STOP 1 stop 1
!$omp endtask !$omp endtask
!$omp endtaskgroup !$omp endtaskgroup
!$omp endparallel !$omp endparallel
......
...@@ -67,6 +67,6 @@ contains ...@@ -67,6 +67,6 @@ contains
l = l .or. f .ne. 'YY' .or. p .ne. 'm3' .or. r .ne. 'M3' l = l .or. f .ne. 'YY' .or. p .ne. 'm3' .or. r .ne. 'M3'
end if end if
!$omp end parallel !$omp end parallel
if (l) STOP 1 if (l) stop 1
end subroutine test end subroutine test
end end
...@@ -56,6 +56,6 @@ contains ...@@ -56,6 +56,6 @@ contains
l = l .or. t .ne. '456' l = l .or. t .ne. '456'
end if end if
!$omp end parallel !$omp end parallel
if (l) STOP 1 if (l) stop 1
end subroutine test end subroutine test
end end
...@@ -22,5 +22,5 @@ program collapse1 ...@@ -22,5 +22,5 @@ program collapse1
end do end do
end do end do
!$omp end parallel do !$omp end parallel do
if (l) STOP 1 if (l) stop 1
end program collapse1 end program collapse1
...@@ -25,7 +25,7 @@ firstdo: do i = 1, 3 ...@@ -25,7 +25,7 @@ firstdo: do i = 1, 3
end do end do
end do firstdo end do firstdo
!$omp end parallel do !$omp end parallel do
if (l) STOP 1 if (l) stop 1
end subroutine test1 end subroutine test1
subroutine test2 subroutine test2
...@@ -38,7 +38,7 @@ firstdo: do i = 1, 3 ...@@ -38,7 +38,7 @@ firstdo: do i = 1, 3
enddo enddo
enddo dokk enddo dokk
115 continue 115 continue
if (any(a(1:3,1:3,1:3).ne.1)) STOP 2 if (any(a(1:3,1:3,1:3).ne.1)) stop 2
!$omp do collapse(3) !$omp do collapse(3)
dol: do 120 l=1,3 dol: do 120 l=1,3
...@@ -48,7 +48,7 @@ firstdo: do i = 1, 3 ...@@ -48,7 +48,7 @@ firstdo: do i = 1, 3
enddo enddo
enddo doll enddo doll
120 end do dol 120 end do dol
if (any(a(1:3,1:3,1:3).ne.2)) STOP 3 if (any(a(1:3,1:3,1:3).ne.2)) stop 3
end subroutine test2 end subroutine test2
end program collapse2 end program collapse2
...@@ -24,8 +24,8 @@ contains ...@@ -24,8 +24,8 @@ contains
end do end do
end do end do
end do end do
if (i.ne.7.or.j.ne.5.or.k.ne.19) STOP 1 if (i.ne.7.or.j.ne.5.or.k.ne.19) stop 1
if (m.ne.(600+40+18)) STOP 2 if (m.ne.(600+40+18)) stop 2
do i = 1, 7 do i = 1, 7
do j = -3, 5 do j = -3, 5
do k = 12, 19 do k = 12, 19
...@@ -56,8 +56,8 @@ contains ...@@ -56,8 +56,8 @@ contains
end do end do
end do end do
end do end do
if (i.ne.7.or.j.ne.5.or.k.ne.19) STOP 3 if (i.ne.7.or.j.ne.5.or.k.ne.19) stop 3
if (m.ne.(600+40+18)) STOP 4 if (m.ne.(600+40+18)) stop 4
do i = 1, 7 do i = 1, 7
do j = -3, 5 do j = -3, 5
do k = 12, 19 do k = 12, 19
...@@ -88,8 +88,8 @@ contains ...@@ -88,8 +88,8 @@ contains
end do end do
end do end do
end do end do
if (i.ne.7.or.j.ne.5.or.k.ne.19) STOP 5 if (i.ne.7.or.j.ne.5.or.k.ne.19) stop 5
if (m.ne.(600+40+18)) STOP 6 if (m.ne.(600+40+18)) stop 6
do i = 1, 7 do i = 1, 7
do j = -3, 5 do j = -3, 5
do k = 12, 19 do k = 12, 19
...@@ -120,8 +120,8 @@ contains ...@@ -120,8 +120,8 @@ contains
end do end do
end do end do
end do end do
if (i.ne.7.or.j.ne.5.or.k.ne.19) STOP 7 if (i.ne.7.or.j.ne.5.or.k.ne.19) stop 7
if (m.ne.(600+40+18)) STOP 8 if (m.ne.(600+40+18)) stop 8
do i = 1, 7 do i = 1, 7
do j = -3, 5 do j = -3, 5
do k = 12, 19 do k = 12, 19
...@@ -153,8 +153,8 @@ contains ...@@ -153,8 +153,8 @@ contains
end do end do
end do end do
end do end do
if (i.ne.7.or.j.ne.5.or.k.ne.19) STOP 9 if (i.ne.7.or.j.ne.5.or.k.ne.19) stop 9
if (m.ne.(600+40+18)) STOP 10 if (m.ne.(600+40+18)) stop 10
do i = 1, 7 do i = 1, 7
do j = -3, 5 do j = -3, 5
do k = 12, 19 do k = 12, 19
...@@ -186,8 +186,8 @@ contains ...@@ -186,8 +186,8 @@ contains
end do end do
end do end do
end do end do
if (i.ne.7.or.j.ne.5.or.k.ne.19) STOP 11 if (i.ne.7.or.j.ne.5.or.k.ne.19) stop 11
if (m.ne.(600+40+18)) STOP 12 if (m.ne.(600+40+18)) stop 12
do i = 1, 7 do i = 1, 7
do j = -3, 5 do j = -3, 5
do k = 12, 19 do k = 12, 19
......
...@@ -8,5 +8,5 @@ ...@@ -8,5 +8,5 @@
end do end do
end do end do
end do end do
if (i .ne. 18 .or. j .ne. 7 .or. k .ne. 6) STOP 1 if (i .ne. 18 .or. j .ne. 7 .or. k .ne. 6) stop 1
end end
...@@ -26,7 +26,7 @@ ...@@ -26,7 +26,7 @@
l = l .or. p .ne. 3 l = l .or. p .ne. 3
!$omp end parallel !$omp end parallel
if (l) STOP 1 if (l) stop 1
l = .false. l = .false.
!$omp parallel num_threads (2) reduction (.or.:l) default (private) !$omp parallel num_threads (2) reduction (.or.:l) default (private)
...@@ -41,6 +41,6 @@ ...@@ -41,6 +41,6 @@
l = l .or. p .ne. 3 * omp_get_thread_num () + 5 l = l .or. p .ne. 3 * omp_get_thread_num () + 5
!$omp end parallel !$omp end parallel
if (l) STOP 2 if (l) stop 2
end end
...@@ -27,5 +27,5 @@ ...@@ -27,5 +27,5 @@
l = l .or. (p .ne. d + 1) l = l .or. (p .ne. d + 1)
!$omp end parallel !$omp end parallel
if (l) STOP 1 if (l) stop 1
end end
...@@ -18,7 +18,7 @@ ...@@ -18,7 +18,7 @@
l = l .or. (p .ne. (2 + omp_get_thread_num ())) l = l .or. (p .ne. (2 + omp_get_thread_num ()))
!$omp end parallel !$omp end parallel
if (l) STOP 1 if (l) stop 1
l = .false. l = .false.
ip = loc (a) ip = loc (a)
...@@ -31,6 +31,6 @@ ...@@ -31,6 +31,6 @@
l = l .or. (p .ne. (2 + i)) l = l .or. (p .ne. (2 + i))
end do end do
if (l) STOP 2 if (l) stop 2
if (p .ne. 3) STOP 3 if (p .ne. 3) stop 3
end end
...@@ -61,7 +61,7 @@ end module declare_simd_1_mod ...@@ -61,7 +61,7 @@ end module declare_simd_1_mod
do i = 1, 128 do i = 1, 128
b(i) = bar (a(i), 2 * i, b(i)) b(i) = bar (a(i), 2 * i, b(i))
end do end do
if (any (b.ne.d)) STOP 1 if (any (b.ne.d)) stop 1
!$omp simd !$omp simd
do i = 1, 128 do i = 1, 128
b(i) = i * 2.0 b(i) = i * 2.0
...@@ -71,7 +71,7 @@ end module declare_simd_1_mod ...@@ -71,7 +71,7 @@ end module declare_simd_1_mod
b(i) = baz (7.0_8, 2, b(i)) b(i) = baz (7.0_8, 2, b(i))
end do end do
do i = 1, 128 do i = 1, 128
if (b(i).ne.(7.0 + 4.0 * i)) STOP 2 if (b(i).ne.(7.0 + 4.0 * i)) stop 2
end do end do
contains contains
function baz (x, y, z) function baz (x, y, z)
......
...@@ -17,6 +17,6 @@ subroutine bar ...@@ -17,6 +17,6 @@ subroutine bar
b(i) = foo (7.0_8, 5 * i, b(i)) b(i) = foo (7.0_8, 5 * i, b(i))
end do end do
do i = 1, 128 do i = 1, 128
if (b(i).ne.(7.0 + 10.0 * i * i)) STOP 1 if (b(i).ne.(7.0 + 10.0 * i * i)) stop 1
end do end do
end subroutine bar end subroutine bar
...@@ -14,5 +14,5 @@ subroutine foo ...@@ -14,5 +14,5 @@ subroutine foo
!$omp end target !$omp end target
!$omp target update from(var_x) !$omp target update from(var_x)
if (var_x /= 20) STOP 1 if (var_x /= 20) stop 1
end subroutine foo end subroutine foo
...@@ -21,7 +21,7 @@ contains ...@@ -21,7 +21,7 @@ contains
x = 2 x = 2
!$omp end task !$omp end task
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 1 if (x.ne.2) stop 1
!$omp end task !$omp end task
!$omp end single !$omp end single
!$omp end parallel !$omp end parallel
...@@ -36,7 +36,7 @@ contains ...@@ -36,7 +36,7 @@ contains
x = 2 x = 2
!$omp end task !$omp end task
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 2 if (x.ne.2) stop 2
!$omp end task !$omp end task
!$omp taskwait !$omp taskwait
!$omp end single !$omp end single
...@@ -52,7 +52,7 @@ contains ...@@ -52,7 +52,7 @@ contains
x = 2 x = 2
!$omp endtask !$omp endtask
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 3 if (x.ne.2) stop 3
!$omp endtask !$omp endtask
!$omp endsingle !$omp endsingle
!$omp endparallel !$omp endparallel
...@@ -67,7 +67,7 @@ contains ...@@ -67,7 +67,7 @@ contains
x = 2 x = 2
!$omp end task !$omp end task
!$omp task depend(in: x) !$omp task depend(in: x)
if (x.ne.1) STOP 4 if (x.ne.1) stop 4
!$omp end task !$omp end task
!$omp end single !$omp end single
!$omp end parallel !$omp end parallel
...@@ -79,7 +79,7 @@ contains ...@@ -79,7 +79,7 @@ contains
!$omp parallel !$omp parallel
!$omp single !$omp single
!$omp task shared(x) depend(in: x) !$omp task shared(x) depend(in: x)
if (x.ne.1) STOP 5 if (x.ne.1) stop 5
!$omp end task !$omp end task
!$omp task shared(x) depend(out: x) !$omp task shared(x) depend(out: x)
x = 2 x = 2
...@@ -95,7 +95,7 @@ contains ...@@ -95,7 +95,7 @@ contains
x = 1 x = 1
!$omp taskgroup !$omp taskgroup
!$omp task shared(x) depend(in: x) !$omp task shared(x) depend(in: x)
if (x.ne.1) STOP 6 if (x.ne.1) stop 6
!$omp end task !$omp end task
!$omp task shared(x) depend(out: x) !$omp task shared(x) depend(out: x)
x = 2 x = 2
...@@ -111,7 +111,7 @@ contains ...@@ -111,7 +111,7 @@ contains
x = 1 x = 1
!$omp single !$omp single
!$omp task shared(x) depend(in: x) !$omp task shared(x) depend(in: x)
if (x.ne.1) STOP 7 if (x.ne.1) stop 7
!$omp end task !$omp end task
!$omp task shared(x) depend(out: x) !$omp task shared(x) depend(out: x)
x = 2 x = 2
...@@ -132,7 +132,7 @@ contains ...@@ -132,7 +132,7 @@ contains
x = 2 x = 2
!$omp end task !$omp end task
!$omp taskwait !$omp taskwait
if (x.ne.2) STOP 8 if (x.ne.2) stop 8
!$omp end single !$omp end single
!$omp end parallel !$omp end parallel
end subroutine outdep end subroutine outdep
...@@ -146,13 +146,13 @@ contains ...@@ -146,13 +146,13 @@ contains
x = 2 x = 2
!$omp end task !$omp end task
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 9 if (x.ne.2) stop 9
!$omp end task !$omp end task
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 10 if (x.ne.2) stop 10
!$omp end task !$omp end task
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 11 if (x.ne.2) stop 11
!$omp end task !$omp end task
!$omp end single !$omp end single
!$omp end parallel !$omp end parallel
...@@ -167,13 +167,13 @@ contains ...@@ -167,13 +167,13 @@ contains
x = 2; x = 2;
!$omp end task !$omp end task
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 12 if (x.ne.2) stop 12
!$omp end task !$omp end task
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 13 if (x.ne.2) stop 13
!$omp end task !$omp end task
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 14 if (x.ne.2) stop 14
!$omp end task !$omp end task
!$omp taskwait !$omp taskwait
!$omp end single !$omp end single
...@@ -189,13 +189,13 @@ contains ...@@ -189,13 +189,13 @@ contains
x = 2 x = 2
!$omp end task !$omp end task
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 15 if (x.ne.2) stop 15
!$omp end task !$omp end task
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 16 if (x.ne.2) stop 16
!$omp end task !$omp end task
!$omp task shared (x) depend(in: x) !$omp task shared (x) depend(in: x)
if (x.ne.2) STOP 17 if (x.ne.2) stop 17
!$omp end task !$omp end task
!$omp end single !$omp end single
!$omp end parallel !$omp end parallel
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
!$omp single !$omp single
!$omp taskgroup !$omp taskgroup
!$omp task depend(in: x(:, :)) !$omp task depend(in: x(:, :))
if (y.ne.1) STOP 1 if (y.ne.1) stop 1
!$omp end task !$omp end task
!$omp task depend(out: x(:, :)) !$omp task depend(out: x(:, :))
y = 2 y = 2
...@@ -14,7 +14,7 @@ ...@@ -14,7 +14,7 @@
!$omp end taskgroup !$omp end taskgroup
!$omp taskgroup !$omp taskgroup
!$omp task depend(in: x(4, 7)) !$omp task depend(in: x(4, 7))
if (y.ne.2) STOP 2 if (y.ne.2) stop 2
!$omp end task !$omp end task
!$omp task depend(out: x(4:4, 7:7)) !$omp task depend(out: x(4:4, 7:7))
y = 3 y = 3
...@@ -22,7 +22,7 @@ ...@@ -22,7 +22,7 @@
!$omp end taskgroup !$omp end taskgroup
!$omp taskgroup !$omp taskgroup
!$omp task depend(in: x(4:, 8:)) !$omp task depend(in: x(4:, 8:))
if (y.ne.3) STOP 3 if (y.ne.3) stop 3
!$omp end task !$omp end task
!$omp task depend(out: x(4:6, 8:12)) !$omp task depend(out: x(4:6, 8:12))
y = 4 y = 4
...@@ -30,5 +30,5 @@ ...@@ -30,5 +30,5 @@
!$omp end taskgroup !$omp end taskgroup
!$omp end single !$omp end single
!$omp end parallel !$omp end parallel
if (y.ne.4) STOP 4 if (y.ne.4) stop 4
end end
...@@ -13,7 +13,7 @@ contains ...@@ -13,7 +13,7 @@ contains
!$omp single !$omp single
!$omp taskgroup !$omp taskgroup
!$omp task depend(in: x) !$omp task depend(in: x)
if (y.ne.1) STOP 1 if (y.ne.1) stop 1
!$omp end task !$omp end task
!$omp task depend(out: x(1:2, 1:3)) !$omp task depend(out: x(1:2, 1:3))
y = 2 y = 2
...@@ -21,7 +21,7 @@ contains ...@@ -21,7 +21,7 @@ contains
!$omp end taskgroup !$omp end taskgroup
!$omp taskgroup !$omp taskgroup
!$omp task depend(in: z) !$omp task depend(in: z)
if (y.ne.2) STOP 2 if (y.ne.2) stop 2
!$omp end task !$omp end task
!$omp task depend(out: z(-2:3, 2:4)) !$omp task depend(out: z(-2:3, 2:4))
y = 3 y = 3
...@@ -29,7 +29,7 @@ contains ...@@ -29,7 +29,7 @@ contains
!$omp end taskgroup !$omp end taskgroup
!$omp taskgroup !$omp taskgroup
!$omp task depend(in: x) !$omp task depend(in: x)
if (y.ne.3) STOP 3 if (y.ne.3) stop 3
!$omp end task !$omp end task
!$omp task depend(out: x(1:, 1:)) !$omp task depend(out: x(1:, 1:))
y = 4 y = 4
...@@ -37,6 +37,6 @@ contains ...@@ -37,6 +37,6 @@ contains
!$omp end taskgroup !$omp end taskgroup
!$omp end single !$omp end single
!$omp end parallel !$omp end parallel
if (y.ne.4) STOP 4 if (y.ne.4) stop 4
end subroutine end subroutine
end end
...@@ -47,7 +47,7 @@ ...@@ -47,7 +47,7 @@
!$omp end parallel !$omp end parallel
if (any (a .ne. b)) STOP 1 if (any (a .ne. b)) stop 1
a = -1 a = -1
!$omp parallel num_threads (4) !$omp parallel num_threads (4)
...@@ -79,7 +79,7 @@ ...@@ -79,7 +79,7 @@
!$omp end parallel !$omp end parallel
if (any (a .ne. b)) STOP 2 if (any (a .ne. b)) stop 2
a = -1 a = -1
!$omp parallel num_threads (4) !$omp parallel num_threads (4)
...@@ -111,7 +111,7 @@ ...@@ -111,7 +111,7 @@
!$omp end parallel !$omp end parallel
if (any (a .ne. b)) STOP 3 if (any (a .ne. b)) stop 3
a = -1 a = -1
!$omp parallel num_threads (4) !$omp parallel num_threads (4)
...@@ -143,7 +143,7 @@ ...@@ -143,7 +143,7 @@
!$omp end parallel !$omp end parallel
if (any (a .ne. b)) STOP 4 if (any (a .ne. b)) stop 4
a = -1 a = -1
!$omp parallel num_threads (4) !$omp parallel num_threads (4)
...@@ -175,5 +175,5 @@ ...@@ -175,5 +175,5 @@
!$omp end parallel !$omp end parallel
if (any (a .ne. b)) STOP 5 if (any (a .ne. b)) stop 5
end end
...@@ -86,7 +86,7 @@ ...@@ -86,7 +86,7 @@
!$omp end parallel !$omp end parallel
if (any (a .ne. b) .or. k) STOP 1 if (any (a .ne. b) .or. k) stop 1
a = -1 a = -1
k = .false. k = .false.
j = 8 j = 8
...@@ -155,7 +155,7 @@ ...@@ -155,7 +155,7 @@
!$omp end parallel !$omp end parallel
if (any (a .ne. b) .or. k) STOP 2 if (any (a .ne. b) .or. k) stop 2
a = -1 a = -1
k = .false. k = .false.
j = 8 j = 8
...@@ -224,7 +224,7 @@ ...@@ -224,7 +224,7 @@
!$omp end parallel !$omp end parallel
if (any (a .ne. b) .or. k) STOP 3 if (any (a .ne. b) .or. k) stop 3
a = -1 a = -1
k = .false. k = .false.
j = 8 j = 8
...@@ -293,7 +293,7 @@ ...@@ -293,7 +293,7 @@
!$omp end parallel !$omp end parallel
if (any (a .ne. b) .or. k) STOP 4 if (any (a .ne. b) .or. k) stop 4
a = -1 a = -1
k = .false. k = .false.
j = 8 j = 8
...@@ -362,5 +362,5 @@ ...@@ -362,5 +362,5 @@
!$omp end parallel !$omp end parallel
if (any (a .ne. b) .or. k) STOP 5 if (any (a .ne. b) .or. k) stop 5
end end
...@@ -33,7 +33,7 @@ program main ...@@ -33,7 +33,7 @@ program main
do concurrent (i = 1:nsplit) do concurrent (i = 1:nsplit)
pi(i) = sum(compute( low(i), high(i) )) pi(i) = sum(compute( low(i), high(i) ))
end do end do
if (abs (sum(pi) - atan(1.0d0)) > 1e-5) STOP 1 if (abs (sum(pi) - atan(1.0d0)) > 1e-5) stop 1
contains contains
......
...@@ -17,14 +17,14 @@ ...@@ -17,14 +17,14 @@
if (i.gt.1) then if (i.gt.1) then
!$omp atomic read !$omp atomic read
l = a(i - 1) l = a(i - 1)
if (l.lt.2) STOP 1 if (l.lt.2) stop 1
end if end if
!$omp atomic write !$omp atomic write
a(i) = 2 a(i) = 2
if (i.lt.N) then if (i.lt.N) then
!$omp atomic read !$omp atomic read
l = a(i + 1) l = a(i + 1)
if (l.eq.3) STOP 2 if (l.eq.3) stop 2
end if end if
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp atomic write !$omp atomic write
...@@ -43,19 +43,19 @@ ...@@ -43,19 +43,19 @@
if (j.gt.2.and.k.gt.2) then if (j.gt.2.and.k.gt.2) then
!$omp atomic read !$omp atomic read
l = b(i,j-2,k-1) l = b(i,j-2,k-1)
if (l.lt.2) STOP 3 if (l.lt.2) stop 3
end if end if
!$omp atomic write !$omp atomic write
b(i,j,k) = 2 b(i,j,k) = 2
if (i.gt.4.and.j.gt.2.and.k.lt.4) then if (i.gt.4.and.j.gt.2.and.k.lt.4) then
!$omp atomic read !$omp atomic read
l = b(i-2,j-2, k+1) l = b(i-2,j-2, k+1)
if (l.lt.2) STOP 4 if (l.lt.2) stop 4
end if end if
if (i.gt.5.and.j.le.N/16-3.and.k.eq.4) then if (i.gt.5.and.j.le.N/16-3.and.k.eq.4) then
!$omp atomic read !$omp atomic read
l = b( i - 3, j+2, k-2) l = b( i - 3, j+2, k-2)
if (l.lt.2) STOP 5 if (l.lt.2) stop 5
end if end if
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp atomic write !$omp atomic write
...@@ -94,19 +94,19 @@ ...@@ -94,19 +94,19 @@
if (k.le.5) then if (k.le.5) then
!$omp atomic read !$omp atomic read
l = c(i, j, k + 2) l = c(i, j, k + 2)
if (l.lt.2) STOP 6 if (l.lt.2) stop 6
end if end if
!$omp atomic write !$omp atomic write
c(i, j, k) = 2 c(i, j, k) = 2
if (i.ge.3.and.j.lt.8.and.k.ge.5) then if (i.ge.3.and.j.lt.8.and.k.ge.5) then
!$omp atomic read !$omp atomic read
l = c(i - 2, j + 1, k - 4) l = c(i - 2, j + 1, k - 4)
if (l.lt.2) STOP 7 if (l.lt.2) stop 7
end if end if
if (i.ge.2.and.j.ge.5.and.k.ge.3) then if (i.ge.2.and.j.ge.5.and.k.ge.3) then
!$omp atomic read !$omp atomic read
l = c(i - 1, j - 2, k - 2) l = c(i - 1, j - 2, k - 2)
if (l.lt.2) STOP 8 if (l.lt.2) stop 8
end if end if
!$omp ordered depend ( source ) !$omp ordered depend ( source )
!$omp atomic write !$omp atomic write
...@@ -137,13 +137,13 @@ ...@@ -137,13 +137,13 @@
do l = 0, d + 1 do l = 0, d + 1
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp ordered depend(sink: i-2,j+2,k-2,l) !$omp ordered depend(sink: i-2,j+2,k-2,l)
if (e.eq.0) STOP 9 if (e.eq.0) stop 9
end do end do
end do end do
end do end do
end do end do
!$omp single !$omp single
if (i.ne.1.or.j.ne.-1.or.k.ne.0) STOP 10 if (i.ne.1.or.j.ne.-1.or.k.ne.0) stop 10
i = 8; j = 9; k = 10 i = 8; j = 9; k = 10
!$omp end single !$omp end single
!$omp do ordered(4) collapse(2) lastprivate (i, j, k, m) !$omp do ordered(4) collapse(2) lastprivate (i, j, k, m)
...@@ -153,13 +153,13 @@ ...@@ -153,13 +153,13 @@
do m = 0, d-1 do m = 0, d-1
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp ordered depend(sink: i - 2, j + 2, k - 2, m) !$omp ordered depend(sink: i - 2, j + 2, k - 2, m)
STOP 11 stop 11
end do end do
end do end do
end do end do
end do end do
!$omp single !$omp single
if (i.ne.1.or.j.ne.-1.or.k.ne.2.or.m.ne.0) STOP 12 if (i.ne.1.or.j.ne.-1.or.k.ne.2.or.m.ne.0) stop 12
!$omp end single !$omp end single
!$omp do collapse(2) ordered(4) lastprivate (i,j,k) !$omp do collapse(2) ordered(4) lastprivate (i,j,k)
do i = 0, d do i = 0, d
...@@ -168,7 +168,7 @@ ...@@ -168,7 +168,7 @@
do l = 0, d + 3 do l = 0, d + 3
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp ordered depend(sink: i-2,j+2,k-2,l) !$omp ordered depend(sink: i-2,j+2,k-2,l)
if (e.eq.0) STOP 13 if (e.eq.0) stop 13
end do end do
end do end do
end do end do
...@@ -176,7 +176,7 @@ ...@@ -176,7 +176,7 @@
!$omp end do nowait !$omp end do nowait
!$omp do !$omp do
do i = 1, N do i = 1, N
if (a(i) .ne. 3) STOP 14 if (a(i) .ne. 3) stop 14
end do end do
!$omp end do nowait !$omp end do nowait
!$omp do collapse(2) private(k) !$omp do collapse(2) private(k)
...@@ -184,9 +184,9 @@ ...@@ -184,9 +184,9 @@
do j = 1, 8 do j = 1, 8
do k = 1, 4 do k = 1, 4
if (i.ge.3.and.i.lt.N/16.and.iand(j,1).ne.0.and.k.ge.2) then if (i.ge.3.and.i.lt.N/16.and.iand(j,1).ne.0.and.k.ge.2) then
if (b(i,j,k).ne.3) STOP 15 if (b(i,j,k).ne.3) stop 15
else else
if (b(i,j,k).ne.0) STOP 16 if (b(i,j,k).ne.0) stop 16
end if end if
end do end do
end do end do
...@@ -197,9 +197,9 @@ ...@@ -197,9 +197,9 @@
do j = 1, 8 do j = 1, 8
do k = 1, 4 do k = 1, 4
if (j.ge.3.and.iand(k,1).ne.0) then if (j.ge.3.and.iand(k,1).ne.0) then
if (c(i,j,k).ne.3) STOP 17 if (c(i,j,k).ne.3) stop 17
else else
if (c(i,j,k).ne.0) STOP 18 if (c(i,j,k).ne.0) stop 18
end if end if
end do end do
end do end do
......
...@@ -20,14 +20,14 @@ ...@@ -20,14 +20,14 @@
if (i.gt.2) then if (i.gt.2) then
!$omp atomic read !$omp atomic read
l = a(i - 1) l = a(i - 1)
if (l.lt.2) STOP 1 if (l.lt.2) stop 1
end if end if
!$omp atomic write !$omp atomic write
a(i) = 2 a(i) = 2
if (i.lt.N) then if (i.lt.N) then
!$omp atomic read !$omp atomic read
l = a(i + 1) l = a(i + 1)
if (l.eq.3) STOP 2 if (l.eq.3) stop 2
end if end if
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp atomic write !$omp atomic write
...@@ -46,19 +46,19 @@ ...@@ -46,19 +46,19 @@
if (j.gt.2.and.k.gt.2) then if (j.gt.2.and.k.gt.2) then
!$omp atomic read !$omp atomic read
l = b(i,j-2,k-1) l = b(i,j-2,k-1)
if (l.lt.2) STOP 3 if (l.lt.2) stop 3
end if end if
!$omp atomic write !$omp atomic write
b(i,j,k) = 2 b(i,j,k) = 2
if (i.gt.5.and.j.gt.2.and.k.lt.4) then if (i.gt.5.and.j.gt.2.and.k.lt.4) then
!$omp atomic read !$omp atomic read
l = b(i-2,j-2, k+1) l = b(i-2,j-2, k+1)
if (l.lt.2) STOP 4 if (l.lt.2) stop 4
end if end if
if (i.gt.6.and.j.le.N/16-3.and.k.eq.4) then if (i.gt.6.and.j.le.N/16-3.and.k.eq.4) then
!$omp atomic read !$omp atomic read
l = b( i - 3, j+2, k-2) l = b( i - 3, j+2, k-2)
if (l.lt.2) STOP 5 if (l.lt.2) stop 5
end if end if
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp atomic write !$omp atomic write
...@@ -97,19 +97,19 @@ ...@@ -97,19 +97,19 @@
if (k.le.5) then if (k.le.5) then
!$omp atomic read !$omp atomic read
l = c(i, j, k + 2) l = c(i, j, k + 2)
if (l.lt.2) STOP 6 if (l.lt.2) stop 6
end if end if
!$omp atomic write !$omp atomic write
c(i, j, k) = 2 c(i, j, k) = 2
if (i.ge.5.and.j.lt.8.and.k.ge.5) then if (i.ge.5.and.j.lt.8.and.k.ge.5) then
!$omp atomic read !$omp atomic read
l = c(i - 2, j + 1, k - 4) l = c(i - 2, j + 1, k - 4)
if (l.lt.2) STOP 7 if (l.lt.2) stop 7
end if end if
if (i.ge.4.and.j.ge.5.and.k.ge.3) then if (i.ge.4.and.j.ge.5.and.k.ge.3) then
!$omp atomic read !$omp atomic read
l = c(i - 1, j - 2, k - 2) l = c(i - 1, j - 2, k - 2)
if (l.lt.2) STOP 8 if (l.lt.2) stop 8
end if end if
!$omp ordered depend ( source ) !$omp ordered depend ( source )
!$omp atomic write !$omp atomic write
...@@ -145,19 +145,19 @@ ...@@ -145,19 +145,19 @@
if (k.gt.2.and.i.gt.4) then if (k.gt.2.and.i.gt.4) then
!$omp atomic read !$omp atomic read
l = g(j,k-2,i-1) l = g(j,k-2,i-1)
if (l.lt.2) STOP 9 if (l.lt.2) stop 9
end if end if
!$omp atomic write !$omp atomic write
g(j,k,i) = 2 g(j,k,i) = 2
if (j.gt.2.and.k.gt.2.and.i.lt.6) then if (j.gt.2.and.k.gt.2.and.i.lt.6) then
!$omp atomic read !$omp atomic read
l = g(j-2,k-2, i+1) l = g(j-2,k-2, i+1)
if (l.lt.2) STOP 10 if (l.lt.2) stop 10
end if end if
if (j.gt.3.and.k.le.N/16-3.and.i.eq.6) then if (j.gt.3.and.k.le.N/16-3.and.i.eq.6) then
!$omp atomic read !$omp atomic read
l = g( j - 3, k+2, i-2) l = g( j - 3, k+2, i-2)
if (l.lt.2) STOP 11 if (l.lt.2) stop 11
end if end if
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp atomic write !$omp atomic write
...@@ -173,13 +173,13 @@ ...@@ -173,13 +173,13 @@
do l = 0, d + 1 do l = 0, d + 1
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp ordered depend(sink: i-2,j+2,k-2,l) !$omp ordered depend(sink: i-2,j+2,k-2,l)
if (e.eq.0) STOP 12 if (e.eq.0) stop 12
end do end do
end do end do
end do end do
end do end do
!$omp single !$omp single
if (i.ne.3.or.j.ne.-1.or.k.ne.0) STOP 13 if (i.ne.3.or.j.ne.-1.or.k.ne.0) stop 13
i = 8; j = 9; k = 10 i = 8; j = 9; k = 10
!$omp end single !$omp end single
!$omp do ordered(4) collapse(2) lastprivate (i, j, k, m) !$omp do ordered(4) collapse(2) lastprivate (i, j, k, m)
...@@ -189,13 +189,13 @@ ...@@ -189,13 +189,13 @@
do m = 0, d-1 do m = 0, d-1
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp ordered depend(sink: i - 2, j + 2, k - 2, m) !$omp ordered depend(sink: i - 2, j + 2, k - 2, m)
STOP 14 stop 14
end do end do
end do end do
end do end do
end do end do
!$omp single !$omp single
if (i.ne.3.or.j.ne.-1.or.k.ne.2.or.m.ne.0) STOP 15 if (i.ne.3.or.j.ne.-1.or.k.ne.2.or.m.ne.0) stop 15
!$omp end single !$omp end single
!$omp do collapse(2) ordered(4) lastprivate (i,j,k) !$omp do collapse(2) ordered(4) lastprivate (i,j,k)
do i = 2, f + 2 do i = 2, f + 2
...@@ -204,18 +204,18 @@ ...@@ -204,18 +204,18 @@
do l = 0, d + 3 do l = 0, d + 3
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp ordered depend(sink: i-2,j+2,k-2,l) !$omp ordered depend(sink: i-2,j+2,k-2,l)
if (e.eq.0) STOP 16 if (e.eq.0) stop 16
end do end do
end do end do
end do end do
end do end do
!$omp end do nowait !$omp end do nowait
!$omp single !$omp single
if (a(1) .ne. 0) STOP 17 if (a(1) .ne. 0) stop 17
!$omp end single nowait !$omp end single nowait
!$omp do !$omp do
do i = 2, N do i = 2, N
if (a(i) .ne. 3) STOP 18 if (a(i) .ne. 3) stop 18
end do end do
!$omp end do nowait !$omp end do nowait
!$omp do collapse(2) private(k) !$omp do collapse(2) private(k)
...@@ -223,9 +223,9 @@ ...@@ -223,9 +223,9 @@
do j = 1, 8 do j = 1, 8
do k = 1, 4 do k = 1, 4
if (i.ge.4.and.i.lt.N/16.and.iand(j,1).ne.0.and.k.ge.2) then if (i.ge.4.and.i.lt.N/16.and.iand(j,1).ne.0.and.k.ge.2) then
if (b(i,j,k).ne.3) STOP 19 if (b(i,j,k).ne.3) stop 19
else else
if (b(i,j,k).ne.0) STOP 20 if (b(i,j,k).ne.0) stop 20
end if end if
end do end do
end do end do
...@@ -236,9 +236,9 @@ ...@@ -236,9 +236,9 @@
do j = 1, 8 do j = 1, 8
do k = 1, 4 do k = 1, 4
if (i.ge.3.and.j.ge.3.and.iand(k,1).ne.0) then if (i.ge.3.and.j.ge.3.and.iand(k,1).ne.0) then
if (c(i,j,k).ne.3) STOP 21 if (c(i,j,k).ne.3) stop 21
else else
if (c(i,j,k).ne.0) STOP 22 if (c(i,j,k).ne.0) stop 22
end if end if
end do end do
end do end do
...@@ -249,9 +249,9 @@ ...@@ -249,9 +249,9 @@
do j = 1, 8 do j = 1, 8
do k = 1, 6 do k = 1, 6
if (i.lt.N/16.and.iand(j,1).ne.0.and.k.ge.4) then if (i.lt.N/16.and.iand(j,1).ne.0.and.k.ge.4) then
if (g(i,j,k).ne.3) STOP 23 if (g(i,j,k).ne.3) stop 23
else else
if (g(i,j,k).ne.0) STOP 24 if (g(i,j,k).ne.0) stop 24
end if end if
end do end do
end do end do
......
...@@ -20,14 +20,14 @@ ...@@ -20,14 +20,14 @@
if (i.gt.2) then if (i.gt.2) then
!$omp atomic read !$omp atomic read
l = a(i - 1) l = a(i - 1)
if (l.lt.2) STOP 1 if (l.lt.2) stop 1
end if end if
!$omp atomic write !$omp atomic write
a(i) = 2 a(i) = 2
if (i.lt.N) then if (i.lt.N) then
!$omp atomic read !$omp atomic read
l = a(i + 1) l = a(i + 1)
if (l.eq.3) STOP 2 if (l.eq.3) stop 2
end if end if
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp atomic write !$omp atomic write
...@@ -46,19 +46,19 @@ ...@@ -46,19 +46,19 @@
if (j.gt.2.and.k.gt.2) then if (j.gt.2.and.k.gt.2) then
!$omp atomic read !$omp atomic read
l = b(i,j-2,k-1) l = b(i,j-2,k-1)
if (l.lt.2) STOP 3 if (l.lt.2) stop 3
end if end if
!$omp atomic write !$omp atomic write
b(i,j,k) = 2 b(i,j,k) = 2
if (i.gt.5.and.j.gt.2.and.k.lt.4) then if (i.gt.5.and.j.gt.2.and.k.lt.4) then
!$omp atomic read !$omp atomic read
l = b(i-2,j-2, k+1) l = b(i-2,j-2, k+1)
if (l.lt.2) STOP 4 if (l.lt.2) stop 4
end if end if
if (i.gt.6.and.j.le.N/16-3.and.k.eq.4) then if (i.gt.6.and.j.le.N/16-3.and.k.eq.4) then
!$omp atomic read !$omp atomic read
l = b( i - 3, j+2, k-2) l = b( i - 3, j+2, k-2)
if (l.lt.2) STOP 5 if (l.lt.2) stop 5
end if end if
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp atomic write !$omp atomic write
...@@ -97,19 +97,19 @@ ...@@ -97,19 +97,19 @@
if (k.le.5) then if (k.le.5) then
!$omp atomic read !$omp atomic read
l = c(i, j, k + 2) l = c(i, j, k + 2)
if (l.lt.2) STOP 6 if (l.lt.2) stop 6
end if end if
!$omp atomic write !$omp atomic write
c(i, j, k) = 2 c(i, j, k) = 2
if (i.ge.5.and.j.lt.8.and.k.ge.5) then if (i.ge.5.and.j.lt.8.and.k.ge.5) then
!$omp atomic read !$omp atomic read
l = c(i - 2, j + 1, k - 4) l = c(i - 2, j + 1, k - 4)
if (l.lt.2) STOP 7 if (l.lt.2) stop 7
end if end if
if (i.ge.4.and.j.ge.5.and.k.ge.3) then if (i.ge.4.and.j.ge.5.and.k.ge.3) then
!$omp atomic read !$omp atomic read
l = c(i - 1, j - 2, k - 2) l = c(i - 1, j - 2, k - 2)
if (l.lt.2) STOP 8 if (l.lt.2) stop 8
end if end if
!$omp ordered depend ( source ) !$omp ordered depend ( source )
!$omp atomic write !$omp atomic write
...@@ -145,19 +145,19 @@ ...@@ -145,19 +145,19 @@
if (k.gt.2.and.i.gt.4) then if (k.gt.2.and.i.gt.4) then
!$omp atomic read !$omp atomic read
l = g(j,k-2,i-1) l = g(j,k-2,i-1)
if (l.lt.2) STOP 9 if (l.lt.2) stop 9
end if end if
!$omp atomic write !$omp atomic write
g(j,k,i) = 2 g(j,k,i) = 2
if (j.gt.2.and.k.gt.2.and.i.lt.6) then if (j.gt.2.and.k.gt.2.and.i.lt.6) then
!$omp atomic read !$omp atomic read
l = g(j-2,k-2, i+1) l = g(j-2,k-2, i+1)
if (l.lt.2) STOP 10 if (l.lt.2) stop 10
end if end if
if (j.gt.3.and.k.le.N/16-3.and.i.eq.6) then if (j.gt.3.and.k.le.N/16-3.and.i.eq.6) then
!$omp atomic read !$omp atomic read
l = g( j - 3, k+2, i-2) l = g( j - 3, k+2, i-2)
if (l.lt.2) STOP 11 if (l.lt.2) stop 11
end if end if
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp atomic write !$omp atomic write
...@@ -173,13 +173,13 @@ ...@@ -173,13 +173,13 @@
do l = 0, d + 1, 1 + d do l = 0, d + 1, 1 + d
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp ordered depend(sink: i-2,j+2,k-2,l) !$omp ordered depend(sink: i-2,j+2,k-2,l)
if (e.eq.0) STOP 12 if (e.eq.0) stop 12
end do end do
end do end do
end do end do
end do end do
!$omp single !$omp single
if (i.ne.3.or.j.ne.-1.or.k.ne.0) STOP 13 if (i.ne.3.or.j.ne.-1.or.k.ne.0) stop 13
i = 8; j = 9; k = 10 i = 8; j = 9; k = 10
!$omp end single !$omp end single
!$omp do ordered(4) collapse(2) lastprivate (i, j, k, m) !$omp do ordered(4) collapse(2) lastprivate (i, j, k, m)
...@@ -189,13 +189,13 @@ ...@@ -189,13 +189,13 @@
do m = 0, d-1, d+1 do m = 0, d-1, d+1
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp ordered depend(sink: i - 2, j + 2, k - 2, m) !$omp ordered depend(sink: i - 2, j + 2, k - 2, m)
STOP 14 stop 14
end do end do
end do end do
end do end do
end do end do
!$omp single !$omp single
if (i.ne.3.or.j.ne.-1.or.k.ne.2.or.m.ne.0) STOP 15 if (i.ne.3.or.j.ne.-1.or.k.ne.2.or.m.ne.0) stop 15
!$omp end single !$omp end single
!$omp do collapse(2) ordered(4) lastprivate (i,j,k) !$omp do collapse(2) ordered(4) lastprivate (i,j,k)
do i = 2, f + 2, 1 + f do i = 2, f + 2, 1 + f
...@@ -204,18 +204,18 @@ ...@@ -204,18 +204,18 @@
do l = 0, d + 3, d + 1 do l = 0, d + 3, d + 1
!$omp ordered depend(source) !$omp ordered depend(source)
!$omp ordered depend(sink: i-2,j+2,k-2,l) !$omp ordered depend(sink: i-2,j+2,k-2,l)
if (e.eq.0) STOP 16 if (e.eq.0) stop 16
end do end do
end do end do
end do end do
end do end do
!$omp end do nowait !$omp end do nowait
!$omp single !$omp single
if (a(1) .ne. 0) STOP 17 if (a(1) .ne. 0) stop 17
!$omp end single nowait !$omp end single nowait
!$omp do !$omp do
do i = 2, N do i = 2, N
if (a(i) .ne. 3) STOP 18 if (a(i) .ne. 3) stop 18
end do end do
!$omp end do nowait !$omp end do nowait
!$omp do collapse(2) private(k) !$omp do collapse(2) private(k)
...@@ -223,9 +223,9 @@ ...@@ -223,9 +223,9 @@
do j = 1, 8 do j = 1, 8
do k = 1, 4 do k = 1, 4
if (i.ge.4.and.i.lt.N/16.and.iand(j,1).ne.0.and.k.ge.2) then if (i.ge.4.and.i.lt.N/16.and.iand(j,1).ne.0.and.k.ge.2) then
if (b(i,j,k).ne.3) STOP 19 if (b(i,j,k).ne.3) stop 19
else else
if (b(i,j,k).ne.0) STOP 20 if (b(i,j,k).ne.0) stop 20
end if end if
end do end do
end do end do
...@@ -236,9 +236,9 @@ ...@@ -236,9 +236,9 @@
do j = 1, 8 do j = 1, 8
do k = 1, 4 do k = 1, 4
if (i.ge.3.and.j.ge.3.and.iand(k,1).ne.0) then if (i.ge.3.and.j.ge.3.and.iand(k,1).ne.0) then
if (c(i,j,k).ne.3) STOP 21 if (c(i,j,k).ne.3) stop 21
else else
if (c(i,j,k).ne.0) STOP 22 if (c(i,j,k).ne.0) stop 22
end if end if
end do end do
end do end do
...@@ -249,9 +249,9 @@ ...@@ -249,9 +249,9 @@
do j = 1, 8 do j = 1, 8
do k = 1, 6 do k = 1, 6
if (i.lt.N/16.and.iand(j,1).ne.0.and.k.ge.4) then if (i.lt.N/16.and.iand(j,1).ne.0.and.k.ge.4) then
if (g(i,j,k).ne.3) STOP 23 if (g(i,j,k).ne.3) stop 23
else else
if (g(i,j,k).ne.0) STOP 24 if (g(i,j,k).ne.0) stop 24
end if end if
end do end do
end do end do
......
...@@ -12,6 +12,6 @@ contains ...@@ -12,6 +12,6 @@ contains
p(9) = 777 p(9) = 777
!$omp end target !$omp end target
!$omp end target data !$omp end target data
if (A(3) /= 777 .or. A(9) /= 777) STOP 1 if (A(3) /= 777 .or. A(9) /= 777) stop 1
end subroutine end subroutine
end end
...@@ -13,6 +13,6 @@ contains ...@@ -13,6 +13,6 @@ contains
A(9) = 999 A(9) = 999
!$omp end target !$omp end target
!$omp end target data !$omp end target data
if (A(3) /= 777 .or. A(9) /= 999) STOP 1 if (A(3) /= 777 .or. A(9) /= 999) stop 1
end subroutine end subroutine
end end
...@@ -27,7 +27,7 @@ subroutine check () ...@@ -27,7 +27,7 @@ subroutine check ()
else else
err = (Y(i) - Z(i)) / Z(i) err = (Y(i) - Z(i)) / Z(i)
end if end if
if (err > EPS .or. err < -EPS) STOP 1 if (err > EPS .or. err < -EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -17,7 +17,7 @@ subroutine check (p, N) ...@@ -17,7 +17,7 @@ subroutine check (p, N)
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
...@@ -30,14 +30,14 @@ subroutine vec_mult (p, N) ...@@ -30,14 +30,14 @@ subroutine vec_mult (p, N)
!$omp target data map(to: v1, v2, N) map(from: p) !$omp target data map(to: v1, v2, N) map(from: p)
!$omp task shared(v1, v2, p) depend(out: v1, v2) !$omp task shared(v1, v2, p) depend(out: v1, v2)
!$omp target map(to: v1, v2, N) !$omp target map(to: v1, v2, N)
if (omp_is_initial_device ()) STOP 2 if (omp_is_initial_device ()) stop 2
allocate (v1(N), v2(N)) allocate (v1(N), v2(N))
call init (v1, v2, N) call init (v1, v2, N)
!$omp end target !$omp end target
!$omp end task !$omp end task
!$omp task shared(v1, v2, p) depend(in: v1, v2) !$omp task shared(v1, v2, p) depend(in: v1, v2)
!$omp target map(to: v1, v2, N) map(from: p) !$omp target map(to: v1, v2, N) map(from: p)
if (omp_is_initial_device ()) STOP 3 if (omp_is_initial_device ()) stop 3
!$omp parallel do !$omp parallel do
do i = 1, N do i = 1, N
p(i) = v1(i) * v2(i) p(i) = v1(i) * v2(i)
......
...@@ -26,8 +26,8 @@ end module ...@@ -26,8 +26,8 @@ end module
program e_53_1 program e_53_1
use e_53_1_mod, only : fib, fib_wrapper use e_53_1_mod, only : fib, fib_wrapper
if (fib (15) /= fib_wrapper (15)) STOP 1 if (fib (15) /= fib_wrapper (15)) stop 1
! Reduced from 25 to 23, otherwise execution runs out of thread stack on ! Reduced from 25 to 23, otherwise execution runs out of thread stack on
! Nvidia Titan V. ! Nvidia Titan V.
if (fib (23) /= fib_wrapper (23)) STOP 2 if (fib (23) /= fib_wrapper (23)) stop 2
end program end program
...@@ -8,7 +8,7 @@ program e_53_2 ...@@ -8,7 +8,7 @@ program e_53_2
! Nvidia Titan V. ! Nvidia Titan V.
x = fib (23) x = fib (23)
!$omp end target !$omp end target
if (x /= fib (23)) STOP 1 if (x /= fib (23)) stop 1
end program end program
integer recursive function fib (n) result (f) integer recursive function fib (n) result (f)
......
...@@ -21,7 +21,7 @@ subroutine check (p, N) ...@@ -21,7 +21,7 @@ subroutine check (p, N)
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -53,7 +53,7 @@ subroutine check (a, b) ...@@ -53,7 +53,7 @@ subroutine check (a, b)
else else
err = (a - b) / b err = (a - b) / b
end if end if
if (err > EPS .or. err < -EPS) STOP 1 if (err > EPS .or. err < -EPS) stop 1
end subroutine end subroutine
program e_53_4 program e_53_4
......
...@@ -68,7 +68,7 @@ subroutine check (a, b) ...@@ -68,7 +68,7 @@ subroutine check (a, b)
else else
err = (a - b) / b err = (a - b) / b
end if end if
if (err > EPS .or. err < -EPS) STOP 1 if (err > EPS .or. err < -EPS) stop 1
end subroutine end subroutine
program e_53_5 program e_53_5
......
...@@ -20,7 +20,7 @@ program e_57_1 ...@@ -20,7 +20,7 @@ program e_57_1
!$omp end target !$omp end target
!$omp end target data !$omp end target data
if (b /= 100 .or. .not. c .or. d) STOP 1 if (b /= 100 .or. .not. c .or. d) stop 1
a = a + 200 a = a + 200
b = 0 b = 0
...@@ -36,7 +36,7 @@ program e_57_1 ...@@ -36,7 +36,7 @@ program e_57_1
!$omp end target !$omp end target
!$omp end target data !$omp end target data
if (b /= 0 .or. c .or. d) STOP 2 if (b /= 0 .or. c .or. d) stop 2
a = a + 200 a = a + 200
b = 0 b = 0
...@@ -52,5 +52,5 @@ program e_57_1 ...@@ -52,5 +52,5 @@ program e_57_1
!$omp end target !$omp end target
!$omp end target data !$omp end target data
if (b /= 100 .or. .not. c .or. d) STOP 3 if (b /= 100 .or. .not. c .or. d) stop 3
end program end program
...@@ -15,10 +15,10 @@ program e_57_2 ...@@ -15,10 +15,10 @@ program e_57_2
end do end do
do i = 1, num do i = 1, num
if (offload(i)) STOP 1 if (offload(i)) stop 1
end do end do
do i = num+1, N do i = num+1, N
if (.not. offload(i)) STOP 2 if (.not. offload(i)) stop 2
end do end do
end program end program
...@@ -11,11 +11,11 @@ program e_57_3 ...@@ -11,11 +11,11 @@ program e_57_3
!$omp target map(from: res) !$omp target map(from: res)
res = omp_is_initial_device () res = omp_is_initial_device ()
!$omp end target !$omp end target
if (res) STOP 1 if (res) stop 1
call omp_set_default_device (omp_get_num_devices ()) call omp_set_default_device (omp_get_num_devices ())
!$omp target map(from: res) !$omp target map(from: res)
res = omp_is_initial_device () res = omp_is_initial_device ()
!$omp end target !$omp end target
if (.not. res) STOP 2 if (.not. res) stop 2
end program end program
...@@ -28,7 +28,7 @@ contains ...@@ -28,7 +28,7 @@ contains
double precision :: diff, a(*), b(*) double precision :: diff, a(*), b(*)
do i = 1, n do i = 1, n
diff = a(i) - b(i) diff = a(i) - b(i)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -49,7 +49,7 @@ contains ...@@ -49,7 +49,7 @@ contains
double precision :: diff, a(*), b(*) double precision :: diff, a(*), b(*)
do i = 1, n do i = 1, n
diff = a(i) - b(i) diff = a(i) - b(i)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
end module end module
......
...@@ -57,6 +57,6 @@ program SIMD3 ...@@ -57,6 +57,6 @@ program SIMD3
diff = sum - sum_ref diff = sum - sum_ref
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end program end program
...@@ -47,7 +47,7 @@ contains ...@@ -47,7 +47,7 @@ contains
real :: diff, a(*), b(*) real :: diff, a(*), b(*)
do i = 1, n do i = 1, n
diff = a(i) - b(i) diff = a(i) - b(i)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -56,7 +56,7 @@ contains ...@@ -56,7 +56,7 @@ contains
do j = 1, n do j = 1, n
do i = 1, n do i = 1, n
diff = a(i,j) - b(i,j) diff = a(i,j) - b(i,j)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end do end do
end subroutine end subroutine
......
...@@ -109,14 +109,14 @@ contains ...@@ -109,14 +109,14 @@ contains
real :: diff, a(*), b(*) real :: diff, a(*), b(*)
do i = 1, n do i = 1, n
diff = a(i) - b(i) diff = a(i) - b(i)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
subroutine checkint (a, b, n) subroutine checkint (a, b, n)
integer :: i, n, a(*), b(*) integer :: i, n, a(*), b(*)
do i = 1, n do i = 1, n
if (a(i) .ne. b(i)) STOP 2 if (a(i) .ne. b(i)) stop 2
end do end do
end subroutine end subroutine
......
...@@ -23,7 +23,7 @@ program fibonacci ...@@ -23,7 +23,7 @@ program fibonacci
call fib_ref (a_ref, N) call fib_ref (a_ref, N)
do i = 0, N-1 do i = 0, N-1
if (a(i) .ne. a_ref(i)) STOP 1 if (a(i) .ne. a_ref(i)) stop 1
end do end do
end program end program
......
...@@ -47,6 +47,6 @@ program simd_8f ...@@ -47,6 +47,6 @@ program simd_8f
diff = pri - 8237.25 diff = pri - 8237.25
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end program end program
...@@ -17,7 +17,7 @@ contains ...@@ -17,7 +17,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -17,7 +17,7 @@ contains ...@@ -17,7 +17,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -17,7 +17,7 @@ contains ...@@ -17,7 +17,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -17,7 +17,7 @@ contains ...@@ -17,7 +17,7 @@ contains
real, pointer, dimension(:) :: p real, pointer, dimension(:) :: p
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -19,7 +19,7 @@ contains ...@@ -19,7 +19,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
...@@ -29,7 +29,7 @@ contains ...@@ -29,7 +29,7 @@ contains
real :: p(N), v1(N), v2(N) real :: p(N), v1(N), v2(N)
call init (v1, v2, N) call init (v1, v2, N)
!$omp target if(N > THRESHOLD1) map(to: v1,v2) map(from: p) !$omp target if(N > THRESHOLD1) map(to: v1,v2) map(from: p)
if (omp_is_initial_device ()) STOP 2 if (omp_is_initial_device ()) stop 2
!$omp parallel do if(N > THRESHOLD2) !$omp parallel do if(N > THRESHOLD2)
do i = 1, N do i = 1, N
p(i) = v1(i) * v2(i) p(i) = v1(i) * v2(i)
......
...@@ -17,7 +17,7 @@ contains ...@@ -17,7 +17,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -26,7 +26,7 @@ contains ...@@ -26,7 +26,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - 2 * (i + 2.0) * (i - 3.0) diff = p(i) - 2 * (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -19,7 +19,7 @@ contains ...@@ -19,7 +19,7 @@ contains
do k = 1, cols do k = 1, cols
do i = 1, rows do i = 1, rows
diff = P(i,k) - Q(i,k) diff = P(i,k) - Q(i,k)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end do end do
end subroutine end subroutine
......
...@@ -17,7 +17,7 @@ contains ...@@ -17,7 +17,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -17,7 +17,7 @@ contains ...@@ -17,7 +17,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -28,7 +28,7 @@ contains ...@@ -28,7 +28,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - 2 * (i + 2.0) * (i - 3.0) diff = p(i) - 2 * (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
...@@ -39,7 +39,7 @@ contains ...@@ -39,7 +39,7 @@ contains
call init (v1, v2, N) call init (v1, v2, N)
!$omp target data if(N > THRESHOLD) map(from: p) !$omp target data if(N > THRESHOLD) map(from: p)
!$omp target if(N > THRESHOLD) map(to: v1, v2) !$omp target if(N > THRESHOLD) map(to: v1, v2)
if (omp_is_initial_device ()) STOP 2 if (omp_is_initial_device ()) stop 2
!$omp parallel do !$omp parallel do
do i = 1, N do i = 1, N
p(i) = v1(i) * v2(i) p(i) = v1(i) * v2(i)
...@@ -47,7 +47,7 @@ contains ...@@ -47,7 +47,7 @@ contains
!$omp end target !$omp end target
call init_again (v1, v2, N) call init_again (v1, v2, N)
!$omp target if(N > THRESHOLD) map(to: v1, v2) !$omp target if(N > THRESHOLD) map(to: v1, v2)
if (omp_is_initial_device ()) STOP 3 if (omp_is_initial_device ()) stop 3
!$omp parallel do !$omp parallel do
do i = 1, N do i = 1, N
p(i) = p(i) + v1(i) * v2(i) p(i) = p(i) + v1(i) * v2(i)
......
...@@ -19,7 +19,7 @@ contains ...@@ -19,7 +19,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
...@@ -30,7 +30,7 @@ contains ...@@ -30,7 +30,7 @@ contains
call init (v1, v2, N) call init (v1, v2, N)
!$omp target data if(N > THRESHOLD) map(to: v1, v2) map(from: p) !$omp target data if(N > THRESHOLD) map(to: v1, v2) map(from: p)
!$omp target !$omp target
if (omp_is_initial_device ()) STOP 2 if (omp_is_initial_device ()) stop 2
!$omp parallel do !$omp parallel do
do i = 1, N do i = 1, N
p(i) = v1(i) * v2(i) p(i) = v1(i) * v2(i)
......
...@@ -26,7 +26,7 @@ contains ...@@ -26,7 +26,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - 2 * (i + 2.0) * (i - 3.0) diff = p(i) - 2 * (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -26,7 +26,7 @@ contains ...@@ -26,7 +26,7 @@ contains
real :: diff, p(N) real :: diff, p(N)
do i = 1, N do i = 1, N
diff = p(i) - (i * i + (i + 2.0) * (i - 3.0)) diff = p(i) - (i * i + (i + 2.0) * (i - 3.0))
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -9,7 +9,7 @@ program example ...@@ -9,7 +9,7 @@ program example
x = 2 x = 2
!$omp end task !$omp end task
!$omp task shared(x) depend(in: x) !$omp task shared(x) depend(in: x)
if (x .ne. 2) STOP 1 if (x .ne. 2) stop 1
!$omp end task !$omp end task
!$omp end single !$omp end single
!$omp end parallel !$omp end parallel
......
...@@ -6,7 +6,7 @@ program example ...@@ -6,7 +6,7 @@ program example
!$omp parallel !$omp parallel
!$omp single !$omp single
!$omp task shared(x) depend(in: x) !$omp task shared(x) depend(in: x)
if (x .ne. 1) STOP 1 if (x .ne. 1) stop 1
!$omp end task !$omp end task
!$omp task shared(x) depend(out: x) !$omp task shared(x) depend(out: x)
x = 2 x = 2
......
...@@ -12,7 +12,7 @@ program example ...@@ -12,7 +12,7 @@ program example
x = 2 x = 2
!$omp end task !$omp end task
!$omp taskwait !$omp taskwait
if ((x .ne. 1) .and. (x .ne. 2)) STOP 1 if ((x .ne. 1) .and. (x .ne. 2)) stop 1
!$omp end single !$omp end single
!$omp end parallel !$omp end parallel
end program end program
...@@ -9,10 +9,10 @@ program example ...@@ -9,10 +9,10 @@ program example
x = 2 x = 2
!$omp end task !$omp end task
!$omp task shared(x) depend(in: x) !$omp task shared(x) depend(in: x)
if (x .ne. 2) STOP 1 if (x .ne. 2) stop 1
!$omp end task !$omp end task
!$omp task shared(x) depend(in: x) !$omp task shared(x) depend(in: x)
if (x .ne. 2) STOP 2 if (x .ne. 2) stop 2
!$omp end task !$omp end task
!$omp end single !$omp end single
!$omp end parallel !$omp end parallel
......
...@@ -51,7 +51,7 @@ contains ...@@ -51,7 +51,7 @@ contains
do j = 1, N do j = 1, N
diff = A(i, j) - B(i, j) diff = A(i, j) - B(i, j)
if (diff > EPS .or. -diff > EPS) then if (diff > EPS .or. -diff > EPS) then
STOP 1 stop 1
end if end if
end do end do
end do end do
......
...@@ -49,7 +49,7 @@ subroutine check (a, b) ...@@ -49,7 +49,7 @@ subroutine check (a, b)
else else
err = (a - b) / b err = (a - b) / b
end if end if
if (err > EPS .or. err < -EPS) STOP 1 if (err > EPS .or. err < -EPS) stop 1
end subroutine end subroutine
program e_54_1 program e_54_1
......
...@@ -42,7 +42,7 @@ subroutine check (a, b) ...@@ -42,7 +42,7 @@ subroutine check (a, b)
else else
err = (a - b) / b err = (a - b) / b
end if end if
if (err > EPS .or. err < -EPS) STOP 1 if (err > EPS .or. err < -EPS) stop 1
end subroutine end subroutine
program e_54_3 program e_54_3
......
...@@ -44,7 +44,7 @@ subroutine check (a, b) ...@@ -44,7 +44,7 @@ subroutine check (a, b)
else else
err = (a - b) / b err = (a - b) / b
end if end if
if (err > EPS .or. err < -EPS) STOP 1 if (err > EPS .or. err < -EPS) stop 1
end subroutine end subroutine
program e_54_4 program e_54_4
......
...@@ -18,7 +18,7 @@ contains ...@@ -18,7 +18,7 @@ contains
real :: diff real :: diff
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -18,7 +18,7 @@ contains ...@@ -18,7 +18,7 @@ contains
real :: diff real :: diff
do i = 1, N do i = 1, N
diff = p(i) - (i + 2.0) * (i - 3.0) diff = p(i) - (i + 2.0) * (i - 3.0)
if (diff > EPS .or. -diff > EPS) STOP 1 if (diff > EPS .or. -diff > EPS) stop 1
end do end do
end subroutine end subroutine
......
...@@ -5,15 +5,15 @@ program lastprivate ...@@ -5,15 +5,15 @@ program lastprivate
!$omp parallel num_threads (4) !$omp parallel num_threads (4)
call test1 call test1
!$omp end parallel !$omp end parallel
if (i .ne. 21) STOP 1 if (i .ne. 21) stop 1
!$omp parallel num_threads (4) !$omp parallel num_threads (4)
call test2 call test2
!$omp end parallel !$omp end parallel
if (i .ne. 64) STOP 2 if (i .ne. 64) stop 2
!$omp parallel num_threads (4) !$omp parallel num_threads (4)
call test3 call test3
!$omp end parallel !$omp end parallel
if (i .ne. 14) STOP 3 if (i .ne. 14) stop 3
call test4 call test4
call test5 call test5
call test6 call test6
...@@ -54,21 +54,21 @@ contains ...@@ -54,21 +54,21 @@ contains
!$omp parallel do lastprivate (j) num_threads (4) default (none) !$omp parallel do lastprivate (j) num_threads (4) default (none)
do j = 1, 20 do j = 1, 20
end do end do
if (j .ne. 21) STOP 4 if (j .ne. 21) stop 4
end subroutine test4 end subroutine test4
subroutine test5 subroutine test5
integer :: j integer :: j
!$omp parallel do lastprivate (j) num_threads (4) default (none) !$omp parallel do lastprivate (j) num_threads (4) default (none)
do j = 7, 61, 3 do j = 7, 61, 3
end do end do
if (j .ne. 64) STOP 5 if (j .ne. 64) stop 5
end subroutine test5 end subroutine test5
subroutine test6 subroutine test6
integer :: j integer :: j
!$omp parallel do lastprivate (j) num_threads (4) default (none) !$omp parallel do lastprivate (j) num_threads (4) default (none)
do j = -10, 11, ret3 () do j = -10, 11, ret3 ()
end do end do
if (j .ne. 14) STOP 6 if (j .ne. 14) stop 6
end subroutine test6 end subroutine test6
subroutine test7 subroutine test7
integer :: i integer :: i
...@@ -76,7 +76,7 @@ contains ...@@ -76,7 +76,7 @@ contains
!$omp parallel do lastprivate (i) num_threads (4) default (none) !$omp parallel do lastprivate (i) num_threads (4) default (none)
do i = 1, 20 do i = 1, 20
end do end do
if (i .ne. 21) STOP 7 if (i .ne. 21) stop 7
end subroutine test7 end subroutine test7
subroutine test8 subroutine test8
integer :: i integer :: i
...@@ -84,7 +84,7 @@ contains ...@@ -84,7 +84,7 @@ contains
!$omp parallel do lastprivate (i) num_threads (4) default (none) !$omp parallel do lastprivate (i) num_threads (4) default (none)
do i = 7, 61, 3 do i = 7, 61, 3
end do end do
if (i .ne. 64) STOP 8 if (i .ne. 64) stop 8
end subroutine test8 end subroutine test8
subroutine test9 subroutine test9
integer :: i integer :: i
...@@ -92,7 +92,7 @@ contains ...@@ -92,7 +92,7 @@ contains
!$omp parallel do lastprivate (i) num_threads (4) default (none) !$omp parallel do lastprivate (i) num_threads (4) default (none)
do i = -10, 11, ret3 () do i = -10, 11, ret3 ()
end do end do
if (i .ne. 14) STOP 9 if (i .ne. 14) stop 9
end subroutine test9 end subroutine test9
subroutine test10 subroutine test10
integer :: i integer :: i
...@@ -102,7 +102,7 @@ contains ...@@ -102,7 +102,7 @@ contains
do i = 1, 20 do i = 1, 20
end do end do
!$omp end parallel !$omp end parallel
if (i .ne. 21) STOP 10 if (i .ne. 21) stop 10
end subroutine test10 end subroutine test10
subroutine test11 subroutine test11
integer :: i integer :: i
...@@ -112,7 +112,7 @@ contains ...@@ -112,7 +112,7 @@ contains
do i = 7, 61, 3 do i = 7, 61, 3
end do end do
!$omp end parallel !$omp end parallel
if (i .ne. 64) STOP 11 if (i .ne. 64) stop 11
end subroutine test11 end subroutine test11
subroutine test12 subroutine test12
integer :: i integer :: i
...@@ -122,6 +122,6 @@ contains ...@@ -122,6 +122,6 @@ contains
do i = -10, 11, ret3 () do i = -10, 11, ret3 ()
end do end do
!$omp end parallel !$omp end parallel
if (i .ne. 14) STOP 12 if (i .ne. 14) stop 12
end subroutine test12 end subroutine test12
end program lastprivate end program lastprivate
...@@ -5,15 +5,15 @@ program lastprivate ...@@ -5,15 +5,15 @@ program lastprivate
!$omp parallel num_threads (4) !$omp parallel num_threads (4)
call test1 call test1
!$omp end parallel !$omp end parallel
if (i .ne. 21 .or. k .ne. 20) STOP 1 if (i .ne. 21 .or. k .ne. 20) stop 1
!$omp parallel num_threads (4) !$omp parallel num_threads (4)
call test2 call test2
!$omp end parallel !$omp end parallel
if (i .ne. 64 .or. k .ne. 61) STOP 2 if (i .ne. 64 .or. k .ne. 61) stop 2
!$omp parallel num_threads (4) !$omp parallel num_threads (4)
call test3 call test3
!$omp end parallel !$omp end parallel
if (i .ne. 14 .or. k .ne. 11) STOP 3 if (i .ne. 14 .or. k .ne. 11) stop 3
call test4 call test4
call test5 call test5
call test6 call test6
...@@ -58,7 +58,7 @@ contains ...@@ -58,7 +58,7 @@ contains
do j = 1, 20 do j = 1, 20
l = j l = j
end do end do
if (j .ne. 21 .or. l .ne. 20) STOP 4 if (j .ne. 21 .or. l .ne. 20) stop 4
end subroutine test4 end subroutine test4
subroutine test5 subroutine test5
integer :: j, l integer :: j, l
...@@ -67,7 +67,7 @@ contains ...@@ -67,7 +67,7 @@ contains
do j = 7, 61, 3 do j = 7, 61, 3
l = j l = j
end do end do
if (j .ne. 64 .or. l .ne. 61) STOP 5 if (j .ne. 64 .or. l .ne. 61) stop 5
end subroutine test5 end subroutine test5
subroutine test6 subroutine test6
integer :: j, l integer :: j, l
...@@ -75,7 +75,7 @@ contains ...@@ -75,7 +75,7 @@ contains
do j = -10, 11, ret3 () do j = -10, 11, ret3 ()
l = j l = j
end do end do
if (j .ne. 14 .or. l .ne. 11) STOP 6 if (j .ne. 14 .or. l .ne. 11) stop 6
end subroutine test6 end subroutine test6
subroutine test7 subroutine test7
integer :: i, k integer :: i, k
...@@ -84,7 +84,7 @@ contains ...@@ -84,7 +84,7 @@ contains
do i = 1, 20 do i = 1, 20
k = i k = i
end do end do
if (i .ne. 21 .or. k .ne. 20) STOP 7 if (i .ne. 21 .or. k .ne. 20) stop 7
end subroutine test7 end subroutine test7
subroutine test8 subroutine test8
integer :: i, k integer :: i, k
...@@ -93,7 +93,7 @@ contains ...@@ -93,7 +93,7 @@ contains
do i = 7, 61, 3 do i = 7, 61, 3
k = i k = i
end do end do
if (i .ne. 64 .or. k .ne. 61) STOP 8 if (i .ne. 64 .or. k .ne. 61) stop 8
end subroutine test8 end subroutine test8
subroutine test9 subroutine test9
integer :: i, k integer :: i, k
...@@ -103,7 +103,7 @@ contains ...@@ -103,7 +103,7 @@ contains
do i = -10, 11, ret3 () do i = -10, 11, ret3 ()
k = i k = i
end do end do
if (i .ne. 14 .or. k .ne. 11) STOP 9 if (i .ne. 14 .or. k .ne. 11) stop 9
end subroutine test9 end subroutine test9
subroutine test10 subroutine test10
integer :: i, k integer :: i, k
...@@ -114,7 +114,7 @@ contains ...@@ -114,7 +114,7 @@ contains
k = i k = i
end do end do
!$omp end parallel !$omp end parallel
if (i .ne. 21 .or. k .ne. 20) STOP 10 if (i .ne. 21 .or. k .ne. 20) stop 10
end subroutine test10 end subroutine test10
subroutine test11 subroutine test11
integer :: i, k integer :: i, k
...@@ -125,7 +125,7 @@ contains ...@@ -125,7 +125,7 @@ contains
k = i k = i
end do end do
!$omp end parallel !$omp end parallel
if (i .ne. 64 .or. k .ne. 61) STOP 11 if (i .ne. 64 .or. k .ne. 61) stop 11
end subroutine test11 end subroutine test11
subroutine test12 subroutine test12
integer :: i, k integer :: i, k
...@@ -137,6 +137,6 @@ contains ...@@ -137,6 +137,6 @@ contains
k = i k = i
end do end do
!$omp end parallel !$omp end parallel
if (i .ne. 14 .or. k .ne. 11) STOP 12 if (i .ne. 14 .or. k .ne. 11) stop 12
end subroutine test12 end subroutine test12
end program lastprivate end program lastprivate
...@@ -11,42 +11,42 @@ ...@@ -11,42 +11,42 @@
call omp_init_lock (lck) call omp_init_lock (lck)
call omp_set_lock (lck) call omp_set_lock (lck)
if (omp_test_lock (lck)) STOP 1 if (omp_test_lock (lck)) stop 1
call omp_unset_lock (lck) call omp_unset_lock (lck)
if (.not. omp_test_lock (lck)) STOP 2 if (.not. omp_test_lock (lck)) stop 2
if (omp_test_lock (lck)) STOP 3 if (omp_test_lock (lck)) stop 3
call omp_unset_lock (lck) call omp_unset_lock (lck)
call omp_destroy_lock (lck) call omp_destroy_lock (lck)
call omp_init_nest_lock (nlck) call omp_init_nest_lock (nlck)
if (omp_test_nest_lock (nlck) .ne. 1) STOP 4 if (omp_test_nest_lock (nlck) .ne. 1) stop 4
call omp_set_nest_lock (nlck) call omp_set_nest_lock (nlck)
if (omp_test_nest_lock (nlck) .ne. 3) STOP 5 if (omp_test_nest_lock (nlck) .ne. 3) stop 5
call omp_unset_nest_lock (nlck) call omp_unset_nest_lock (nlck)
call omp_unset_nest_lock (nlck) call omp_unset_nest_lock (nlck)
if (omp_test_nest_lock (nlck) .ne. 2) STOP 6 if (omp_test_nest_lock (nlck) .ne. 2) stop 6
call omp_unset_nest_lock (nlck) call omp_unset_nest_lock (nlck)
call omp_unset_nest_lock (nlck) call omp_unset_nest_lock (nlck)
call omp_destroy_nest_lock (nlck) call omp_destroy_nest_lock (nlck)
call omp_set_dynamic (.true.) call omp_set_dynamic (.true.)
if (.not. omp_get_dynamic ()) STOP 7 if (.not. omp_get_dynamic ()) stop 7
call omp_set_dynamic (.false.) call omp_set_dynamic (.false.)
if (omp_get_dynamic ()) STOP 8 if (omp_get_dynamic ()) stop 8
call omp_set_nested (.true.) call omp_set_nested (.true.)
if (.not. omp_get_nested ()) STOP 9 if (.not. omp_get_nested ()) stop 9
call omp_set_nested (.false.) call omp_set_nested (.false.)
if (omp_get_nested ()) STOP 10 if (omp_get_nested ()) stop 10
call omp_set_num_threads (5) call omp_set_num_threads (5)
if (omp_get_num_threads () .ne. 1) STOP 11 if (omp_get_num_threads () .ne. 1) stop 11
if (omp_get_max_threads () .ne. 5) STOP 12 if (omp_get_max_threads () .ne. 5) stop 12
if (omp_get_thread_num () .ne. 0) STOP 13 if (omp_get_thread_num () .ne. 0) stop 13
call omp_set_num_threads (3) call omp_set_num_threads (3)
if (omp_get_num_threads () .ne. 1) STOP 14 if (omp_get_num_threads () .ne. 1) stop 14
if (omp_get_max_threads () .ne. 3) STOP 15 if (omp_get_max_threads () .ne. 3) stop 15
if (omp_get_thread_num () .ne. 0) STOP 16 if (omp_get_thread_num () .ne. 0) stop 16
l = .false. l = .false.
!$omp parallel reduction (.or.:l) !$omp parallel reduction (.or.:l)
l = omp_get_num_threads () .ne. 3 l = omp_get_num_threads () .ne. 3
...@@ -56,22 +56,22 @@ ...@@ -56,22 +56,22 @@
l = l .or. (omp_get_thread_num () .ne. 0) l = l .or. (omp_get_thread_num () .ne. 0)
!$omp end master !$omp end master
!$omp end parallel !$omp end parallel
if (l) STOP 17 if (l) stop 17
if (omp_get_num_procs () .le. 0) STOP 18 if (omp_get_num_procs () .le. 0) stop 18
if (omp_in_parallel ()) STOP 19 if (omp_in_parallel ()) stop 19
!$omp parallel reduction (.or.:l) !$omp parallel reduction (.or.:l)
l = .not. omp_in_parallel () l = .not. omp_in_parallel ()
!$omp end parallel !$omp end parallel
!$omp parallel reduction (.or.:l) if (.true.) !$omp parallel reduction (.or.:l) if (.true.)
l = .not. omp_in_parallel () l = .not. omp_in_parallel ()
!$omp end parallel !$omp end parallel
if (l) STOP 20 if (l) stop 20
e = omp_get_wtime () e = omp_get_wtime ()
if (d .gt. e) STOP 21 if (d .gt. e) stop 21
d = omp_get_wtick () d = omp_get_wtick ()
! Negative precision is definitely wrong, ! Negative precision is definitely wrong,
! bigger than 1s clock resolution is also strange ! bigger than 1s clock resolution is also strange
if (d .le. 0 .or. d .gt. 1.) STOP 22 if (d .le. 0 .or. d .gt. 1.) stop 22
end end
...@@ -6,11 +6,11 @@ program lib4 ...@@ -6,11 +6,11 @@ program lib4
integer :: modifier integer :: modifier
call omp_set_schedule (omp_sched_static, 32) call omp_set_schedule (omp_sched_static, 32)
call omp_get_schedule (kind, modifier) call omp_get_schedule (kind, modifier)
if (kind.ne.omp_sched_static.or.modifier.ne.32) STOP 1 if (kind.ne.omp_sched_static.or.modifier.ne.32) stop 1
call omp_set_schedule (omp_sched_dynamic, 4) call omp_set_schedule (omp_sched_dynamic, 4)
call omp_get_schedule (kind, modifier) call omp_get_schedule (kind, modifier)
if (kind.ne.omp_sched_dynamic.or.modifier.ne.4) STOP 2 if (kind.ne.omp_sched_dynamic.or.modifier.ne.4) stop 2
if (omp_get_thread_limit ().lt.0) STOP 3 if (omp_get_thread_limit ().lt.0) stop 3
call omp_set_max_active_levels (6) call omp_set_max_active_levels (6)
if (omp_get_max_active_levels ().ne.6) STOP 4 if (omp_get_max_active_levels ().ne.6) stop 4
end program lib4 end program lib4
...@@ -7,16 +7,16 @@ ...@@ -7,16 +7,16 @@
l = .false. l = .false.
call omp_init_nest_lock (lock) call omp_init_nest_lock (lock)
if (omp_test_nest_lock (lock) .ne. 1) STOP 1 if (omp_test_nest_lock (lock) .ne. 1) stop 1
if (omp_test_nest_lock (lock) .ne. 2) STOP 2 if (omp_test_nest_lock (lock) .ne. 2) stop 2
!$omp parallel if (.false.) reduction (.or.:l) !$omp parallel if (.false.) reduction (.or.:l)
! In OpenMP 2.5 this was supposed to return 3, ! In OpenMP 2.5 this was supposed to return 3,
! but in OpenMP 3.0 the parallel region has a different ! but in OpenMP 3.0 the parallel region has a different
! task and omp_*_lock_t are owned by tasks, not by threads. ! task and omp_*_lock_t are owned by tasks, not by threads.
if (omp_test_nest_lock (lock) .ne. 0) l = .true. if (omp_test_nest_lock (lock) .ne. 0) l = .true.
!$omp end parallel !$omp end parallel
if (l) STOP 3 if (l) stop 3
if (omp_test_nest_lock (lock) .ne. 3) STOP 4 if (omp_test_nest_lock (lock) .ne. 3) stop 4
call omp_unset_nest_lock (lock) call omp_unset_nest_lock (lock)
call omp_unset_nest_lock (lock) call omp_unset_nest_lock (lock)
call omp_unset_nest_lock (lock) call omp_unset_nest_lock (lock)
......
...@@ -8,8 +8,8 @@ ...@@ -8,8 +8,8 @@
l = .false. l = .false.
call omp_init_nest_lock (lock) call omp_init_nest_lock (lock)
!$omp parallel num_threads (1) reduction (.or.:l) !$omp parallel num_threads (1) reduction (.or.:l)
if (omp_test_nest_lock (lock) .ne. 1) STOP 1 if (omp_test_nest_lock (lock) .ne. 1) stop 1
if (omp_test_nest_lock (lock) .ne. 2) STOP 2 if (omp_test_nest_lock (lock) .ne. 2) stop 2
!$omp task if (.false.) shared (lock, l) !$omp task if (.false.) shared (lock, l)
if (omp_test_nest_lock (lock) .ne. 0) l = .true. if (omp_test_nest_lock (lock) .ne. 0) l = .true.
!$omp end task !$omp end task
...@@ -19,6 +19,6 @@ ...@@ -19,6 +19,6 @@
call omp_unset_nest_lock (lock) call omp_unset_nest_lock (lock)
call omp_unset_nest_lock (lock) call omp_unset_nest_lock (lock)
!$omp end parallel !$omp end parallel
if (l) STOP 3 if (l) stop 3
call omp_destroy_nest_lock (lock) call omp_destroy_nest_lock (lock)
end end
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment