blob: 71a28e3902e6c59e3e6bab139d2ba731cf0ad1a9 [file] [log] [blame]
! { dg-do run }
!
! PR fortran/57354
!
! Contributed by Vladimir Fuka <vladimir.fuka@gmail.com>
!
type t
integer,allocatable :: i
end type
type(t) :: e
type(t), allocatable :: a(:)
integer :: chksum = 0
do i=1,3 ! Was 100 in original
e%i = i
chksum = chksum + i
if (.not.allocated(a)) then
a = [e]
else
call foo
end if
end do
if (sum ([(a(i)%i, i=1,size(a))]) .ne. chksum) STOP 1
contains
subroutine foo
a = [a, e]
end subroutine
end