aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.4.3/libgomp/testsuite/libgomp.fortran/appendix-a/a.39.1.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc-4.4.3/libgomp/testsuite/libgomp.fortran/appendix-a/a.39.1.f90')
-rw-r--r--gcc-4.4.3/libgomp/testsuite/libgomp.fortran/appendix-a/a.39.1.f9026
1 files changed, 26 insertions, 0 deletions
diff --git a/gcc-4.4.3/libgomp/testsuite/libgomp.fortran/appendix-a/a.39.1.f90 b/gcc-4.4.3/libgomp/testsuite/libgomp.fortran/appendix-a/a.39.1.f90
new file mode 100644
index 000000000..540d17f5b
--- /dev/null
+++ b/gcc-4.4.3/libgomp/testsuite/libgomp.fortran/appendix-a/a.39.1.f90
@@ -0,0 +1,26 @@
+! { dg-do run }
+
+ SUBROUTINE SKIP(ID)
+ END SUBROUTINE SKIP
+ SUBROUTINE WORK(ID)
+ END SUBROUTINE WORK
+ PROGRAM A39
+ INCLUDE "omp_lib.h" ! or USE OMP_LIB
+ INTEGER(OMP_LOCK_KIND) LCK
+ INTEGER ID
+ CALL OMP_INIT_LOCK(LCK)
+!$OMP PARALLEL SHARED(LCK) PRIVATE(ID)
+ ID = OMP_GET_THREAD_NUM()
+ CALL OMP_SET_LOCK(LCK)
+ PRINT *, "My thread id is ", ID
+ CALL OMP_UNSET_LOCK(LCK)
+ DO WHILE (.NOT. OMP_TEST_LOCK(LCK))
+ CALL SKIP(ID) ! We do not yet have the lock
+ ! so we must do something else
+ END DO
+ CALL WORK(ID) ! We now have the lock
+ ! and can do the work
+ CALL OMP_UNSET_LOCK( LCK )
+!$OMP END PARALLEL
+ CALL OMP_DESTROY_LOCK( LCK )
+ END PROGRAM A39