Fix gcc.c-torture/execute/ieee/cdivchkf.c on hpux
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / depend-4.f90
blob35b47e93ac2d6fcc2563915dbe9c3b2bcfe6adff
1 ! { dg-additional-options "-fdump-tree-gimple" }
3 ! { dg-additional-sources my-usleep.c }
4 ! { dg-additional-options -Wno-complain-wrong-lang }
6 ! Ensure that 'depend(...: var)' and 'depobj(...) depend(...: var)'
7 ! depend on the same variable when 'var' is a pointer
9 program main
10 use omp_lib
11 use iso_c_binding
12 implicit none (external, type)
14 interface
15 subroutine usleep(t) bind(C, name="my_usleep")
16 use iso_c_binding
17 integer(c_int), value :: t
18 end subroutine
19 end interface
21 integer :: bbb
22 integer, target :: c
23 integer(omp_depend_kind) :: obj(2)
24 integer, pointer :: ppp
26 integer :: x1, x2, x3
28 c = 42
29 ppp => c
31 if (.not. associated (ppp)) &
32 stop 0;
34 x1 = 43
35 x2 = 44
36 x3 = 45
37 !$omp depobj(obj(1)) depend(inout: ppp)
38 !$omp depobj(obj(2)) depend(in: bbb)
40 !$omp parallel num_threads(5)
41 !$omp single
43 !$omp task depend (out: ppp)
44 write (*,*) "task 1 (start)"
45 call usleep(40)
46 if (x1 /= 43) stop 11
47 if (x2 /= 44) stop 12
48 x1 = 11
49 write (*,*) "task 1 (end)"
50 !$omp end task
52 !$omp task depend(inout: ppp)
53 write (*,*) "task 2 (start)"
54 call usleep(30)
55 if (x1 /= 11) stop 21
56 if (x2 /= 44) stop 22
57 x1 = 111
58 x2 = 222
59 write (*,*) "task 2 (end)"
60 !$omp end task
62 !$omp task depend(out: bbb)
63 write (*,*) "task 3 (start)"
64 call usleep(40)
65 if (x3 /= 45) stop 3
66 x3 = 33
67 write (*,*) "task 3 (end)"
68 !$omp end task
70 !$omp task depend(depobj: obj(1), obj(2))
71 write (*,*) "task 4 (start)"
72 if (x1 /= 111) stop 41
73 if (x2 /= 222) stop 42
74 if (x3 /= 33) stop 43
75 call usleep(10)
76 x1 = 411
77 x2 = 422
78 x3 = 433
79 write (*,*) "task 4 (end)"
80 !$omp end task
82 !$omp task depend(in: ppp)
83 if (x1 /= 411) stop 51
84 if (x2 /= 422) stop 52
85 if (x3 /= 433) stop 53
86 write (*,*) "task 5"
87 !$omp end task
89 !$omp end single
90 !$omp end parallel
92 ! expectation (task dependencies):
93 ! 1 - 2 \
94 ! 4 - 5
95 ! 3 ----/
97 end program main
99 ! Ensure that the pointer target address for ppp is taken
100 ! but the address of bbb itself:
102 ! { dg-final { scan-tree-dump-times "#pragma omp task depend\\(out:ppp\\)" 1 "gimple" } }
103 ! { dg-final { scan-tree-dump-times "#pragma omp task depend\\(inout:ppp\\)" 1 "gimple" } }
104 ! { dg-final { scan-tree-dump-times "#pragma omp task depend\\(out:&bbb\\)" 1 "gimple" } }
105 ! { dg-final { scan-tree-dump-times "#pragma omp task depend\\(depobj:&obj\\\[0\\\]\\) depend\\(depobj:&obj\\\[1\\\]\\)" 1 "gimple" } }
106 ! { dg-final { scan-tree-dump-times "#pragma omp task depend\\(in:ppp\\)" 1 "gimple" } }
108 ! { dg-final { scan-tree-dump-times "MEM\\\[\[^\r\n]+\\\] = ppp;" 1 "gimple" } }
109 ! { dg-final { scan-tree-dump-times "MEM\\\[\[^\r\n]+\\\] = &bbb;" 1 "gimple" } }