OSDN Git Service

2011-04-29 Jerry DeLisle <jvdelisle@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / alloc_comp_constructor_2.f90
1 ! { dg-do run }
2 ! Test constructors of nested derived types with allocatable components(PR 20541).
3 !
4 ! Contributed by Erik Edelmann  <eedelmann@gcc.gnu.org>
5 !            and Paul Thomas  <pault@gcc.gnu.org>
6 !
7   type :: thytype
8     integer(4), allocatable :: h(:)
9   end type thytype
10
11   type :: mytype
12     type(thytype), allocatable :: q(:)
13   end type mytype
14
15   type (mytype) :: x
16   type (thytype) :: w(2)
17   integer :: y(2) =(/1,2/)
18
19   w = (/thytype(y), thytype (2*y)/)
20   x = mytype (w)
21   if (any ((/((x%q(j)%h(i),j=1,2),i=1,2)/) .ne. (/1,2,2,4/))) call abort ()
22
23   x = mytype ((/thytype(3*y), thytype (4*y)/))
24   if (any ((/((x%q(j)%h(i),j=1,2),i=1,2)/) .ne. (/3,4,6,8/))) call abort ()
25
26 end