URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [libgomp/] [testsuite/] [libgomp.fortran/] [lib1.f90] - Rev 735
Compare with Previous | Blame | View Log
! { dg-do run }use omp_libdouble precision :: d, elogical :: linteger (kind = omp_lock_kind) :: lckinteger (kind = omp_nest_lock_kind) :: nlckd = omp_get_wtime ()call omp_init_lock (lck)call omp_set_lock (lck)if (omp_test_lock (lck)) call abortcall omp_unset_lock (lck)if (.not. omp_test_lock (lck)) call abortif (omp_test_lock (lck)) call abortcall omp_unset_lock (lck)call omp_destroy_lock (lck)call omp_init_nest_lock (nlck)if (omp_test_nest_lock (nlck) .ne. 1) call abortcall omp_set_nest_lock (nlck)if (omp_test_nest_lock (nlck) .ne. 3) call abortcall omp_unset_nest_lock (nlck)call omp_unset_nest_lock (nlck)if (omp_test_nest_lock (nlck) .ne. 2) call abortcall omp_unset_nest_lock (nlck)call omp_unset_nest_lock (nlck)call omp_destroy_nest_lock (nlck)call omp_set_dynamic (.true.)if (.not. omp_get_dynamic ()) call abortcall omp_set_dynamic (.false.)if (omp_get_dynamic ()) call abortcall omp_set_nested (.true.)if (.not. omp_get_nested ()) call abortcall omp_set_nested (.false.)if (omp_get_nested ()) call abortcall omp_set_num_threads (5)if (omp_get_num_threads () .ne. 1) call abortif (omp_get_max_threads () .ne. 5) call abortif (omp_get_thread_num () .ne. 0) call abortcall omp_set_num_threads (3)if (omp_get_num_threads () .ne. 1) call abortif (omp_get_max_threads () .ne. 3) call abortif (omp_get_thread_num () .ne. 0) call abortl = .false.!$omp parallel reduction (.or.:l)l = omp_get_num_threads () .ne. 3l = l .or. (omp_get_thread_num () .lt. 0)l = l .or. (omp_get_thread_num () .ge. 3)!$omp masterl = l .or. (omp_get_thread_num () .ne. 0)!$omp end master!$omp end parallelif (l) call abortif (omp_get_num_procs () .le. 0) call abortif (omp_in_parallel ()) call abort!$omp parallel reduction (.or.:l)l = .not. omp_in_parallel ()!$omp end parallel!$omp parallel reduction (.or.:l) if (.true.)l = .not. omp_in_parallel ()!$omp end parallele = omp_get_wtime ()if (d .gt. e) call abortd = omp_get_wtick ()! Negative precision is definitely wrong,! bigger than 1s clock resolution is also strangeif (d .le. 0 .or. d .gt. 1.) call abortend
