File: taskloop-1.f90

package info (click to toggle)
gcc-arm-none-eabi 15%3A14.2.rel1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 1,099,328 kB
  • sloc: cpp: 3,627,108; ansic: 2,571,498; ada: 834,230; f90: 235,082; makefile: 79,231; asm: 74,984; xml: 51,692; exp: 39,736; sh: 33,298; objc: 15,629; python: 15,069; fortran: 14,429; pascal: 7,003; awk: 5,070; perl: 3,106; ml: 285; lisp: 253; lex: 204; haskell: 135
file content (126 lines) | stat: -rw-r--r-- 5,094 bytes parent folder | download | duplicates (2)
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
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
module m
  implicit none
  integer :: t
  !$omp threadprivate (t)
  integer :: f, l, ll, r, r2
  !$omp declare target to(f, l, ll, r, r2)
end module m

subroutine foo(fi, p, pp, g, s, nta, nth, ntm, i1, i2, i3, q)
  use m
  implicit none
  integer, value :: p, pp, g, s, nta, nth, ntm
  logical, value :: fi, i1, i2, i3
  integer, pointer :: q(:)
  integer :: i

  !$omp taskgroup task_reduction(+:r2) !allocate (r2)
  !$omp taskloop simd &
  !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) untied if(taskloop: i1) &
  !$omp& if(simd: i2) final(fi) mergeable priority (pp) &
  !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) in_reduction(+:r2) nontemporal(ntm) &
  !$omp& order(concurrent) !allocate (f)
  do i = 1, 64
    ll = ll + 1
  end do
  !$omp end taskgroup

  !$omp taskgroup task_reduction(+:r) !allocate (r)
  !$omp taskloop simd &
  !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) &
  !$omp& collapse(1) untied if(i1) final(fi) mergeable nogroup priority (pp) &
  !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) in_reduction(+:r) nontemporal(ntm) &
  !$omp& order(concurrent) !allocate (f)
  do i = 1, 64
    ll = ll + 1
  end do
  !$omp taskwait

  !$omp taskloop simd &
  !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) &
  !$omp& collapse(1) if(taskloop: i1) final(fi) priority (pp) &
  !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(+:r) if (simd: i3) nontemporal(ntm) &
  !$omp& order(concurrent) !allocate (f)
  do i = 1, 64
    ll = ll + 1
  end do
  !$omp end taskgroup

  !$omp taskgroup task_reduction (+:r2) !allocate (r2)
  !$omp master taskloop &
  !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) &
  !$omp& collapse(1) untied if(taskloop: i1) final(fi) mergeable priority (pp) &
  !$omp& reduction(default, +:r) in_reduction(+:r2) !allocate (f)
  do i = 1, 64
    ll = ll + 1
  end do
  !$omp end taskgroup

  !$omp taskgroup task_reduction (+:r2) !allocate (r2)
  !$omp master taskloop simd &
  !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) &
  !$omp& collapse(1) untied if(taskloop: i1) if(simd: i2) final(fi) mergeable priority (pp) &
  !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) in_reduction(+:r2) nontemporal(ntm) &
  !$omp& order(concurrent) !allocate (f)
  do i = 1, 64
    ll = ll + 1
  end do
  !$omp end taskgroup

  !$omp parallel master taskloop &
  !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) &
  !$omp& collapse(1) untied if(taskloop: i1) final(fi) mergeable priority (pp) &
  !$omp& reduction(default, +:r) if (parallel: i2) num_threads (nth) proc_bind(spread) copyin(t) !allocate (f)
  do i = 1, 64
    ll = ll + 1
  end do

  !$omp parallel master taskloop simd &
  !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) &
  !$omp& untied if(taskloop: i1) if(simd: i2) final(fi) mergeable priority (pp) &
  !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) nontemporal(ntm) &
  !$omp& if (parallel: i2) num_threads (nth) proc_bind(spread) copyin(t) &
  !$omp& order(concurrent) !allocate (f)
  do i = 1, 64
    ll = ll + 1
  end do

  !$omp taskgroup task_reduction (+:r2) !allocate (r2)
  !$omp master taskloop &
  !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) &
  !$omp& collapse(1) untied if(i1) final(fi) mergeable priority (pp) &
  !$omp& reduction(default, +:r) in_reduction(+:r2)
  do i = 1, 64
    ll = ll + 1
  end do
  !$omp end taskgroup

  !$omp taskgroup task_reduction (+:r2) !allocate (r2)
  !$omp master taskloop simd &
  !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) &
  !$omp& collapse(1) untied if(i1) final(fi) mergeable priority (pp) &
  !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) in_reduction(+:r2) nontemporal(ntm) &
  !$omp& order(concurrent) !allocate (f)
  do i = 1, 64
    ll = ll + 1
  end do
  !$omp end taskgroup

  !$omp parallel master taskloop &
  !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) &
  !$omp& collapse(1) untied if(i1) final(fi) mergeable priority (pp) &
  !$omp& reduction(default, +:r) num_threads (nth) proc_bind(spread) copyin(t) !allocate (f)
  do i = 1, 64
    ll = ll + 1
  end do

  !$omp parallel master taskloop simd &
  !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) &
  !$omp& collapse(1) untied if(i1) final(fi) mergeable priority (pp) &
  !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) &
  !$omp& nontemporal(ntm) num_threads (nth) proc_bind(spread) copyin(t) &
  !$omp& order(concurrent) !allocate (f)
  do i = 1, 64
    ll = ll + 1
  end do
end