aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/realloc_on_assign_23.f90
blob: f9897f17401ee45c2f639fa02a4d90faf7f29c7f (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
27
28
29
30
! { 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) call abort
contains
  subroutine foo
    a = [a, e]
  end subroutine
end