PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / assumed_rank_6.f90
blob86da3f853c3a05df6cc6988e518a06c987e08b62
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
4 ! PR fortran/48820
6 ! Assumed-rank constraint checks and other diagnostics
9 subroutine foo(x) ! { dg-error "Assumed-type variable x at .1. may not have the INTENT.OUT. attribute" }
10 type(*), intent(out) :: x
11 end subroutine
13 subroutine bar(x)
14 integer, intent(out) :: x(..)
15 end subroutine bar
17 subroutine foo3(y)
18 integer :: y(..)
19 y = 7 ! { dg-error "Assumed-rank variable y at .1. may only be used as actual argument" }
20 print *, y + 10 ! { dg-error "Assumed-rank variable y at .1. may only be used as actual argument" }
21 print *, y ! { dg-error "Assumed-rank variable y at .1. may only be used as actual argument" }
22 end subroutine
24 subroutine foo2(x, y)
25 integer :: x(..), y(..)
26 call valid3(x(:)) ! { dg-error "Assumed-rank variable x at .1. shall not have a subobject reference" }
27 contains
28 subroutine valid3(y)
29 integer :: y(..)
30 end subroutine
31 end subroutine
33 subroutine foo4(x)
34 integer, codimension[*] :: x(..) ! { dg-error "The assumed-rank array at .1. shall not have a codimension" }
35 end subroutine
37 subroutine foo5(y) ! { dg-error "may not have the VALUE or CODIMENSION attribute" }
38 integer :: y(..)[*]
39 end subroutine