Make a derived type with allocatable components an allocatable scalar to simplify deallocation

I think that if a derived type has allocatable components, making an instance of the derived type an allocatable scalar simplifies the deallocation of the derived type, since you can just write deallocate(dt) and the compiler will take care of deallocating the components of dt. I have subroutines that deallocate the components of a derived type, but I must update them when allocatable components are added to a type. Deallocating the entire type makes this automatic. Here is an example.

module m
implicit none
type :: data_frame
   character (len=:), allocatable :: title,row_labels(:),col_labels(:)
   real             , allocatable :: x(:,:)
end type data_frame
end module m
!
program main
use m
implicit none
type(data_frame), allocatable :: dt
logical, parameter :: manual_deallocate = .false.
allocate (dt)
! allocate components of dt here
if (manual_deallocate) then
   if (allocated(dt%title)) deallocate(dt%title)
   if (allocated(dt%row_labels)) deallocate(dt%row_labels)
   if (allocated(dt%col_labels)) deallocate(dt%col_labels)
   if (allocated(dt%x)) deallocate(dt%x)
else
   deallocate (dt)
end if
end program main

Like you say there is indeed no reason to manually deallocate any allocatable members when before deallocating the variable itself.

In terms of language design I find allocatable to be quite interesting. It is a pointer with ownership semantics enforced by the compiler. The advantage is memory allocation without the risk of memory leaks. The equivalent in C++ would be a unique_ptr which wasn’t standardised until C++11.

I’m not sure I understand what you are getting at. The compiler will take care of deallocating any allocated allocatable components of a derived type instance whenever the instance is explicitly deallocated or goes out of scope (e.g., at the end of a procedure). Normally, there should be no need for any extra subroutines that deallocate the components. If one wants to recover allocated resources of a no-longer-needed instance in the middle of a procedure, then making that instance allocatable is the way to do that as you point out. Maybe that was your sole point; the bit about having procedures to deallocate components confused me – they’re not needed (DT with pointer components is another matter).

Yes, this is a useful technique. If you want to write a subroutine to deallocate all the components, then all that is necessary is to make the dummy argument intent(out). You don’t really need any executable statements in the subroutine, just a return statement is sufficient. Before allocatable scalars were added to the language, the other workaround was to allocate an array of length 1. Deallocation of that 1-element array then triggered the deallocation of all its components.

3 Likes