OpenMP-Examples/sources/Example_task_dep.11.f90
2020-06-26 07:54:45 -07:00

44 lines
874 B
Fortran

! @@name: task_dep.11f90
! @@type: F-free
! @@compilable: yes
! @@linkable: no
! @@expect: success
! @@version: omp_5.0
subroutine set_an_element(e, val)
implicit none
integer :: e, val
e = val
end subroutine
subroutine print_all_elements(v, n)
implicit none
integer :: n, v(n)
print *, v
end subroutine
subroutine parallel_computation(n)
implicit none
integer :: n
integer :: i, v(n)
!$omp parallel
!$omp single
do i=1, n
!$omp task depend(out: v(i))
call set_an_element(v(i), i)
!$omp end task
enddo
!$omp task depend(iterator(it = 1:n), in: v(it))
!!$omp task depend(in: v(1:n)) Violates Array section restriction.
call print_all_elements(v, n)
!$omp end task
!$omp end single
!$omp end parallel
end subroutine