blob: 5d0e7edb71ba37c129d2840c1a528a8d013d6b47 [file] [log] [blame]
Jim Cownie18d84732014-05-10 17:02:09 +00001<ompts:test>
2<ompts:testdescription>Test which checks the guided option of the omp do schedule directive.</ompts:testdescription>
3<ompts:ompversion>2.0</ompts:ompversion>
4<ompts:directive>omp do schedule(guided)</ompts:directive>
5<ompts:dependences>omp flush,omp do nowait,omp critical,omp single</ompts:dependences>
6<ompts:testcode>
7 ! TODO:
8 ! C. Niethammer:
9 ! Find check to decide if the test was run as schedule(static) because
Alp Tokerc2d5e612014-06-01 18:28:36 +000010 ! this also can pass the test if the work is divided into thread-counts
Jim Cownie18d84732014-05-10 17:02:09 +000011 INTEGER FUNCTION <ompts:testcode:functionname>do_schedule_guided</ompts:testcode:functionname>()
12 IMPLICIT NONE
13 INTEGER omp_get_thread_num,omp_get_num_threads
14 CHARACTER*20 logfile
15 INTEGER threads
16 INTEGER tmp_count
17 INTEGER, allocatable :: tmp(:)
18 INTEGER ii, flag
19 INTEGER result
20 INTEGER expected
21 INTEGER openwork
22 DOUBLE PRECISION c
23
24 <ompts:orphan:vars>
25 INTEGER i
26 INTEGER tid
27 INTEGER count
28
29 INTEGER DELAY
30 INTEGER MAX_TIME
31 INTEGER CFSMAX_SIZE
32
33! ... choose small iteration space for small sync. overhead
34 PARAMETER (DELAY = 1)
35 PARAMETER (MAX_TIME = 5)
36 PARAMETER (CFSMAX_SIZE = 150)
37
38 INTEGER notout
39 INTEGER maxiter
40 INTEGER tids(0:CFSMAX_SIZE-1)
41
42 COMMON /orphvars/ notout,maxiter,tids
43 </ompts:orphan:vars>
44
45 result = 0
46 notout = 1
47 maxiter = 0
48 count = 0
49 tmp_count = 0
50 openwork = CFSMAX_SIZE
51<ompts:check>
52
53! Determine the number of available threads
54!$omp parallel
55!$omp single
56 threads = omp_get_num_threads()
57!$omp end single
58!$omp end parallel
59 IF ( threads .LT. 2) THEN
60 PRINT *,"This test only works with at least two threads"
61 WRITE(1,*) "This test only works with at least two threads"
62 <testfunctionname></testfunctionname> = 0
63 STOP
64 END IF
65
66! ... Now the real parallel work:
67! ... Each thread will start immediately with the first chunk.
68
69!$omp parallel private(tid,count) shared(tids,maxiter)
70 tid = omp_get_thread_num()
71 <ompts:orphan>
72!$omp do schedule(guided)
73 DO i = 0 , CFSMAX_SIZE-1
74 count = 0
75!$omp flush(maxiter)
76 IF ( i .GT. maxiter ) THEN
77!$omp critical
78 maxiter = i
79!$omp end critical
80 END IF
81
82!.. if it is not our turn we wait
83! a) until another thread executed an iteration
84! with a higher iteration count
85! b) we are at the end of the loop (first thread finished
86! and set notout=0 OR
87! c) timeout arrived
88
89!$omp flush(maxiter,notout)
90 IF ( notout .GE. 1 .AND. count .LT. MAX_TIME
91 & .AND. maxiter .EQ. i ) THEN
92 DO WHILE ( notout .GE. 1 .AND. count .LT. MAX_TIME
93 & .AND. maxiter .EQ. i )
94 CALL sleep(DELAY)
95 count = count + DELAY
96 END DO
97 END IF
98 tids(i) = tid
99 END DO
100!$omp end do nowait
101 </ompts:orphan>
102
103 notout = 0
104!$omp flush(notout)
105
106!$omp end parallel
107
108!*******************************************************!
109! evaluation of the values
110!*******************************************************!
111 count = 0
112
113 DO i=0, CFSMAX_SIZE - 2
114 IF ( tids(i) .NE. tids(i+1) ) THEN
115 count = count + 1
116 END IF
117 END DO
118
119 ALLOCATE( tmp(0:count) )
120 tmp_count = 0
121 tmp(0) = 1
122! ... calculate the chunksize for each dispatch
123
124 DO i=0, CFSMAX_SIZE - 2
125 IF ( tids(i) .EQ. tids(i+1) ) THEN
126 tmp(tmp_count) = tmp(tmp_count) + 1
127 ELSE
128 tmp_count = tmp_count + 1
129 tmp(tmp_count) = 1
130 END IF
131 END DO
132
133! ... Check if chunk sizes are decreased until equals to
134! ... the specified one, ignore the last dispatch
135! ... for possible smaller remainder
136
137! Determine the constant
138 expected = openwork / threads
139 c = real(tmp(0)) / real(expected)
140 WRITE(1,*) "Found constant to be ", c
141
142 DO i = 0, count - 2
143 WRITE(1,*) "open:", openwork, "size:", tmp(i)
144 IF (expected .GT. 1) THEN
145 expected = c * openwork / threads
146 END IF
147
148 IF (abs(tmp(i) - expected) .GE. 2 ) THEN
149 result = 1
150 WRITE(1,*) "Chunksize differed from expected ",
151 & "value: ",tmp(i), "instead ", expected
152 END IF
153
154 IF (i .GT. 0 .AND. (tmp(i-1) - tmp(i)) .LT. 0) THEN
155 WRITE(1,*) "Chunksize did not decrease: ", tmp(i),
156 & "instead",tmp(i-1)
157 END IF
158
159 openwork = openwork - tmp(i)
160 END DO
161
162 IF ( result .EQ. 0 ) THEN
163 <testfunctionname></testfunctionname> = 1
164 ELSE
165 <testfunctionname></testfunctionname> = 0
166 END IF
167 END
168</ompts:check>
169<ompts:crosscheck>
170 <testfunctionname></testfunctionname> = 0
171 END
172</ompts:crosscheck>
173</ompts:testcode>
174</omtps:test>