OSDN Git Service

2010-06-07 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / dependency_19.f90
1 ! { dg-do compile }
2 ! Tests the fix for PR30273, in which the pointer assignment was
3 ! wrongly determined to have dependence because NULL() was not
4 ! recognised by the analysis.
5 !
6 ! Contributed by Harald Anlauf <anlauf@gmx.de>
7 !
8 module gfcbug49
9   implicit none
10
11   type spot_t
12      integer, pointer     :: vm(:,:,:)
13   end type spot_t
14
15   type rc_t
16     integer               :: n
17     type(spot_t), pointer :: spots(:) => NULL()
18   end type rc_t  
19
20 contains
21
22   subroutine construct (rc, n)
23     type(rc_t), intent(out) :: rc
24     integer   , intent(in)  :: n
25     integer :: k
26     rc% n = n
27     allocate (rc% spots (n))
28     forall (k=1:n)
29        rc% spots (k)% vm => NULL() ! gfortran didn't swallow this
30     end forall
31   end subroutine construct
32
33 end module gfcbug49
34 ! { dg-final { cleanup-modules "gfcbug49" } }