1! { dg-do run }
2!
3! TS 29113
4! 6.3  Argument association
5! An assumed-rank dummy argument may correspond to an actual argument of
6! any rank. [...] If the actual argument has rank greater than zero, the
7! rank and extents of the dummy argument are assumed from the actual
8! argument, including the lack of a final extent in the case of an
9! assumed-size array. If the actual argument is an array and the dummy
10! argument is allocatable or a pointer, the bounds of the dummy argument
11! are assumed from the actual argument.
12
13program test
14
15  integer, allocatable :: a(:,:,:)
16  integer, allocatable :: b(:,:,:,:)
17
18  allocate (a(3, 4, 5))
19  allocate (b(-3:3, 0:4, 2:5, 10:20))
20
21  call testit (a, rank(a), shape(a), lbound(a), ubound(a))
22  call testit (b, rank(b), shape(b), lbound(b), ubound(b))
23
24contains
25
26  subroutine testit (x, r, s, l, u) bind (c)
27    integer, allocatable :: x(..)
28    integer :: r
29    integer :: s(r)
30    integer :: l(r)
31    integer :: u(r)
32
33    ! expect rank to match
34    if (rank (x) .ne. r) stop 101
35
36    ! expect shape to match
37    if (size (shape (x)) .ne. r) stop 102
38    if (any (shape (x) .ne. s))  stop 103
39
40    ! expect lbound and ubound functions to return rank-sized arrays.
41    ! for non-pointer/non-allocatable arrays, bounds are normalized
42    ! to be 1-based.
43    if (size (lbound (x)) .ne. r) stop 104
44    if (any (lbound (x) .ne. l)) stop 105
45
46    if (size (ubound (x)) .ne. r) stop 106
47    if (any (ubound (x) .ne. u)) stop 107
48  end subroutine
49
50end program
51