AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / structure_constructor_13.f03
blobdeb0569094581314a677a5e8cb3d26c7aa2a4ac3
1 ! { dg-do run }
3 ! Contributed by Melven Roehrig-Zoellner  <Melven.Roehrig-Zoellner@DLR.de>
4 ! PR fortran/66035
6 program test_pr66035
7   type t
8   end type t
9   type w
10     class(t), allocatable :: c
11   end type w
13   type(t) :: o
15   call test(o)
16 contains
17   subroutine test(o)
18     class(t), intent(inout) :: o
19     type(w), dimension(:), allocatable :: list
21     select type (o)
22       class is (t)
23         list = [w(o)] ! This caused an ICE
24       class default
25         STOP 1
26     end select
27   end subroutine
28 end program