AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / assumed_rank_4.f90
blob756ab2245c5d3d04efa98d1ddd766b6e180a9df6
1 ! { dg-do compile }
2 ! { dg-options "-std=f2008ts" }
4 ! PR fortran/48820
6 ! Assumed-rank constraint checks and other diagnostics
9 subroutine valid1a(x)
10 integer, intent(in), pointer, contiguous :: x(..)
11 end subroutine valid1a
13 subroutine valid1(x)
14 integer, intent(in) :: x(..)
15 end subroutine valid1
17 subroutine valid2(x)
18 type(*) :: x
19 end subroutine valid2
21 subroutine foo99(x)
22 integer x(99)
23 call valid1(x) ! { dg-error "Explicit interface required" }
24 call valid2(x(1)) ! { dg-error "Explicit interface required" }
25 end subroutine foo99
27 subroutine foo(x)
28 integer :: x(..)
29 print *, ubound(x,dim=2000) ! { dg-error "is not a valid dimension index" }
30 call bar(x) ! { dg-error "Assumed-rank argument requires an explicit interface" }
31 call intnl(x) ! { dg-error "requires that the dummy argument 'x' has assumed-rank" }
32 contains
33 subroutine intnl(x)
34 integer :: x(:)
35 end subroutine intnl
36 end subroutine foo
38 subroutine foo2(x)
39 integer :: x(..)
40 call valid3(x(:)) ! { dg-error "Assumed-rank variable x at .1. shall not have a subobject reference" }
41 call valid3(x+1) ! { dg-error "Assumed-rank variable x at .1. may only be used as actual argument" }
42 contains
43 subroutine valid3(y)
44 integer :: y(..)
45 end subroutine
46 end subroutine
48 subroutine foo3()
49 integer :: x(..) ! { dg-error "Assumed-rank array at .1. must be a dummy argument" }
50 end subroutine