1! { dg-do run }
2
3  integer, allocatable :: a(:, :)
4  integer :: b(6, 3)
5  integer :: i, j
6  logical :: k, l
7  b(:, :) = 16
8  l = .false.
9  if (allocated (a)) stop 1
10!$omp task private (a, b) shared (l)
11  l = l.or.allocated (a)
12  allocate (a(3, 6))
13  l = l.or..not.allocated (a)
14  l = l.or.size(a).ne.18.or.size(a,1).ne.3.or.size(a,2).ne.6
15  a(3, 2) = 1
16  b(3, 2) = 1
17  deallocate (a)
18  l = l.or.allocated (a)
19!$omp end task
20!$omp taskwait
21  if (allocated (a).or.l) stop 2
22  allocate (a(6, 3))
23  a(:, :) = 3
24  if (.not.allocated (a)) stop 3
25  l = l.or.size(a).ne.18.or.size(a,1).ne.6.or.size(a,2).ne.3
26  if (l) stop 4
27!$omp task private (a, b) shared (l)
28  l = l.or..not.allocated (a)
29  a(3, 2) = 1
30  b(3, 2) = 1
31!$omp end task
32!$omp taskwait
33  if (l.or..not.allocated (a)) stop 5
34!$omp task firstprivate (a, b) shared (l)
35  l = l.or..not.allocated (a)
36  l = l.or.size(a).ne.18.or.size(a,1).ne.6.or.size(a,2).ne.3
37  do i = 1, 6
38    l = l.or.(a(i, 1).ne.3).or.(a(i, 2).ne.3)
39    l = l.or.(a(i, 3).ne.3).or.(b(i, 1).ne.16)
40    l = l.or.(b(i, 2).ne.16).or.(b(i, 3).ne.16)
41  end do
42  a(:, :) = 7
43  b(:, :) = 8
44!$omp end task
45!$omp taskwait
46  if (any (a.ne.3).or.any (b.ne.16).or.l) stop 6
47end
48