gcc/libgomp/testsuite/libgomp.fortran/task-detach-12.f90
Tobias Burnus 211a923049 OpenMP: detach - fix firstprivate handling
gcc/ChangeLog:

	* omp-low.c (finish_taskreg_scan): Use the proper detach decl.

libgomp/ChangeLog:

	* testsuite/libgomp.c-c++-common/task-detach-12.c: New test.
	* testsuite/libgomp.fortran/task-detach-12.f90: New test.

(cherry picked from commit d21963ce7a)
2021-05-13 22:52:35 +02:00

23 lines
522 B
Fortran

program test
use omp_lib
implicit none
integer(omp_event_handle_kind) :: oevent, ievent
integer :: i
integer, allocatable :: temp(:)
ALLOCATE(temp(5))
!$omp parallel num_threads(3)
!$omp single
DO i=1,5
!$omp task firstprivate(i) firstprivate(temp) detach(oevent)
temp(:) = 0;
temp(1) = -1;
!print *,temp
call omp_fulfill_event(oevent)
!$omp end task
ENDDO
!$omp taskwait
!$omp end single
!$omp end parallel
end program