URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [libgomp/] [testsuite/] [libgomp.fortran/] [omp_parse1.f90] - Rev 735
Compare with Previous | Blame | View Log
! { dg-do run }use omp_libcall test_parallelcall test_docall test_sectionscall test_singlecontainssubroutine test_parallelinteger :: a, b, c, e, f, g, i, jinteger, dimension (20) :: dlogical :: ha = 6b = 8c = 11d(:) = -1e = 13f = 24g = 27h = .false.i = 1j = 16!$omp para&!$omp&llel &!$omp if (a .eq. 6) private (b, c) shared (d) private (e) &!$omp firstprivate(f) num_threads (a - 1) first&!$ompprivate(g)default (shared) reduction (.or. : h) &!$omp reduction(*:i)if (i .ne. 1) h = .true.i = 2if (f .ne. 24) h = .true.if (g .ne. 27) h = .true.e = 7b = omp_get_thread_num ()if (b .eq. 0) j = 24f = bg = fc = omp_get_num_threads ()if (c .gt. a - 1 .or. c .le. 0) h = .true.if (b .ge. c) h = .true.d(b + 1) = cif (f .ne. g .or. f .ne. b) h = .true.!$omp endparallelif (h) call abortif (a .ne. 6) call abortif (j .ne. 24) call abortif (d(1) .eq. -1) call aborte = 1do g = 1, d(1)if (d(g) .ne. d(1)) call aborte = e * 2end doif (e .ne. i) call abortend subroutine test_parallelsubroutine test_do_orphaninteger :: k, l!$omp parallel do private (l)do 600 k = 1, 16, 2600 l = kend subroutine test_do_orphansubroutine test_dointeger :: i, j, k, l, ninteger, dimension (64) :: dlogical :: mj = 16d(:) = -1m = .true.n = 24!$omp parallel num_threads (4) shared (i, k, d) private (l) &!$omp&reduction (.and. : m)if (omp_get_thread_num () .eq. 0) thenk = omp_get_num_threads ()end ifcall test_do_orphan!$omp do schedule (static) firstprivate (n)do 200 i = 1, jif (i .eq. 1 .and. n .ne. 24) call abortn = i200 d(n) = omp_get_thread_num ()!$omp enddo nowait!$omp do lastprivate (i) schedule (static, 5)do 201 i = j + 1, 2 * j201 d(i) = omp_get_thread_num () + 1024! Implied omp end do hereif (i .ne. 33) m = .false.!$omp do private (j) schedule (dynamic)do i = 33, 48d(i) = omp_get_thread_num () + 2048end do!$omp end do nowait!$omp do schedule (runtime)do i = 49, 4 * jd(i) = omp_get_thread_num () + 4096end do! Implied omp end do here!$omp end parallelif (.not. m) call abortj = 0do i = 1, 64if (d(i) .lt. j .or. d(i) .ge. j + k) call abortif (i .eq. 16) j = 1024if (i .eq. 32) j = 2048if (i .eq. 48) j = 4096end doend subroutine test_dosubroutine test_sectionsinteger :: i, j, k, l, m, ni = 9j = 10k = 11l = 0m = 0n = 30call omp_set_dynamic (.false.)call omp_set_num_threads (4)!$omp parallel num_threads (4)!$omp sections private (i) firstprivate (j, k) lastprivate (j) &!$omp& reduction (+ : l, m)!$omp sectioni = 24if (j .ne. 10 .or. k .ne. 11 .or. m .ne. 0) l = 1m = m + 4!$omp sectioni = 25if (j .ne. 10 .or. k .ne. 11) l = 1m = m + 6!$omp sectioni = 26if (j .ne. 10 .or. k .ne. 11) l = 1m = m + 8!$omp sectioni = 27if (j .ne. 10 .or. k .ne. 11) l = 1m = m + 10j = 271!$omp end sections nowait!$omp sections lastprivate (n)!$omp sectionn = 6!$omp sectionn = 7!$omp endsections!$omp end parallelif (j .ne. 271 .or. l .ne. 0) call abortif (m .ne. 4 + 6 + 8 + 10) call abortif (n .ne. 7) call abortend subroutine test_sectionssubroutine test_singleinteger :: i, j, k, llogical :: mi = 200j = 300k = 400l = 500m = .false.!$omp parallel num_threads (4), private (i, j), reduction (.or. : m)i = omp_get_thread_num ()j = omp_get_thread_num ()!$omp single private (k)k = 64!$omp end single nowait!$omp single private (k) firstprivate (l)if (i .ne. omp_get_thread_num () .or. i .ne. j) thenj = -1elsej = -2end ifif (l .ne. 500) j = -1l = 265!$omp end single copyprivate (j)if (i .ne. omp_get_thread_num () .or. j .ne. -2) m = .true.!$omp endparallelif (m) call abortend subroutine test_singleend
