OSDN Git Service

2011-08-18 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / assumed_size_refs_3.f90
1 ! { dg-do compile }
2 ! Tests the fix for PR25951, a regression caused by the assumed
3 ! size patch.
4 ! Test case provided by Mark Hesselink  <mhesseli@caltech.edu>
5 PROGRAM loc_1
6   integer i(10)
7   call f (i)
8 CONTAINS
9    SUBROUTINE f (x)
10       INTEGER, DIMENSION(*)   :: x
11       INTEGER                 :: address
12 ! The next line would cause:
13 ! Error: The upper bound in the last dimension must appear in the
14 ! reference to the assumed size array 'x' at (1)
15       address=LOC(x)
16    END SUBROUTINE f
17 END PROGRAM loc_1