I’d like to use finalization to do the clean-up of allocated memory in an array of a derived type but I’m not sure how I’d get the routine referenced in the type’s FINAL statement, DESTROY_TYPE2, to be called upon deallocation of the derived type. Is there a way to achieve what I’m attempting without looping of type2 and deallocating pd_1 manually?
MODULE test
TYPE t_type1
TYPE(t_type2), DIMENSION(:), POINTER :: type2 => NULL()
END TYPE t_type1
TYPE t_type2
DOUBLE PRECISION, DIMENSION(:), POINTER :: pd_1 => NULL()
CONTAINS
FINAL :: DESTROY_TYPE2
END TYPE t_type2
CONTAINS
SUBROUTINE DESTROY_TYPE2(this)
TYPE(t_type2) :: this
WRITE(*,*) "Deallocating type2"
DEALLOCATE(this%pd_1)
END SUBROUTINE DESTROY_TYPE2
END MODULE test
PROGRAM testprog
USE test
INTEGER :: i
TYPE(t_type1), POINTER :: type1
ALLOCATE(type1)
ALLOCATE(type1%type2(3))
DO i = 1, SIZE(type1%type2)
ALLOCATE(type1%type2(i)%pd_1(2*i))
type1%type2(i)%pd_1(:) = i
END DO
DO i = 1, SIZE(type1%type2)
WRITE(*,*) type1%type2(i)%pd_1
END DO
DEALLOCATE(type1%type2)
DEALLOCATE(type1)
END PROGRAM testprog
It does work using a FINAL routine that accepts array of the type with manual looping; not sure if that’s the “correct” way of doing things, though:
MODULE test
TYPE t_type1
TYPE(t_type2), DIMENSION(:), POINTER :: type2 => NULL()
END TYPE t_type1
TYPE t_type2
DOUBLE PRECISION, DIMENSION(:), POINTER :: pd_1 => NULL()
CONTAINS
FINAL :: DESTROY_TYPE2_ARR
END TYPE t_type2
CONTAINS
SUBROUTINE DESTROY_TYPE2_ARR(this)
TYPE(t_type2), DIMENSION(:) :: this
INTEGER :: i
WRITE(*,*) "Deallocating type2 arr"
DO i = 1, SIZE(this)
CALL DESTROY_TYPE2(this(i))
END DO
END SUBROUTINE DESTROY_TYPE2_ARR
SUBROUTINE DESTROY_TYPE2(this)
TYPE(t_type2) :: this
WRITE(*,*) "Deallocating type2"
DEALLOCATE(this%pd_1)
END SUBROUTINE DESTROY_TYPE2
END MODULE test
PROGRAM testprog
USE test
INTEGER :: i
TYPE(t_type1), POINTER :: type1
ALLOCATE(type1)
ALLOCATE(type1%type2(3))
DO i = 1, SIZE(type1%type2)
ALLOCATE(type1%type2(i)%pd_1(2*i))
type1%type2(i)%pd_1(:) = i
END DO
DO i = 1, SIZE(type1%type2)
WRITE(*,*) type1%type2(i)%pd_1
END DO
DEALLOCATE(type1%type2)
DEALLOCATE(type1)
END PROGRAM testprog
Note there isnt necessarily a “correct” way of doing this, you have to think like an architectural engineer and see what works best based on different considerations: functionality, efficiency, aesthetics, etc.
An immediate option is to make the finalizer elemental.
Thanks for the hint with elemental. Unfortunately, I cannot use it in my actual case as the deallocation routines do have side effects as they modify global variables.
So I’ll use the “array of type” finalization.
Sure an “array type” finalizer can be used, note in.a general scenario an author of a finalizable type requiring a finalizer may then need to implement finalizers of rank-0, rank-1, rank-2, etc. depending on how the customers may consume said type and which can be a guessing game.
Or, there is also the option of IMPURE ELEMENTAL for a finalizer with “side effects”!
I think, it is better to add a nullify statement after DEALLOCATE(this%pd_1) in the DESTROY_TYPE2 subroutine.
So that, the status of the pointer is well defined to null().