aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/alloc_comp_constructor_2.f90
blob: 08c3bdf696ebdfaec0eac3dd6ac4b3f471e0f525 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
! { dg-do run }
! Test constructors of nested derived types with allocatable components(PR 20541).
!
! Contributed by Erik Edelmann  <eedelmann@gcc.gnu.org>
!            and Paul Thomas  <pault@gcc.gnu.org>
!
  type :: thytype
    integer(4), allocatable :: h(:)
  end type thytype

  type :: mytype
    type(thytype), allocatable :: q(:)
  end type mytype

  type (mytype) :: x
  type (thytype) :: w(2)
  integer :: y(2) =(/1,2/)

  w = (/thytype(y), thytype (2*y)/)
  x = mytype (w)
  if (any ((/((x%q(j)%h(i),j=1,2),i=1,2)/) .ne. (/1,2,2,4/))) call abort ()

  x = mytype ((/thytype(3*y), thytype (4*y)/))
  if (any ((/((x%q(j)%h(i),j=1,2),i=1,2)/) .ne. (/3,4,6,8/))) call abort ()

end