aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/libgomp/testsuite/libgomp.fortran/threadprivate4.f90
blob: b5fb10bfee765e51df14b6f54404aa2aef4064d8 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
! { dg-do run }
! { dg-require-effective-target tls_runtime }

module threadprivate4
  integer :: vi
  procedure(), pointer :: foo
!$omp threadprivate (foo, vi)

contains
  subroutine fn0
    vi = 0
  end subroutine fn0
  subroutine fn1
    vi = 1
  end subroutine fn1
  subroutine fn2
    vi = 2
  end subroutine fn2
  subroutine fn3
    vi = 3
  end subroutine fn3
end module threadprivate4

  use omp_lib
  use threadprivate4

  integer :: i
  logical :: l

  procedure(), pointer :: bar1
  common /thrc/ bar1
!$omp threadprivate (/thrc/)

  procedure(), pointer, save :: bar2
!$omp threadprivate (bar2)

  l = .false.
  call omp_set_dynamic (.false.)
  call omp_set_num_threads (4)

!$omp parallel num_threads (4) reduction (.or.:l) private (i)
  i = omp_get_thread_num ()
  if (i.eq.0) then
    foo => fn0
    bar1 => fn0
    bar2 => fn0
  elseif (i.eq.1) then
    foo => fn1
    bar1 => fn1
    bar2 => fn1
  elseif (i.eq.2) then
    foo => fn2
    bar1 => fn2
    bar2 => fn2
  else
    foo => fn3
    bar1 => fn3
    bar2 => fn3
  end if
  vi = -1
!$omp barrier
  vi = -1
  call foo ()
  l=l.or.(vi.ne.i)
  vi = -2
  call bar1 ()
  l=l.or.(vi.ne.i)
  vi = -3
  call bar2 ()
  l=l.or.(vi.ne.i)
  vi = -1
!$omp end parallel

  if (l) call abort

end

! { dg-final { cleanup-modules "threadprivate4" } }