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