1*404b540aSrobert! { dg-do run }
2*404b540aSrobert! { dg-require-effective-target tls_runtime }
3*404b540aSrobert
4*404b540aSrobertmodule threadprivate3
5*404b540aSrobert  integer, dimension(:,:), pointer :: foo => NULL()
6*404b540aSrobert!$omp threadprivate (foo)
7*404b540aSrobertend module threadprivate3
8*404b540aSrobert
9*404b540aSrobert  use omp_lib
10*404b540aSrobert  use threadprivate3
11*404b540aSrobert
12*404b540aSrobert  integer, dimension(:), pointer :: bar1
13*404b540aSrobert  integer, dimension(2), target :: bar2, var
14*404b540aSrobert  common /thrc/ bar1, bar2
15*404b540aSrobert!$omp threadprivate (/thrc/)
16*404b540aSrobert
17*404b540aSrobert  integer, dimension(:), pointer, save :: bar3 => NULL()
18*404b540aSrobert!$omp threadprivate (bar3)
19*404b540aSrobert
20*404b540aSrobert  logical :: l
21*404b540aSrobert  type tt
22*404b540aSrobert    integer :: a
23*404b540aSrobert    integer :: b = 32
24*404b540aSrobert  end type tt
25*404b540aSrobert  type (tt), save :: baz
26*404b540aSrobert!$omp threadprivate (baz)
27*404b540aSrobert
28*404b540aSrobert  l = .false.
29*404b540aSrobert  call omp_set_dynamic (.false.)
30*404b540aSrobert  call omp_set_num_threads (4)
31*404b540aSrobert  var = 6
32*404b540aSrobert
33*404b540aSrobert!$omp parallel num_threads (4) reduction (.or.:l)
34*404b540aSrobert  bar2 = omp_get_thread_num ()
35*404b540aSrobert  l = associated (bar3)
36*404b540aSrobert  bar1 => bar2
37*404b540aSrobert  l = l.or..not.associated (bar1)
38*404b540aSrobert  l = l.or..not.associated (bar1, bar2)
39*404b540aSrobert  l = l.or.any (bar1.ne.omp_get_thread_num ())
40*404b540aSrobert  nullify (bar1)
41*404b540aSrobert  l = l.or.associated (bar1)
42*404b540aSrobert  allocate (bar3 (4))
43*404b540aSrobert  l = l.or..not.associated (bar3)
44*404b540aSrobert  bar3 = omp_get_thread_num () - 2
45*404b540aSrobert  if (omp_get_thread_num () .ne. 0) then
46*404b540aSrobert    deallocate (bar3)
47*404b540aSrobert    if (associated (bar3)) call abort
48*404b540aSrobert  else
49*404b540aSrobert    bar1 => var
50*404b540aSrobert  end if
51*404b540aSrobert  bar2 = omp_get_thread_num () * 6 + 130
52*404b540aSrobert
53*404b540aSrobert  l = l.or.(baz%b.ne.32)
54*404b540aSrobert  baz%a = omp_get_thread_num () * 2
55*404b540aSrobert  baz%b = omp_get_thread_num () * 2 + 1
56*404b540aSrobert!$omp end parallel
57*404b540aSrobert
58*404b540aSrobert  if (l) call abort
59*404b540aSrobert  if (.not.associated (bar1)) call abort
60*404b540aSrobert  if (any (bar1.ne.6)) call abort
61*404b540aSrobert  if (.not.associated (bar3)) call abort
62*404b540aSrobert  if (any (bar3 .ne. -2)) call abort
63*404b540aSrobert  deallocate (bar3)
64*404b540aSrobert  if (associated (bar3)) call abort
65*404b540aSrobert
66*404b540aSrobert  allocate (bar3 (10))
67*404b540aSrobert  bar3 = 17
68*404b540aSrobert
69*404b540aSrobert!$omp parallel copyin (bar1, bar2, bar3, baz) num_threads (4) &
70*404b540aSrobert!$omp& reduction (.or.:l)
71*404b540aSrobert  l = l.or..not.associated (bar1)
72*404b540aSrobert  l = l.or.any (bar1.ne.6)
73*404b540aSrobert  l = l.or.any (bar2.ne.130)
74*404b540aSrobert  l = l.or..not.associated (bar3)
75*404b540aSrobert  l = l.or.size (bar3).ne.10
76*404b540aSrobert  l = l.or.any (bar3.ne.17)
77*404b540aSrobert  allocate (bar1 (4))
78*404b540aSrobert  bar1 = omp_get_thread_num ()
79*404b540aSrobert  bar2 = omp_get_thread_num () + 8
80*404b540aSrobert
81*404b540aSrobert  l = l.or.(baz%a.ne.0)
82*404b540aSrobert  l = l.or.(baz%b.ne.1)
83*404b540aSrobert  baz%a = omp_get_thread_num () * 3 + 4
84*404b540aSrobert  baz%b = omp_get_thread_num () * 3 + 5
85*404b540aSrobert
86*404b540aSrobert!$omp barrier
87*404b540aSrobert  if (omp_get_thread_num () .eq. 0) then
88*404b540aSrobert    deallocate (bar3)
89*404b540aSrobert  end if
90*404b540aSrobert  bar3 => bar2
91*404b540aSrobert!$omp barrier
92*404b540aSrobert
93*404b540aSrobert  l = l.or..not.associated (bar1)
94*404b540aSrobert  l = l.or..not.associated (bar3)
95*404b540aSrobert  l = l.or.any (bar1.ne.omp_get_thread_num ())
96*404b540aSrobert  l = l.or.size (bar1).ne.4
97*404b540aSrobert  l = l.or.any (bar2.ne.omp_get_thread_num () + 8)
98*404b540aSrobert  l = l.or.any (bar3.ne.omp_get_thread_num () + 8)
99*404b540aSrobert  l = l.or.size (bar3).ne.2
100*404b540aSrobert
101*404b540aSrobert  l = l.or.(baz%a .ne. omp_get_thread_num () * 3 + 4)
102*404b540aSrobert  l = l.or.(baz%b .ne. omp_get_thread_num () * 3 + 5)
103*404b540aSrobert!$omp end parallel
104*404b540aSrobert
105*404b540aSrobert  if (l) call abort
106*404b540aSrobertend
107