PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / alloc_comp_basics_2.f90
blobf10eaf7c932859e4bdecdab71e8561ccf126c18a
1 ! { dg-do run }
2 ! Check "double" allocations of allocatable components (PR 20541).
4 ! Contributed by Erik Edelmann <eedelmann@gcc.gnu.org>
5 ! and Paul Thomas <pault@gcc.gnu.org>
7 program main
9 implicit none
11 type foo
12 integer, dimension(:), allocatable :: array
13 end type foo
15 type(foo),allocatable,dimension(:) :: mol
16 type(foo),pointer,dimension(:) :: molp
17 integer :: i
19 allocate (mol(1))
20 allocate (mol(1), stat=i)
21 !print *, i ! /= 0
22 if (i == 0) STOP 1
24 allocate (mol(1)%array(5))
25 allocate (mol(1)%array(5),stat=i)
26 !print *, i ! /= 0
27 if (i == 0) STOP 2
29 allocate (molp(1))
30 allocate (molp(1), stat=i)
31 !print *, i ! == 0
32 if (i /= 0) STOP 3
34 allocate (molp(1)%array(5))
35 allocate (molp(1)%array(5),stat=i)
36 !print *, i ! /= 0
37 if (i == 0) STOP 4
39 end program main