OSDN Git Service

2011-09-26 Janus Weil <janus@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / used_before_typed_6.f90
1 ! { dg-do compile }
2 ! { dg-options "-std=gnu" }
3
4 ! Allow legacy code to work even if not only a single symbol is used as
5 ! expression but a basic arithmetic expression.
6
7 SUBROUTINE test (n, m)
8   IMPLICIT NONE
9
10   ! These should go fine.
11   INTEGER :: arr1(n + 1) ! { dg-bogus "used before it is typed" }
12   INTEGER :: arr2(n / (2 * m**5)) ! { dg-bogus "used before it is typed" }
13
14   ! These should fail for obvious reasons.
15   INTEGER :: arr3(n * 1.1) ! { dg-error "must be of INTEGER type" }
16   INTEGER :: arr4(REAL (m)) ! { dg-error "used before it is typed" }
17   INTEGER :: arr5(SIN (m)) ! { dg-error "used before it is typed" }
18
19   INTEGER :: n, m
20 END SUBROUTINE test