blob: 18f8ba7475236a6acd9c94a0feae21abb5a8e0b2 [file] [log] [blame]
Jim Cownie18d84732014-05-10 17:02:09 +00001<ompts:test>
2<ompts:testdescription>Test which checks the dynamic option of the omp do schedule directive.</ompts:testdescription>
3<ompts:ompversion>2.0</ompts:ompversion>
4<ompts:directive>omp do schedule(dynamic)</ompts:directive>
5<ompts:dependences>omp flush,omp do nowait,omp critical,omp single</ompts:dependences>
6<ompts:testcode>
7
8
9 INTEGER FUNCTION <ompts:testcode:functionname>do_schedule_dynamic</ompts:testcode:functionname>()
10 IMPLICIT NONE
11 CHARACTER*30 logfile
12 INTEGER omp_get_thread_num,omp_get_num_threads
13 INTEGER threads
14 INTEGER count, tmp_count
15 INTEGER,ALLOCATABLE:: tmp(:)
16 INTEGER ii
17 INTEGER result
18
19<ompts:orphan:vars>
20 INTEGER CFDMAX_SIZE
21 PARAMETER (CFDMAX_SIZE = 1000)
22 INTEGER i,tids(0:CFDMAX_SIZE-1),tid,chunk_size
23 COMMON /orphvars/ i,tids,tid,chunk_size
24</ompts:orphan:vars>
25
26 chunk_size = 7
27 count = 0
28 tmp_count = 0
29 result = 0
30 ii = 0
31
32!$omp parallel private(tid)
33 tid = omp_get_thread_num()
34<ompts:orphan>
35!$omp do <ompts:check>schedule(dynamic,chunk_size)</ompts:check>
36 DO i=0, CFDMAX_SIZE-1
37 tids(i) = tid
38 END DO
39!$omp end do
40</ompts:orphan>
41!$omp end parallel
42
43 DO i=0, CFDMAX_SIZE - 2
44 IF ( tids(i) .ne. tids(i+1) ) THEN
45 count = count + 1
46 END IF
47 END DO
48
49 ALLOCATE( tmp(0:count) )
50 tmp(0) = 1
51
52 DO i = 0, CFDMAX_SIZE - 2
53 IF ( tmp_count .GT. count ) THEN
54 WRITE(*,*) "--------------------"
55 WRITE(*,*) "Testinternal Error: List too small!!!"
56 WRITE(*,*) "--------------------"
57 GOTO 10
58 END If
59 IF ( tids(i) .NE. tids(i+1) ) then
60 tmp_count = tmp_count + 1
61 tmp(tmp_count) = 1
62 ELSE
63 tmp(tmp_count) = tmp(tmp_count) +1
64 END IF
65 END DO
66
67!... is dynamic statement working?
68
69 10 DO i=0, count -1
70 IF ( MOD(tmp(i),chunk_size) .ne. 0 ) THEN
71! ... it is possible for 2 adjacent chunks assigned to a same thread
72 result = result + 1
73 WRITE(1,*) "The intermediate dispatch has wrong chunksize."
74 END IF
75 END DO
76
77 IF ( MOD(tmp(count), chunk_size) .NE.
78 & MOD (CFDMAX_SIZE, chunk_size) ) THEN
79 result = result + 1
80 WRITE(1,*) "the last dispatch has wrong chunksize."
81 END IF
82
83 IF ( result .eq. 0) THEN
84 <testfunctionname></testfunctionname> = 1
85 ELSE
86 <testfunctionname></testfunctionname> = 0
87 END IF
88 END FUNCTION
89</ompts:testcode>
90</ompts:test>