Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

bug in nested finalization

may_ka
Beginner
255 Views

Hi,

the code below yields a nice memory leak due to missing finalizer call at deallocation:

module mod_xxx
  use, intrinsic :: iso_fortran_env, only: int64, real64,int32
  implicit none
  type :: a1
    real(real64), pointer :: x(:,:)=>null()
  contains
    final :: subfinal_a1
  end type a1
  type, abstract :: b1
    class(a1), allocatable :: a
  end type b1
  type, extends(b1) :: b2
  contains
    procedure :: init => subinit
    final :: subfinal_b2
  end type b2
contains
  subroutine subfinal_a1(this)
    implicit none
    type(a1), intent(inout) :: this
    write(*,*) "subfinal_a1"
    if(associated(this%x)) deallocate(this%x)
  end subroutine subfinal_a1
  subroutine subinit(this,n)
    implicit none
    class(b2), intent(inout) :: this
    integer, intent(in) :: n
    allocate(this%a)
    allocate(this%a%x(n,n),source=0.0_real64)
  end subroutine subinit
  subroutine subfinal_b2(this)
    implicit none
    type(b2), intent(inout) :: this
    write(*,*) "subfinal_b2"
  end subroutine subfinal_b2
end module mod_xxx
program test
  use mod_xxx, only: b2
  implicit none
  class(b2), allocatable :: y
  integer :: i
  do i=1,1000
    allocate(y)
    call y%init(1000)
    deallocate(y)
  end do
end program test

 

the workaround is to either move "class(a1), allocatable :: a" into b2 or explicitly deallocate "a" in "subfinal_b2". From my understanding this is a bug, and gfortran 10.2 behaves accordingly. If somebody can confirm this I'll lodge a bug report.

Thanks

operation system: linux, kernel version 5.8.11

ifort compiler: 19.1.2.254

0 Kudos
0 Replies
Reply