Ownership for Fortran pointers

This statement is disallowed by the language standard.

1 Like

While I agree that this seems like the most robust ideal case, I have the feeling that this seemingly simple addition, would make its development and adoption longer (not happen at all?).

My feeling remains that IF the action of allocating a pointer variable (that the language already allows) triggers an internal state (known to the processor, transparent for the user), then, the processor would be able to alert of memory freeing errors earlier at compile time.

If proposed this way, the adoption might be faster because it would not require changing declaration of variables. It might of course trigger some warnings/errors on existing code which could be deactivated with some legacy flag. Keeping on this line of thoughts, then one would be able to query if(allocated(..)) on a pointer entity. Which would close the unsymmetric and inconsistent definition of being able of allocating but not querying on the data ownership of the pointer.

I tried to muck-up the behavior here Compiler Explorer very fast… this would need some extra thought to put together limit cases, the improvements that such design should bring and the non-backward compatible behaviors that might be dangling behind the corner.

1 Like

Just a question, cannot the three alias, const_ref, const_data be additional pointer attributes, like real, pointer, alias :: x(:), something like this. Yes it will be considered very verbose but cannot this way be backward compatible?

This indeed works, but as @mEm pointed out, makes it more verbose to use. I think Fortran was designed to use the basic features it allows directly. However, @hkvzjal and I also discussed that there could be syntactic sugar where the compiler internally implements it using the struct trick above, but allows natural array notation.

1 Like

The idea is POINTER-SPEC is an optional subattribute with semantics similar to INTENT and missing declarations permitted toward backward compatibility .

So, for example, both

real, pointer :: x   !<--  A

and

real, pointer( alias ) :: y   !<--- B

will be supported.

The key difference, as I stated upthread, will be the object ‘x’ can appear in ALLOCATE and DEALLOCATE instructions, meaning the target pointed to by them can effectively become undefined. This is only as per the current Fortran standard.

Whereas a reference to y will be disallowed explicitly in ALLOCATE and DEALLOCATE instructions and so forth to guard against circumstances where the target pointed to by y can become undefined.

3 Likes

Here, you’re presupposing a certain design of an existing implementation, say based on looking under the covers at sites such as Compiler Explorer. The language and its semantics, however, needs to work with any processor in the most general manner. This is where anything that steps into implementation details becomes a no-no; reference counting, etc. get into such details. Also, you can bet a new object-type, a la a smart pointer, is really a bridge too far from a standard perspective, given how the vendors tend to view things.

@hkvzjal and all readers interested in similar use cases need to keep in mind that per the current state of Fortran language, a code design is better off envisioning this scenario as two different “classes”, and thus two derived types in Fortran:

  1. A class toward a container where the data are “remote”
  2. A class where the data are “local”

Then, note certain details:

  1. The library developer eschews type-bound procedures in the first case and imposes POINTER attribute on the “holder” of the data and its manipulation and thus requires the consumer to work with the class with remote data with POINTER attribute also.
  2. The class in the second case in any number of ways, meaning there will be flexibility.
  3. Generally, the use of “setter” procedures as SUBROUTINEs will be advisable here instead of “constructor” FUNCTIONs

This means. the overall code in Fortran, with discipline and effort by the practitioner(s), can get the job done without worrying about who owns the data, the design itself shall make that clear.

Now the complaint here might be oh-it’s-so-onerous on Fortranners, in which case the committee will likely tell the complainers to go pound sand. Note the usual refrain of standard committee type of people is the work must focus on what increases performance in Fortran and/or what leads to more processor sales, blah-blah-blah, and therefore your complaint is low to zero priority to us.

So in the meantime, an illustration of what library designers can pursue that effectively bypasses the question of whether a pointer is an “owner” of data is the silly example below:

Click to see code
module remotedatacontainer_m

   private

   type, public :: remotedatacontainer_t
      private
      real, pointer :: x(:) => null()
   contains
      final :: destructor !<-- not strictly necessary, but ok
      procedure, pass(dtv) :: formatted_data_write
      generic, public :: write(formatted) => formatted_data_write
   end type

   generic, public :: setremotecontainerdata => setdata_1 !<-- add other overloads as needed
   ! As needed, add other GENERIC methods for data manipulation - but all of them as NOT type-bound procedures

contains

   subroutine setdata_1( self, dat )
      type(remotedatacontainer_t), pointer, intent(inout) :: self
      real, pointer, intent(in) :: dat(:)
      self%x => dat
   end subroutine
    
   subroutine destructor(self)
      type(remotedatacontainer_t), intent(inout) :: self
      self%x => null()
   end subroutine

   subroutine formatted_data_write( dtv, lun, iotype, vlist, istat, imsg )

      ! Argument list
      class(remotedatacontainer_t), intent(in) :: dtv
      integer, intent(in)                      :: lun
      character(len=*), intent(in)             :: iotype
      integer, intent(in)                      :: vlist(:)
      integer, intent(out)                     :: istat
      character (len=*), intent(inout)         :: imsg

      istat = 0

      select case ( iotype )
         case ( "LISTDIRECTED" )
            ! No special consideration
            if ( associated( dtv%x ) ) then 
               write(lun, fmt=*, iostat=istat, iomsg=imsg) dtv%x
            end if
         case ( "DT" )
            ! Elided
            if ( size(vlist) == 0 ) istat = 1 
         case ( "NAMELIST" )
            ! Elided
      end select

      return

   end subroutine

end module
 
module localdatacontainer_m

   private

   type, public :: localdatacontainer_t
      private
      real, allocatable :: x(:)
   contains
      procedure, pass(dtv) :: formatted_data_write
      generic, public :: write(formatted) => formatted_data_write
   end type

   generic, public :: setlocalcontainerdata => setdata_1 !<-- add other overloads as needed
   ! As needed, add other GENERIC methods for data manipulation - but all of them as NOT type-bound procedures

contains

   subroutine setdata_1( self, siz )
      type(localdatacontainer_t), intent(inout) :: self
      integer, intent(in) :: siz
      self%x = [( 0.0, integer :: i = 1, siz )]
   end subroutine
    
   subroutine formatted_data_write( dtv, lun, iotype, vlist, istat, imsg )

      ! Argument list
      class(localdatacontainer_t), intent(in) :: dtv
      integer, intent(in)                     :: lun
      character(len=*), intent(in)            :: iotype
      integer, intent(in)                     :: vlist(:)
      integer, intent(out)                    :: istat
      character (len=*), intent(inout)        :: imsg

      istat = 0

      select case ( iotype )
         case ( "LISTDIRECTED" )
            ! No special consideration
            if ( allocated( dtv%x ) ) then 
               write(lun, fmt=*, iostat=istat, iomsg=imsg) dtv%x
            else
               write(lun, fmt=*, iostat=istat, iomsg=imsg) "Data of this container is not yet allocated."
            end if
         case ( "DT" )
            ! Elided
            if ( size(vlist) == 0 ) istat = 1 
         case ( "NAMELIST" )
            ! Elided
      end select

      return

   end subroutine

end module
 
program main
   
   use remotedatacontainer_m
   use localdatacontainer_m

   type(remotedatacontainer_t), pointer :: A
   type(localdatacontainer_t) :: B

   real, allocatable, target :: y(:)
   ! Work with the container that holds "remote" data
   y = [( real(i), integer :: i = 1,6 )]
   allocate( A )
   call setremotecontainerdata( A, y )
   print *, "Before data manipulation: A = ", A
   y(3) = y(3)**2
   print *, "After data manipulation: A = ", A
   deallocate( A )

   ! Work with the container that holds "local" data
   call setlocalcontainerdata( B, 6 )
   print *, "B = ", B

end program

Upon execution using a Fortran processor:

C:\temp>ifx /standard-semantics /free p.f
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.1.0 Build 20240308
Copyright (C) 1985-2024 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
 Before data manipulation: A =  1.000000 2.000000 3.000000
 4.000000 5.000000 6.000000
 After data manipulation: A =  1.000000 2.000000 9.000000
 4.000000 5.000000 6.000000
 B =  0.000000 0.000000 0.000000 0.000000 0.000000
 0.000000

C:\temp>

Yes, the whole situation is kinda silly but that is how things are at present.

There was a lot of things discussed in this discussion, but one should come back to the original suggestion which was about allowing allocated(p) where p is a pointer.

Note the following code is legal:

integer, pointer :: a(:), b(:)
allocate( a(10) )
b => a
deallocate( b )
end

That is, even though b that not own the memory in the first place, it can deallocate it. Hence, for consistency, if allocated() was allowed on pointers, allocated(b) should IMO return .true. between the association and the deallocation.

The point is that with Fortran pointers, the ability to deallocate is not linked to the ownership at all.

I do not have the code at hand, but I arrived more or less at similar design. I completed it with some subroutines such as move_ownership (parallel to move_alloc) to make things feel right.

I agree this would be nice extension to memory management. allocatable design causes way too many copies which kills all performance benefit of Fortran.

Also, in my experience, finalizers, especially in conjunction with assignment operations, are way too unreliable. So, as old-fashioned as it sounds, I always end up arriving at using pointers and deallocating stuff myself.

1 Like

Could you give an example of this. The purpose of allocatable in fortran is to make them MORE efficient, EASIER to use, and to make memory management MORE robust than pointers, not less. Of course, there are some algorithms that need anonymous memory, so you need pointers rather than allocatable, but that is not the kind of algorithm being discussed in this “ownership” thread.

There is one performance-related feature that I would like to see added to the language, and that is a way to convert memory from anonymous to named without a copy operation. Currently, if you have anonymous memory available through the pointer pa(:), and you have an allocatable array b(:), then the only way to move the values from one to the other is with the assignment b=pa followed by the deallocation of pa. That copy requries O(n) effort, plus the memory allocation of b(:) if necessary. The move_alloc() intrinsic could be generalized to allow the shallow copy operation move_alloc(from=pa,to=b) that would require only O(1) effort with no new memory allocation.

ALLOCATABLE state is automatically synchronised with subprogram entry/exit, POINTER is not. That idea will make ALLOCATABLE as likely to disappear under your feet as POINTER, negating the whole value of ALLOCATABLE.

You are correct that a local allocatable variable is automatically deallocated upon subroutine exit. That is a feature, not a bug. A local pointer becomes undefined upon program exit, and any anonymous memory it was associated with using an allocate() can no longer be accessed through that pointer, even if you reenter that subroutine. This could be a memory leak.

type :: heavy_type
real a(11111,22222)
end type

class(*), allocatable :: a1
class(heavy_type), allocatable :: a2

allocate(heavy_type :: a1)

! task: move memory from a1 to a2 without a copy
! problem encountered whenever you want to build
! any kind of generic container without using pointers

And the type of the algorithm is not relevant, since pointer and allocatable cannot change their “flavor” (they cannot be converted between each other, as you mentioned), you either have to stick to one or another in the entire code (unless you want to make another copy).

I do find it weird that this isn’t allowed:

select type (a1)
class is (heavy_type)
    call move_alloc(from=a1,to=a2)   ! Error: a1 is not allocatable
end select

Looks like a missing case of move allocation semantics.

The opposite direction seems allowed:

class(*), allocatable :: a1
class(heavy_type), allocatable :: a2

allocate(a2)
call move_alloc(from=a2,to=a1)  ! Compiles with gfortran, ifx, and flang

From 11.1.3.3 Other attributes of associate names

The associating entity does not have the ALLOCATABLE or POINTER attributes;

And from 11.1.11.1 Purpose and form of the SELECT TYPE construct

The associate name of a SELECT TYPE construct is the associate-name if specified; otherwise it is the name that constitutes the selector.

So your comment pointing out the error is correct. Within the body of the SELECT TYPE, a1 does not have the allocatable attribute.

Thanks for checking the fineprint. So it means that move_alloc is not symmetric when it comes to polymorphic variables: class(*) <-> class(whatever). (In other words, once inside an unlimited polymorphic variable, you can never get it out without a copy.)

Exactly. Meaning that whoever designed this feature, never had an idea to try to write a linked list or any data container to test if it even makes any sense.

I think you can do it with pointers, but yeah, this may need to be a feature proposal.