aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/alloc_comp_class_1.f90
blob: 8add2c7f4861b1ecd429a08f75718b082f80cd67 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
! { dg-do run }
! Test the fix for PR43895, in which the dummy 'a' was not
! dereferenced for the deallocation of component 'a', as required
! for INTENT(OUT).
!
! Contributed by Salvatore Filippone <sfilippone@uniroma2.it>
!
module d_mat_mod
  type  :: base_sparse_mat
  end type base_sparse_mat

  type, extends(base_sparse_mat) :: d_base_sparse_mat
    integer :: i
  end type d_base_sparse_mat

  type :: d_sparse_mat
    class(d_base_sparse_mat), allocatable  :: a 
  end type d_sparse_mat
end module d_mat_mod

  use d_mat_mod
  type(d_sparse_mat) :: b
  allocate (b%a)
  b%a%i = 42
  call bug14 (b)
  if (allocated (b%a)) call abort
contains
  subroutine bug14(a)
    implicit none
    type(d_sparse_mat), intent(out) :: a
  end subroutine bug14
end