• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1! RUN: %S/test_errors.sh %s %t %f18 -fopenmp
2! OpenMP Version 4.5
3! 2.13.9 Depend Clause
4! A variable that is part of another variable
5! (such as an element of a structure) but is not an array element or
6! an array section cannot appear in a DEPEND clause
7
8subroutine vec_mult(N)
9  implicit none
10  integer :: i, N
11  real, allocatable :: p(:), v1(:), v2(:)
12
13  type my_type
14    integer :: a(10)
15  end type my_type
16
17  type(my_type) :: my_var
18  allocate( p(N), v1(N), v2(N) )
19
20  !$omp parallel num_threads(2)
21  !$omp single
22
23  !$omp task depend(out:v1)
24  call init(v1, N)
25  !$omp end task
26
27  !$omp task depend(out:v2)
28  call init(v2, N)
29  !$omp end task
30
31  !ERROR: A variable that is part of another variable (such as an element of a structure) but is not an array element or an array section cannot appear in a DEPEND clause
32  !$omp target nowait depend(in:v1,v2, my_var%a) depend(out:p) &
33  !$omp& map(to:v1,v2) map(from: p)
34  !$omp parallel do
35  do i=1,N
36    p(i) = v1(i) * v2(i)
37  end do
38  !$omp end target
39
40  !$omp task depend(in:p)
41  call output(p, N)
42  !$omp end task
43
44  !$omp end single
45  !$omp end parallel
46
47  deallocate( p, v1, v2 )
48
49end subroutine
50