libgfortran/ChangeLog:
[official-gcc.git] / gcc / testsuite / gfortran.dg / multiple_allocation_1.f90
blob58888f0e31b00b7f3a374b4dc1fc167e6b887013
1 ! { dg-do run }
2 ! PR 25031 - We didn't cause an error when allocating an already
3 ! allocated array.
5 ! This testcase has been modified to fix PR 49755.
6 program alloc_test
7 implicit none
8 integer :: i
9 integer, allocatable :: a(:)
10 integer, pointer :: b(:)
12 allocate(a(4))
13 ! This should set the stat code but not change the size.
14 allocate(a(3),stat=i)
15 if (i == 0) call abort
16 if (.not. allocated(a)) call abort
17 if (size(a) /= 4) call abort
19 ! It's OK to allocate pointers twice (even though this causes
20 ! a memory leak)
21 allocate(b(4))
22 allocate(b(4))
23 end program