blob: 7ab02f8ef002d9a135d80acfe2f30194a610b3f8 [file] [log] [blame]
Jim Cownie18d84732014-05-10 17:02:09 +00001<ompts:test>
2<ompts:testdescription>Test which checks the static option of the omp do schedule directive.</ompts:testdescription>
3<ompts:ompversion>2.0</ompts:ompversion>
4<ompts:directive>omp do schedule(static)</ompts:directive>
5<ompts:dependences>omp do nowait,omp flush,omp critical,omp single</ompts:dependences>
6<ompts:testcode>
7
8 INTEGER FUNCTION <ompts:testcode:functionname>do_schedule_static</ompts:testcode:functionname>()
9 IMPLICIT NONE
10 INTEGER omp_get_thread_num,omp_get_num_threads
11 CHARACTER*30 logfile
12 INTEGER threads
13 INTEGER count
14 INTEGER ii
15 INTEGER result
16<ompts:orphan:vars>
17 INTEGER CFSMAX_SIZE
18 PARAMETER (CFSMAX_SIZE = 1000)
19 INTEGER i,tids(0:CFSMAX_SIZE-1), tid, chunk_size
20 COMMON /orphvars/ i,tid,tids,chunk_size
21</ompts:orphan:vars>
22
23 chunk_size = 7
24 result = 0
25 ii = 0
26
27!$omp parallel
28!$omp single
29 threads = omp_get_num_threads()
30!$omp end single
31!$omp end parallel
32
33 IF ( threads .LT. 2) THEN
34 PRINT *,"This test only works with at least two threads"
35 WRITE(1,*) "This test only works with at least two threads"
36 <testfunctionname></testfunctionname> = 0
37 STOP
38 ELSE
39 WRITE(1,*) "Using an internal count of ",CFSMAX_SIZE
40 WRITE(1,*) "Using a specified chunksize of ",chunk_size
41
42!$omp parallel private(tid) shared(tids)
43 tid = omp_get_thread_num()
44<ompts:orphan>
45!$omp do <ompts:check>schedule(static,chunk_size)</ompts:check>
46 DO i = 0 ,CFSMAX_SIZE -1
47 tids(i) = tid
48 END DO
49!$omp end do
50</ompts:orphan>
51!$omp end parallel
52
53 DO i = 0, CFSMAX_SIZE-1
54!... round-robin for static chunk
55 ii = mod( i/chunk_size,threads)
56 IF (tids(i) .NE. ii ) THEN
57 result = result + 1
58 WRITE(1,*)"Iteration ",i,"should be assigned to ",
59 & ii,"instead of ",tids(i)
60 END IF
61 END DO
62 IF ( result .EQ. 0 )THEN
63 <testfunctionname></testfunctionname> = 1
64 ELSE
65 <testfunctionname></testfunctionname> = 0
66 END IF
67 END IF
68 END FUNCTION
69</ompts:testcode>
70</ompts:test>