Add support for ARMv8-R architecture
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / taskloop3.f90
blob748433baf553b6c9d644c63f63e1897cb6a7f91e
1 ! { dg-do run }
2 ! { dg-options "-O2" }
4 integer, save :: g
5 integer :: i
6 !$omp parallel
7 !$omp single
8 if (f1 (74) .ne. 63 + 4) call abort
9 g = 77
10 call f2
11 !$omp taskwait
12 if (g .ne. 63 + 9) call abort
13 if (f3 (7_8, 11_8, 2_8) .ne. 11 * 7 + 13) call abort
14 if (f4 (0_8, 31_8, 16_8, 46_8, 1_8, 2_8, 73) .ne. 32 + 5 * 48 &
15 & + 11 * 31 + 17 * 46) call abort
16 !$omp end single
17 !$omp end parallel
18 contains
19 function f1 (y)
20 integer, intent(in) :: y
21 integer :: i, f1, x
22 x = y
23 !$omp taskloop firstprivate(x)lastprivate(x)
24 do i = 0, 63
25 if (x .ne. 74) call abort
26 if (i .eq. 63) then
27 x = i + 4
28 end if
29 end do
30 f1 = x
31 end function f1
32 subroutine f2 ()
33 integer :: i
34 !$omp taskloop firstprivate(g)lastprivate(g)nogroup
35 do i = 0, 63
36 if (g .ne. 77) call abort
37 if (i .eq. 63) then
38 g = i + 9
39 end if
40 end do
41 end subroutine f2
42 function f3 (a, b, c)
43 integer(kind=8), intent(in) :: a, b, c
44 integer(kind=8) :: i, f3
45 integer :: l
46 !$omp taskloop default(none) lastprivate (i, l)
47 do i = a, b, c
48 l = i
49 end do
50 !$omp end taskloop
51 f3 = l * 7 + i
52 end function f3
53 function f4 (a, b, c, d, e, f, m)
54 integer(kind=8), intent(in) :: a, b, c, d, e, f
55 integer(kind=8) :: i, j, f4
56 integer, intent(in) :: m
57 integer :: l, k
58 k = m
59 !$omp taskloop default (none) collapse (2) firstprivate (k) &
60 !$omp & lastprivate (i, j, k, l)
61 do i = a, b, e
62 do j = c, d, f
63 if (k .ne. 73) call abort
64 if (i .eq. 31 .and. j .eq. 46) then
65 k = i
66 end if
67 l = j
68 end do
69 end do
70 f4 = i + 5 * j + 11 * k + 17 * l
71 end function f4
72 end