1! { dg-do run }
2
3  interface
4    subroutine sub1 (x, y)
5      integer, intent(in) :: y(:)
6      integer, intent(out) :: x(:)
7    end subroutine
8    function fn2 (x, m1, m2, n1, n2)
9      integer, intent(in) :: x(:,:), m1, m2, n1, n2
10      integer :: fn2(m1:m2,n1:n2)
11    end function
12    subroutine sub3 (x, y)
13      integer, allocatable, intent(in) :: y(:,:)
14      integer, allocatable, intent(inout) :: x(:,:)
15    end subroutine
16  end interface
17!$omp declare reduction (foo : integer : sub3 (omp_out, omp_in)) &
18!$omp initializer (omp_priv = fn3 (omp_orig))
19!$omp declare reduction (bar : integer : omp_out = fn1 (omp_out, omp_in, &
20!$omp & lbound (omp_out, 1), ubound (omp_out, 1))) &
21!$omp & initializer (sub1 (omp_priv, omp_orig))
22!$omp declare reduction (baz : integer : sub2 (omp_out, omp_in)) &
23!$omp initializer (omp_priv = fn2 (omp_orig, lbound (omp_priv, 1), &
24!$omp ubound (omp_priv, 1), lbound (omp_priv, 2), ubound (omp_priv, 2)))
25  interface
26    function fn1 (x, y, m1, m2)
27      integer, intent(in) :: x(:), y(:), m1, m2
28      integer :: fn1(m1:m2)
29    end function
30    subroutine sub2 (x, y)
31      integer, intent(in) :: y(:,:)
32      integer, intent(inout) :: x(:,:)
33    end subroutine
34    function fn3 (x)
35      integer, allocatable, intent(in) :: x(:,:)
36      integer, allocatable :: fn3(:,:)
37    end function
38  end interface
39  integer :: a(10), b(3:5,7:9), r
40  integer, allocatable :: c(:,:)
41  a(:) = 0
42  r = 0
43!$omp parallel reduction (bar : a) reduction (+: r)
44  if (lbound (a, 1) /= 1 .or. ubound (a, 1) /= 10) stop 1
45  a = a + 2
46  r = r + 1
47!$omp end parallel
48  if (any (a /= 4 * r) ) stop 2
49  b(:,:) = 0
50  allocate (c (4:6,8:10))
51  c(:,:) = 0
52  r = 0
53!$omp parallel reduction (baz : b, c) reduction (+: r)
54  if (lbound (b, 1) /= 3 .or. ubound (b, 1) /= 5) stop 3
55  if (lbound (b, 2) /= 7 .or. ubound (b, 2) /= 9) stop 4
56  if (.not. allocated (c)) stop 5
57  if (lbound (c, 1) /= 4 .or. ubound (c, 1) /= 6) stop 6
58  if (lbound (c, 2) /= 8 .or. ubound (c, 2) /= 10) stop 7
59  b = b + 3
60  c = c + 4
61  r = r + 1
62!$omp end parallel
63  if (any (b /= 3 * r) .or. any (c /= 4 * r)) stop 8
64  deallocate (c)
65  allocate (c (0:1,7:11))
66  c(:,:) = 0
67  r = 0
68!$omp parallel reduction (foo : c) reduction (+: r)
69  if (.not. allocated (c)) stop 9
70  if (lbound (c, 1) /= 0 .or. ubound (c, 1) /= 1) stop 10
71  if (lbound (c, 2) /= 7 .or. ubound (c, 2) /= 11) stop 11
72  c = c + 5
73  r = r + 1
74!$omp end parallel
75  if (any (c /= 10 * r)) stop 12
76end
77function fn1 (x, y, m1, m2)
78  integer, intent(in) :: x(:), y(:), m1, m2
79  integer :: fn1(m1:m2)
80  fn1 = x + 2 * y
81end function
82subroutine sub1 (x, y)
83  integer, intent(in) :: y(:)
84  integer, intent(out) :: x(:)
85  x = 0
86end subroutine
87function fn2 (x, m1, m2, n1, n2)
88  integer, intent(in) :: x(:,:), m1, m2, n1, n2
89  integer :: fn2(m1:m2,n1:n2)
90  fn2 = x
91end function
92subroutine sub2 (x, y)
93  integer, intent(inout) :: x(:,:)
94  integer, intent(in) :: y(:,:)
95  x = x + y
96end subroutine
97function fn3 (x)
98  integer, allocatable, intent(in) :: x(:,:)
99  integer, allocatable :: fn3(:,:)
100  fn3 = x
101end function
102subroutine sub3 (x, y)
103  integer, allocatable, intent(inout) :: x(:,:)
104  integer, allocatable, intent(in) :: y(:,:)
105  x = x + 2 * y
106end subroutine
107