Managing derived types with pointers

Allocatables should be used whenever possible instead of pointers, but sometimes pointers can make life easier. One of the problems with pointers is that there’s no automatic deallocation when going out of scope. When the pointer is a component of a derived type, is it enough to explicitely deallocate the pointers in a finalization routine?

type sometype
    real, pointer :: p(:)
contains
    final :: destroy
end type

subroutine destroy(this)
type(sometype) :: this
    if (<some appropriate test>) deallocate(this%p)
end subroutine

Are there some cases where the pointer will not be deallocated while an allocatable component would be (without finalization) ?

I believe there have been a couple threads about this, and the conclusion was that a final procedure may not always be called where you expect… When a final subroutine is called This is the one I was thinking of, but searching for I found that there have been others as well. I am not certain the answer to your specific situation is given within, but it’s a good place to start.

1 Like

beyond the question on whether the final procedure is called or not, a way to protect your code would be to :

type sometype
    logical :: imowner = .false.
    real, pointer :: p(:) => null()
contains
    final :: destroy
end type

subroutine destroy(this)
    type(sometype) :: this
    if (this%imowner)then
       if(associated(this%p)) deallocate(this%p)
    else
       if(associated(this%p)) nullify(this%p)
    end if
end subroutine

So you should also have a setter procedure in which you explicitly say whether you want to use you object as a container (allocate on this%p) or just as a working pointer (this%p => something_else), and set this%imowner to .true. for the former.

I’ve found this strategy to work quite well.

2 Likes

Looks like the finalization routine should be made elemental, otherwise the elements of arrays of the type are not finalized. Somehow weird, but good to know.

Yep, that’s what I was thinking at with <some appropriate test>

Another possibility to consider is the combination allocatable, target. This gives you some of the advantages of allocatables, such as automatic deallocation, while still allowing you to have multiple pointers that point to the underlying data. For example, a doubly linked list can be implemented this way, with the allocatable component allowing you to move forward through the list, and with the pointer component allowing you to move backwards through the list. Then the whole list is automatically deallocated when it goes out of scope, or when the first element is deallocated.

1 Like

I definitely need a pointer component to avoid duplicating some data.

Yes, the pointer component is there too. A doubly linked list can be done with something like

type ll_t
   integer :: k  ! value
   type(ll_t), pointer :: previous => null()
   type(ll_t), allocatable :: next
end type ll_t

The first element would be declared as

type(ll_t), allocatable, target :: list
!...
allocate ( list )

This gives the advantages of using allocatables, while still having the flexibility of pointers. If this is done in a subroutine, then upon return from the subroutine the entire list would be automatically deallocated. Or you could deallocate it manually with deallocate(list). Or you could manually deallocate some or all of the list entries from the tail to the head using the pointer component to move backwards.

1 Like

I get that, but what I mean is that my problem is not similar to linked lists and I need a pointer component at the first place (I could do partly with allocatables and partly with pointers ony to point to existing allocatables, but it would be at the price of many complications in the code)

Apologies if I revive this thread. I have a case where, for storage reasons, I need to point to a derived type component from another component, this way:

type :: container
   type(surface) :: wall ! should this be a pointer?
   type(wall_function) :: b_layer
end type

type :: wall_function
   type(surface), pointer :: wall => null() ! => container%wall
   [...]
end type

The reason wall is just referenced from inside the wall_function is that it’s a large object, duplication is not an option. How can I initialize it? target in a dummy argument is not valid, because the upstream variable is a derived type component with no target attribute (verified - it does):

subroutine init_b_layer(this,wall)
   type(wall_function) :: this
   type(surface), intent(in), target :: wall
   this%wall => wall ! illegal: target goes out of scope after subroutine
end subroutine

so, should I declare the upstream type(surface) to be a pointer instead? That would significantly complicate the derived type handling though. If there are better options, please let me know I’d be glad to learn!

Do you want the object to “just” point to the data or to hold it? You could use move_alloc to shift the pointer to your class.

1 Like

type(surface) must have attribute intent(inout).

1 Like

The actual argument must have the target attribute (or itself be a pointer). That’s just the way pointers and targets work in fortran. If the actual argument does not have the target attribute, then the dummy argument might be a copy, which would mean that the pointer to that copy would lose its target upon return.

If the only purpose of the subroutine is to do the pointer assignment, then that could just as easily be done in the calling program and the subroutine could be eliminated.

1 Like

@FedericoPerini ,

Here you may want to be keep in mind Knuth’s warning: “premature optimization is the root of all evil”. That is, you may decide something based on limited analysis influenced also by comments in an online forum of readers with no direct experience with this code base. You can come to realize later the design is suboptimal and deal with the adverse impact if this code is of top importance to you.

But if you are not that concerned (e.g., the code may be a small side project of yours with only you as the user), then you can proceed as you think with derived type components of POINTER attribute. One consideration will be to see if you can avoid a reference to such pointer components directly in an ALLOCATE statement i.e., use the pointer components as aliases only. This may need some change in your program.

Note all that an ALLOCATE statement does with pointer objects is allocate an anonymous object of TARGET attribute and set the pointer to have that target. Such objects can easily be left dangling.

Instead consider working with a named object of ALLOCATABLE attribute and alias the pointers to said object.

   type :: surface
      ..
   end type

   type :: container
      type(surface), pointer :: wall => null()
      type(wall_function) :: b_layer
   end type

   type :: wall_function
      type(surface), pointer :: wall => null()
      ..
   end type
   
   .. ! However in main program
   type(surface), allocatable, target, save :: s  !<-- all objects in main program have SAVE by default; shown here for clarity
   type(container) :: c
   ..
   c%wall => s
    
   ..  ! somewhere in compute section of the code
   ..
   type(wall_function) :: layer
   ..
   layer%wall => c%wall
1 Like

@hkvzjal, yes: type(surface) with the actual data is held upstream in the derived type tree, and I’d like to have a pointer to it to just point to the data downstream inside another derived type, just to avoid having to pass wall as a dummy argument in all routines.

@interkosmos @RonShepard Oh I see, thank you for the hint. If I set it to intent(inout) then I’m sure the actual argument is passed by reference and it’s not a copy. However, it is still going out of scope in my testing code. So now the point is I guess, how far upstream into the derived type should I go with that.

Both classes are inside the same “container” object, so the address of wall should be unchanged for as long as the container object does not go out of scope elsewhere. And even if the container is copied, the pointer should still point to the original data which is still in place? So I think I’m still missing where is the original object changing address.

@FortranFan, yep it seems like I need to eventually reconsider my strategy like you’re suggesting, it is too easy to lose control over these pointers, although I don’t like the idea of using global variables because that is not thread-safe. I can’t afford copying the actual data, so one option would be to plague all derived type subroutines of type(wall_function) with one more type(surface), intent(inout) argument