modula2: Simplify REAL/LONGREAL/SHORTREAL node creation.
[official-gcc.git] / gcc / testsuite / gfortran.dg / select_rank_3.f90
blob35cd8cd9a0e2a1ae79a940f823c123e1d8edef61
1 ! { dg-do compile }
3 ! Test the fix for PR91729
5 ! Contributed by Gerhardt Steinmetz <gscfq@t-online.de>
7 subroutine s(x)
8 integer :: x(..)
9 select rank (-x) ! { dg-error "must be an assumed rank" }
10 rank (1) ! { dg-error "Unexpected RANK statement" }
11 print *, x ! { dg-error "may only be used as actual argument" }
12 end select ! { dg-error "Expecting END SUBROUTINE" }
13 end
15 subroutine t(x)
16 integer :: x(..)
17 select rank (z => -x) ! { dg-error "must be an assumed rank" }
18 rank (1) ! { dg-error "Unexpected RANK statement" }
19 print *, z
20 end select ! { dg-error "Expecting END SUBROUTINE" }
21 end