c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / alloc_comp_basics_5.f90
blob7e88cf26947fcddfa3aa2cbab06e6754718826b0
1 ! { dg-do run }
2 ! This checks the correct functioning of derived types with the SAVE
3 ! attribute and allocatable components - PR31163
5 ! Contributed by Salvatore Filippone <salvatore.filippone@uniroma2.it>
7 Module bar_mod
9 type foo_type
10 integer, allocatable :: mv(:)
11 end type foo_type
14 contains
17 subroutine bar_foo_ab(info)
19 integer, intent(out) :: info
20 Type(foo_type), save :: f_a
22 if (allocated(f_a%mv)) then
23 info = size(f_a%mv)
24 else
25 allocate(f_a%mv(10),stat=info)
26 if (info /= 0) then
27 info = -1
28 endif
29 end if
30 end subroutine bar_foo_ab
33 end module bar_mod
35 program tsave
36 use bar_mod
38 integer :: info
40 call bar_foo_ab(info)
41 if (info .ne. 0) STOP 1
42 call bar_foo_ab(info)
43 if (info .ne. 10) STOP 2
45 end program tsave