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

FINALIZER confusion with pointers

may_ka
Beginner
270 Views

Hi there,

the following example yields seg faults is complied uncommenting "trial a" and commenting "trail b", but works nicely if commented vice versa.

Module mod_type1
  type :: type1
    real, pointer :: p(:,:)=>null()
  contains
    Final :: Dealloc
  End type type1
contains
  Subroutine Dealloc(this)
    type(type1) :: this
    write(*,*) "I am here"
    Deallocate(this%p)
  End Subroutine Dealloc
End Module mod_type1
program Test
  use mod_type1
  real, allocatable, Target :: a(:,:)
  type(type1), allocatable :: b
  allocate(a(1000,1000))
  !!@@@@@@@@@
  !! trial a
  !allocate(b)
  !b%p=>a
  !Deallocate(b)
  !!@@@@@@@@@@
  !! trial b
  allocate(b)
  allocate(b%p(1000,1000))
  Deallocate(b)
End program Test

The big thing is that one cannot ask whether a pointer is allocated or just associated. Otherwise one could make an if branch in "Dealloc" either nullifying or deallocating. From putting trial b into a loop I found that just putting a nullify statment int "Dealloc" will result in memory leak.

Am I missing something here??? Or does one has to live with the risk that the pointer may have been "abused" for memory allocation when writing the finalizer??

Thanks

Karl

0 Kudos
6 Replies
IanH
Honored Contributor II
270 Views

The language rules prohibit an attempt to deallocate an allocatable variable through a pointer (see final sentence of F2008 6.7.3.3p1).

It is not clear from your example what the design intent of your code is.  Typically it should be clear at a point in your code which thing "owns" the target of a pointer.

0 Kudos
FortranFan
Honored Contributor II
270 Views

See IanH's comment above on your design intent being unclear.  With the use of a pointer component, you're venturing into territory that requires some thought and attention.  Does your type really need to support the use cases indicated by both trial a and trial b?  If your primary need is along the lines of your trial b, you may simply make the component of your type a variable with ALLOCATABLE attribute instead of a pointer.  If you do want to do both, you would need to accept some responsibility and keep track of ownership of allocated memory yourself.  A simple example is:

module m

   implicit none

   private

   type, public :: t
      private
      logical :: p_alloc = .false.
      integer, pointer, public :: p(:) => null()
   contains
      private
      final :: clean_t
      procedure, pass(this), public :: set_p
   end type t

contains

   subroutine set_p( this, n )

      class(t), intent(inout) :: this
      integer, intent(in)     :: n

      !.. Local variables
      integer :: istat

      call clean_t( this )

      allocate( this%p(n), stat=istat )
      if ( istat == 0 ) then
         this%p_alloc = .true.
      end if

      return

   end subroutine set_p

   subroutine clean_t( this )

      type(t), intent(inout) :: this

      print *, "clean_t invoked."

      if (this%p_alloc) then
         deallocate(this%p)
      end if
      this%p => null()
      this%p_alloc = .false.

      return

   end subroutine clean_t

end module m
program p

   use m, only : t

   integer, parameter :: n = 1
   integer, allocatable, target :: a(:)
   type(t), allocatable :: b

   !.. Trial A
   allocate( a(n) )
   allocate(b)
   b%p => a
   deallocate(b)
   deallocate(a)

   !.. Trial B
   allocate(b)
   call b%set_p( n=n )
   deallocate(b)

   stop

end program p

Try the above example and see if you still get the segmentation fault and also run it through Valgrind and Intel Inspector, etc. and check for memory leaks.

0 Kudos
may_ka
Beginner
270 Views

Hi there,

Thanks for the reply. I can(have to) live with the responibility and had already code like the logical switch in mind. But I thought I was missing something.

However, your question was about the intent of of such code.

It is for instance usefull when doing linked list where the acutal list content is stored behind an (unlimited) polymorphic pointer. Such a list struture would look like

Module Mod_MMatrix
Type :: MMatrix
  Real, Pointer :: tmp(:,:)=>null()
contains
  Final :: Deallocate
end type
contains
  Subroutine SubDeallocate(this)
    Type(MMatrix) :: this
    if(allocated(this%tmp)) deallocate(this%tmp)
  End Subroutine
end Module Mod_MMatrix
Module LL
Type ListElement
  Type(ListElement), Pointer :: previous=>null(), next=>null()
  Class(*), Pointer :: content=>null()
End Type
end Module LL

Making tmp allocatable would for some applications require copying huge amount of data, where as not allocating memory via the pointer would require additonal variables (more code) for other applications. And since the finalizer is invoked automatically when callling Deallocate(content) the segfault is guaranteed if one is not carefull.

Cheers

0 Kudos
IanH
Honored Contributor II
270 Views

may.ka wrote:

It is for instance usefull when doing linked list where the acutal list content is stored behind an (unlimited) polymorphic pointer. Such a list struture would look like

Module Mod_MMatrix
Type :: MMatrix
  Real, Pointer :: tmp(:,:)=>null()
contains
  Final :: Deallocate
end type
contains
  Subroutine SubDeallocate(this)
    Type(MMatrix) :: this
    if(allocated(this%tmp)) deallocate(this%tmp)
  End Subroutine
end Module Mod_MMatrix
Module LL
Type ListElement
  Type(ListElement), Pointer :: previous=>null(), next=>null()
  Class(*), Pointer :: content=>null()
End Type
end Module LL

Making tmp allocatable would for some applications require copying huge amount of data, where as not allocating memory via the pointer would require additonal variables (more code) for other applications. And since the finalizer is invoked automatically when callling Deallocate(content) the segfault is guaranteed if one is not carefull.

You need to decide whether your list stores references to objects managed elsewhere, or whether the list stores references to objects that it owns, or whether the list stores the value of objects. 

If the list is storing references to objects managed elsewhere, then it shouldn't be calling DEALLOCATE(content) - that's the job of whatever thing is supposed to be doing the management.

(Allocatables can be moved quite efficiently.)

0 Kudos
jimdempseyatthecove
Honored Contributor III
270 Views

In your original post, if your type1%p can be both directly allocated and pointed to => within the same program, then it would be advisable to also include a flag to indicate if the pointer were directly allocated or not. You might be able to discern this without an explicit flag if you have a separate means to determine if the array descriptor has the target attribute. IOW when target, do not deallocate and nullify.

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor II
270 Views

may.ka wrote:

..  I can(have to) live with the responibility and had already code like the logical switch in mind. But I thought I was missing something.

However, your question was about the intent of of such code.

It is for instance usefull when doing linked list where the acutal list content is stored behind an (unlimited) polymorphic pointer. Such a list struture would look like ..

Making tmp allocatable would for some applications require copying huge amount of data, where as not allocating memory via the pointer would require additonal variables (more code) for other applications. And since the finalizer is invoked automatically when callling Deallocate(content) the segfault is guaranteed if one is not carefull.

Cheers

Sure, but you have sufficient options in terms of class design in standard Fortran to work with such linked lists.  It's unclear from your design why tmp component of MMatrix type needs to have pointer attribute nor the content component of your ListElement.  Among other things, you can also consider an abstract data type that does all the mechanics of working with a doubly linked list and a concrete implementation of such an abstract type for a matrix element can have a data component of allocatable attribute.  Memory management and avoiding leaks, etc. becomes much easier then.

0 Kudos
Reply