re PR fortran/78741 (ICE in gfc_get_symbol_decl, at fortran/trans-decl.c:1534)
[official-gcc.git] / gcc / testsuite / gfortran.dg / alloc_comp_constructor_2.f90
blobcd4fb0e95bbe41245bac0aca2b5bb97df35610d4
1 ! { dg-do run }
2 ! Test constructors of nested derived types with allocatable components(PR 20541).
4 ! Contributed by Erik Edelmann <eedelmann@gcc.gnu.org>
5 ! and Paul Thomas <pault@gcc.gnu.org>
7 type :: thytype
8 integer(4), allocatable :: h(:)
9 end type thytype
11 type :: mytype
12 type(thytype), allocatable :: q(:)
13 end type mytype
15 type (mytype) :: x
16 type (thytype) :: w(2)
17 integer :: y(2) =(/1,2/)
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/))) STOP 1
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/))) STOP 2
26 end