lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / alloc_comp_misc_1.f90
blobe118b0328017c2886346d9c890ee8bc7f56217c1
1 ! PR 29804
2 ! This used to fail, it was magically fixed; keep in the testsuite so
3 ! that we keep an eye on it.
5 ! { dg-do run }
6 ! { dg-options "-fbounds-check" }
7 program dt_bnd
8 implicit none
10 type dbprc_type
11 integer, allocatable :: ipv(:)
12 end type dbprc_type
14 type(dbprc_type), allocatable :: pre(:)
15 call ppset(pre)
17 contains
18 subroutine ppset(p)
19 type(dbprc_type),allocatable, intent(inout) :: p(:)
20 integer :: nl
21 nl = 1
23 allocate(p(1))
24 if (.not.allocated(p(nl)%ipv)) then
25 allocate(p(1)%ipv(1))
26 end if
27 end subroutine ppset
28 end program dt_bnd