1181834Sroberto! { dg-do run }
2290000Sglebius! { dg-options "-fdefault-integer-8 -O2" }
3290000Sglebius! Tests the fix for PR34143, where the implicit type
4290000Sglebius! conversion in the derived type constructor would fail,
5290000Sglebius! when 'yy' was not allocated.  The testscase is an
6290000Sglebius! extract from alloc_comp_constructor.f90.
7290000Sglebius!
8290000Sglebius! Reported by Thomas Koenig <tkoenig@gcc.gnu.org>
9290000Sglebius!
10290000SglebiusProgram test_constructor
11290000Sglebius    implicit none
12290000Sglebius    type :: thytype
13290000Sglebius        integer(4) :: a(2,2)
14290000Sglebius    end type thytype
15290000Sglebius    type :: mytype
16290000Sglebius        integer(4), allocatable :: a(:, :)
17290000Sglebius        type(thytype), allocatable :: q(:)
18290000Sglebius    end type mytype
19290000Sglebius    integer, allocatable :: yy(:,:)
20290000Sglebius    type (thytype), allocatable :: bar(:)
21290000Sglebius    call non_alloc
22290000Sglebius    call alloc
23290000Sglebiuscontains
24290000Sglebius    subroutine non_alloc
25290000Sglebius      type (mytype) :: x
26290000Sglebius      x = mytype(yy, bar)
27290000Sglebius      if (allocated (x%a) .or. allocated (x%q)) call abort
28290000Sglebius    end subroutine non_alloc
29181834Sroberto    subroutine alloc
30290000Sglebius      type (mytype) :: x
31181834Sroberto      allocate (yy(2,2))
32181834Sroberto      allocate (bar(2))
33181834Sroberto      yy = reshape ([10,20,30,40],[2,2])
34181834Sroberto      bar = thytype (reshape ([1,2,3,4],[2,2]))
35181834Sroberto      x = mytype(yy, bar)
36181834Sroberto      if (.not.allocated (x%a) .or. .not.allocated (x%q)) call abort
37181834Sroberto    end subroutine alloc
38181834Srobertoend program test_constructor
39181834Sroberto