URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [libgomp/] [testsuite/] [libgomp.fortran/] [omp_parse3.f90] - Rev 735
Compare with Previous | Blame | View Log
! { dg-do run }! { dg-require-effective-target tls_runtime }use omp_libcommon /tlsblock/ x, yinteger :: x, y, zsave z!$omp threadprivate (/tlsblock/, z)call test_flushcall test_orderedcall test_threadprivatecontainssubroutine test_flushinteger :: i, ji = 0j = 0!$omp parallel num_threads (4)if (omp_get_thread_num () .eq. 0) i = omp_get_num_threads ()if (omp_get_thread_num () .eq. 0) j = j + 1!$omp flush (i, j)!$omp barrierif (omp_get_thread_num () .eq. 1) j = j + 2!$omp flush!$omp barrierif (omp_get_thread_num () .eq. 2) j = j + 3!$omp flush (i)!$omp flush (j)!$omp barrierif (omp_get_thread_num () .eq. 3) j = j + 4!$omp end parallelend subroutine test_flushsubroutine test_orderedinteger :: i, jinteger, dimension (100) :: dd(:) = -1!$omp parallel do ordered schedule (dynamic) num_threads (4)do i = 1, 100, 5!$omp orderedd(i) = i!$omp end orderedend doj = 1do 100 i = 1, 100if (i .eq. j) thenif (d(i) .ne. i) call abortj = i + 5elseif (d(i) .ne. -1) call abortend if100 d(i) = -1end subroutine test_orderedsubroutine test_threadprivatecommon /tlsblock/ x, y!$omp threadprivate (/tlsblock/)integer :: i, j, x, ylogical :: m, ncall omp_set_num_threads (4)call omp_set_dynamic (.false.)i = -1x = 6y = 7z = 8n = .false.m = .false.!$omp parallel copyin (/tlsblock/, z) reduction (.or.:m) &!$omp& num_threads (4)if (omp_get_thread_num () .eq. 0) i = omp_get_num_threads ()if (x .ne. 6 .or. y .ne. 7 .or. z .ne. 8) call abortx = omp_get_thread_num ()y = omp_get_thread_num () + 1024z = omp_get_thread_num () + 4096!$omp end parallelif (x .ne. 0 .or. y .ne. 1024 .or. z .ne. 4096) call abort!$omp parallel num_threads (4), private (j) reduction (.or.:n)if (omp_get_num_threads () .eq. i) thenj = omp_get_thread_num ()if (x .ne. j .or. y .ne. j + 1024 .or. z .ne. j + 4096) && call abortend if!$omp end parallelm = m .or. nn = .false.!$omp parallel num_threads (4), copyin (z) reduction (.or. : n) &!$omp&private (j)if (z .ne. 4096) n = .true.if (omp_get_num_threads () .eq. i) thenj = omp_get_thread_num ()if (x .ne. j .or. y .ne. j + 1024) call abortend if!$omp end parallelif (m .or. n) call abortend subroutine test_threadprivateend
