For quite a long time I’ve being thinking if there could be a way of making usage of pointer a bit safer in Fortran. They offer many advantages but can be tricky if one is not careful about memory management.
I have found very useful to define DTs with pointer components which can actually hold the data or simply point to external data and encapsulate processing procedures around the given DT. In order to have the flexibility of using the same DT as owner or pointer of the data I’ve used the following kind of constructs (oversimplified):
module test
type :: mytype
logical :: imowner = .false.
real, pointer :: x(:) => null()
contains
procedure :: clear => destructor
end type
interface mytype
module procedure :: constructor
end interface
contains
type(mytype) function constructor(sze,rbuff) result(p)
integer, intent(in) :: sze
real, intent(in), target, optional :: rbuff(:)
if(present(rbuff))then
p%x => rbuff(1:sze)
else
p%imowner = .true.
allocate(p%x(sze), source=0.0)
end if
end function
subroutine destructor(self)
class(mytype) :: self
if(self%imowner) deallocate(self%x)
self%x => null()
end subroutine
end module
program main
use test
type(mytype) :: A, B
real, allocatable :: y(:)
y = [(real(i), i =1 , 6)]
A = mytype(6,y)
print *, A%x(:)
A%x(3) = A%x(3)**2
print *, y(:)
call A%clear !> A%x is nullified
print *, y(:)
B = mytype(6)
print *, B%x(:)
call B%clear() !> B%x data is deallocated
end program
Now, the one thing that I find annoying here is that, one is allowed to allocate
the pointer but not to query if(allocated(..))
as internally the language does not know if the pointer is a simple pointer or not. Which is kind of normal, yet, the fact that one can allocate and profit from such construct, brings me to the idea that, if a Fortran pointer contained an ownership flag of some sorts, it could avoid the need for the boolean member logical :: imowner = .false.
and probably allow a safer memory management in the long run.
So, I just want to know your opinions on such (most probably extremely naive) idea of advocating for the addition of an ownership notion to Fortran pointers?