Ownership for Fortran pointers

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?

2 Likes

@hkvzjal, you may want to check out the implementation at

3 Likes

A difficulty would be:

integer, pointer :: a(:), b(:)

allocate( a(n) )   ! owner
b => a   ! not owner
deallocate( b )   ! authorized, but a(:) is now undefined,
                  ! although supposed to be the only owner

If such ownership metadata is enabled, I would then say that it should not be inherited through the action of pointing. Which would imply that deallocate( b ) should not be allowed, or at best, just nullify b as only a should carry the ownership of the data.

This would break some existing codes.

@hkvzjal ,

It may make sense if you elaborate why you need to use type components (and objects) with POINTER attribute in the first place and what exactly are the “many advantages” …

The Fortran allocatable concept is similar in some way to the C++ unique_ptr concept. Would it be possible (or simply desirable) to turn the Fortran pointer to something similar to the C++ shared_ptr, in a backward compatible way?

2 Likes

:thinking: this looks indeed like a promising idea!!

@FortranFan using pointers in this context give the freedom as I mentioned of using a DT for restructuring code without forcing the ownership of the data into the DT. A first case is: in some monolithic codes, back when people were frightened or simply sceptical to the use of OOP to architecture a code base, it would be common to find data structures splitted along modules in many files. I do not whish to start a debate on this… simply, reorganizing the code base with a minimal amount of OOP using pointer members enables not reclaming the property of the data which would otherwise imply massive changes to the code base, which in this manner can be done progressively! This is important in two folds: (1) test that no performance is lost in the process (typically by prefering SoA) (2) make sure that your collegues/your-future-self don’t hate you for forcing a massive refactoring when there are other priorities.

Another advantage is that it is much more simple in this manner to bind the data to C/Python with iso_c_binding, keeping a coherent architecture.

After ranting a little bit here, the DT use case is just an example. My main point remains: if one is allowed to allocate a pointer, then ideally one should be allowed to query if(allocated()) and have some few additional safeguards… that’s all

1 Like

What you are describing regarding “ownership” is pretty much what the allocatable attribute does. An allocatable entity is like a tame pointer. The allocatable entity “owns” the memory associated, and it can only be allocated and deallocated through that variable, and there can be only one allocatable entity that “owns” the memory at any time. The allocatable entity can have the target attribute, and the various pointers that are associated with the entity can have their own slices, lower bounds, etc, but the memory cannot be deallocated through any of the pointer references, only through the allocatable variable entity. The move_alloc() intrinsic is a way to transfer that “ownership” from one alloctable entity to another without an expensive copy operation – it is like a shallow copy operation with pointers.

3 Likes

Yes, the whole point is that I do not whish to “steal” the ownership of the data. If any this exactly what I want to avoid just as much as creating extra copies.

The pointer construct enables just that, but it requires tracking whether one did indeed allocate directly the pointer object or not. Which I’ve been doing just like that for some years successfully already, but I think it could be done in a much more cleaner manner if the pointer object internally had that ownership information.

@hkvzjal ,

The way the cards fell at the time.of Fortran 90 standard development back during all of 1980s (they used to call it Fortran 8X) meant the intrinsic ASSOCIATED(..) is what is left for you as a “user” to query regarding objects of POINTER attribute. It’s the poor Fortranner’s equivalent of what you might envision with ALLOCATED.

So the question is what programming tasks do you find difficult or not possible to achieve in your work with ALLOCATE statement and ASSOCIATED intrinsic?

As I showed at the beginning, I have found a way to manage what I want to do by including a boolean which indicates whether the object has the ownership or not.

Yet, I do feel like I was “forced” to hack-away my way through it… And when I have to explain it to a new colleague there is always a :face_with_raised_eyebrow: moment followed by a :open_mouth: … I do believe this could be much more robust and easily done if the language enabled knowing that the pointer is more than just a pointer, if one did indeed allocate the object. And more specifically for the memory release at the end of execution or at the end of the scope.

The associated intrinsic just lets one know if indeed the pointer is pointing somewhere, but the ownership part is missing, which as of now one has to be careful about. Or avoid allocating a pointer, but for me this would be a step backwards.

@hkvzjal ,

Hope you do realize so much of Fortran is much like that, you start to develop any modern solution for any technical computing endeavor with yourself or especially with your colleagues and you will soon realize the gaps/limitations in the Fortran language and its standard start to stare out at you as bigger and bigger until they become God-sized holes in your heart. The moments where you have to “explain it to a new colleague there is always a :face_with_raised_eyebrow: moment folllowed by a :open_mouth:” will become more and more frequent. Technically it all starts with the ridiculous “implicit none” all over the place but you may let that pass.

But there is little to nothing that can be done now: you can rack your brain and develop some ideas and propose them at GitHub - j3-fortran/fortran_proposals: Proposals for the Fortran Standard Committee and you can be as sure as death and taxes the Fortran standard committee will not even table almost all of them, all but the most trivial and the easiest to implement options will be rejected outright or ignored, even among the no-brainers no more 6 to 10 will be included in a given 5-year cycle of a Fortran standard revision. Fortran 202Y, for example, worklist was established by the current editor of the standard as if all proposals under the /DATA subgroup, which is where anything here will go, as starting with minus 100 points in terms of their value to the language. Bottom-line: the forces that want to do “the minimal” are way too strong, that is those that oppose the addition of facilities in Fortran that enable programmers to achieve better structures for data. They see all this as work with little to no reward, meaning little to no increase in sales of hardware.

All you are left with is “take it, or leave it” when it comes to Fortran. And many do leave Fortran like much of the tax-payer funded large institutions now purporting to work on energy and security for the United States.

You mention OOP upthread and that is likely part of the limitation you encounter.

Under the “take it” proposition, you may want refer to the book by Akin re: object-based approach using simply MODULEs and module entities for the data and structures around them rather than the OOP approach you hint at here with type components. That might your best bet if you continue to see “many advantages” with POINTERs in Fortran.

This is all most unfortunate but that is just how things are in the world of Fortran.

I do understand that I’m doing a proposal that might not get anywhere. Ever since joining this forum I got to read specially from you, all the complexities about the politics linked to the standard.

To be fully transparent, I’ve been working in this pattern design for more than 5/6 years. I have had the time to debug it, find many pitfalls and correct them along the way (and I’m pretty sure I’ll find more latter on). The reason for me opening this discussion with the label “Language enhancement” and not “help” is because right now, I’m quite content BUT, looking backwards, I know that there are many bugs and annoyances that could have been avoid if something closer to:

was available intrinsically in the language. So I would like to know where the technical limitations reside, and what could be possible beyond the current hack… If ever just for curiosity, if more, who knows, something could be actually doable.

@hkvzjal what does your approach allow that a regular allocatable attribute does not? Maybe it can be enhanced with the extra features if any are missing.

@certik with an allocatable member, the DT is directly the owner of the data, that’s just perfectly fine! the problem is that I also have to face situations in which the DT can not be the direct owner, as the data might be declared allocatable in modules else-where. For instance, I’m doing developments in a common library for several solvers with legacy constructs. Here, the data is scattered among several modules which contain plain allocatables. Now, I want to centralize new developments with a new architecture without introducing breaking changes. I also want to use the same developments for the solvers to expose data and kernels to Python or C.

All the previous constraints are “easily” (take easy with a grain of salt) tackled by using pointers.

With a pointer component you can either point to data that are already existing in memory, or allocate new memory. I am currently working on a code where I use the very same solution as @hkvzjal :

My code is receiving the data as multiple 2D real pointers, I cannot change that, and I have to keep these pointers alive. I am organising these data like this:

type collection
   real, pointer :: a(:,:)
   logical :: owner
   ! + other useful attributes
contains
   final :: collection_destroy
end type

type(collection), allocatable :: somedata(:)

elemental subroutine collection_destroy(this)
   type(collection) :: this
   if (associated(this% a) .and. this% owner) deallocate( this%a )
end subroutine

The pointers somedata(:)% a point to the existing data I am receiving, and consequently somedata(:)% owner == .false.

Then I process these data with some conjugate gradient algorithm, and I need :

type(collection), allocatable :: residuals(:)
type(collection), allocatable :: modelled(:)

Both have the same shapes/sizes than somedata, but the pointers are allocated, and %owner == .true.

A dataset can be tens of GB, so avoiding duplication whenever possible is desirable. Having pointer components also offers the possibility to use memory mapped files in some cases.

1 Like

@hkvzjal and any readers with some interest with type components and objects in Fortran program units of POINTER attribute:

Note I would very much like to see the Fortran language and its standard to have long introduced facilities to help with so that the practitioners did not have to “roll their own” solutions as displayed in this thread.

I entirely believe the Fortran language can be far better enhanced via different approaches driven by the Fortran Community and, perhaps, a Fortran Foundation rather than the mind-numbingly bureaucratic and “do-the-minimal” mindset, just enough to “keep the lights on”, so to write (in other parlance such as with global politics and macroeconomics, it’s also called “manage the decline”) by the ISO IEC based orgs such as WG5 and J3.

Consider this document at the WG5 site: https://wg5-fortran.org/N2151-N2200/N2165.txt

There were a couple of proposals for Fortran 2023 worklist (referred to as Fortran 202X back then) that had really good ideas connected to them and which, if implemented to their full potential, would have really helped with the topic of this thread:

  1. US19, “Protected components”
  2. US27, “Dummy pointers” (notwithstanding the extremely poor title and initial use case)

There are other ideas and enhancements also, of course, related to POINTERs which can make their use safe and efficient in Fortran.

But the core problem is that such features either fail to make it into the final standard revision (like above with Fortran 202X, both the above worklist items got dropped) or they proceed with too little, too late of a workflow, leaving the end product scarcely usable in actual practice. ENUMs from Fortran 2023 are like that.

You and @PierU et al. are right to think along the lines of “smart pointers” in C++ starting primarily with their C++14 standard revision and the practitioners of Fortran benefitting from something similar in Fortran language. But this is precisely where entirely vile no soup for you mindset kicks in depending on who brings it up; note C++ is typically a four-lettered word in Fortran standard parlance and its mention immediately triggers some. Quite a few others, who like to “suck up to power”, right away jump on those unfavored others who may mentioned C++ or a few other “disliked” languages. That is, on those who “order soup” the wrong way like, in the above skit from a popular US TV show. And the discussions go askew, they are effectively ended because these unfavored are not supposed to be asking for Fortran to become like C++ or other languages, even if that was not the point at all.

Bottom-line: quite a few with influence, whether they admit or not, in the direction of language want to do the minimal, see everything as “cost” rather than uncountable benefits, and they will state, “ha, you’ve something simple you can work with your isowner component - that seems good enough, nothing further to do here, we should be focusing on other performance features, end of discussion.”!!

The NAG compiler has a garbage collector: could it be standardized?