Merged trunk at revision 161680 into branch.
[official-gcc.git] / gcc / testsuite / gfortran.dg / alloc_comp_class_1.f90
blobc783f49ff77f097c4dc063289b7ccbc595731110
1 ! { dg-do run }
2 ! Test the fix for PR43895, in which the dummy 'a' was not
3 ! dereferenced for the deallocation of component 'a', as required
4 ! for INTENT(OUT).
6 ! Contributed by Salvatore Filippone <sfilippone@uniroma2.it>
8 module d_mat_mod
9 type :: base_sparse_mat
10 end type base_sparse_mat
12 type, extends(base_sparse_mat) :: d_base_sparse_mat
13 integer :: i
14 end type d_base_sparse_mat
16 type :: d_sparse_mat
17 class(d_base_sparse_mat), allocatable :: a
18 end type d_sparse_mat
19 end module d_mat_mod
21 use d_mat_mod
22 type(d_sparse_mat) :: b
23 allocate (b%a)
24 b%a%i = 42
25 call bug14 (b)
26 if (allocated (b%a)) call abort
27 contains
28 subroutine bug14(a)
29 implicit none
30 type(d_sparse_mat), intent(out) :: a
31 end subroutine bug14
32 end
33 ! { dg-final { cleanup-modules "d_mat_mod " } }