2010-11-11 Jakub Jelinek <jakub@redhat.com>
[official-gcc.git] / gcc / testsuite / gfortran.dg / multiple_allocation_1.f90
blob2b913734e478f170f823f562761792b9b7f553cf
1 ! { dg-do run }
2 ! PR 25031 - We didn't cause an error when allocating an already
3 ! allocated array.
4 program alloc_test
5 implicit none
6 integer :: i
7 integer, allocatable :: a(:)
8 integer, pointer :: b(:)
10 allocate(a(4))
11 ! This should set the stat code and change the size.
12 allocate(a(3),stat=i)
13 if (i == 0) call abort
14 if (.not. allocated(a)) call abort
15 if (size(a) /= 3) call abort
16 ! It's OK to allocate pointers twice (even though this causes
17 ! a memory leak)
18 allocate(b(4))
19 allocate(b(4))
20 end program