Enforcing target attribute for actual argument in TBP calls

Dear all,

is there a way for a type bound procedure, to enforce that its caller declares the type instance as pointer (or with the target attribute) in its scope? And if not, is there any way to enforce, that no copy-in/copy-out of the instance is done when a type bound procedure is called? (I know, that compiler usually won’t do that, but is there a way warranted by the standard itself?)

Consider the following toy example for a container which takes ownership (instead of copying) of the item it stores:

module test
  implicit none

  type :: container_t
    private
    integer, allocatable :: item
  contains
    procedure :: push
    procedure :: pop
    procedure :: view
  end type container_t

contains

  subroutine push(this, item)
    class(container_t), intent(inout) :: this
    integer, allocatable, intent(inout) :: item
    call move_alloc(item, this%item)
  end subroutine push

  subroutine pop(this, item)
    class(container_t), intent(inout) :: this
    integer, allocatable, intent(out) :: item
    call move_alloc(this%item, item)
  end subroutine pop

  subroutine view(this, item)
    ! Is it WARRANTED that no copy-in/copy-out will be made, if actual argument for this
    ! is not marked as "target" in the callers scope?
    class(container_t), target, intent(in) :: this

    ! Why is this declaration not working? This would warranty that temporary copy is made.
    !class(container_t), pointer, intent(in) :: this

    integer, pointer, intent(out) :: item
    item => this%item
  end subroutine view

end module test


program test_program
  use test, only : container_t
  implicit none

  type(container_t) :: container
  integer, allocatable :: item
  integer, pointer :: item_ptr

  allocate(item, source=42)
  call container%push(item)
  call container%view(item_ptr)
  print *, "Value of item pointer:", item_ptr

end program test_program

The instance of type(container_t) in the callers scope does not have the target attribute. I’d assume, that the compiler is then at least theoretically allowed to make a temporary copy of it, and pass that to the container%view() call. (Is that correct?) In that case, the pointer, returned by the container%view() call would not be valid after the call.

In a normal subroutine, I’d just declare the dummy argument with the pointer attribute, which would force the caller to declare the actual argument as pointer or at least as a target. But for type bound procedures, the class() variable apparently can not have the pointer attribute. Why?

TLDR:, is there a way to ensure (as warranted by the standard), that the pointer returned by the container%view() call above is valid and does not point to a field in a temporary copy?

(I know, that I could have defined item in container_t as pointer, but then the caller would have to pass an allocated pointer to the push() method. For the sake of memory-leak free programming, I would like to avoid that the caller has to allocate pointers…)

1 Like

Maybe a much shorter example which demonstrates the problem/question:

module test
  implicit none

  type :: container_t
    integer :: item = -1
  contains
    procedure :: get_self_ptr
  end type container_t

contains

  subroutine get_self_ptr(this, ptr)
    ! Is it WARRANTED that no copy-in/copy-out will be made under any circumstances, if the actual
    ! argument is not declared as "pointer" or "target" in the callers scope?
    class(container_t), target, intent(in) :: this

    ! Why is this declaration not working? This would warranty that no temporary copy is made,
    ! wouldn't it?
    !class(container_t), pointer, intent(in) :: this

    type(container_t), pointer, intent(out) :: ptr

    ptr => this

  end subroutine get_self_ptr

end module test

program test_program
  use test, only : container_t
  implicit none

  type(container_t) :: inst
  type(container_t), pointer :: ptr

  inst = container_t(42)
  call inst%get_self_ptr(ptr)
  print *, "Value of item pointer:", ptr%item

end program test_program

Is the pointer ptr warranted to point to the instance inst, although latter does not have the target attribute? Is there any way “to enforce”, that the caller has to set the target attribute for the type instance?

19.5.2.5 Events that cause the association status of pointers to become undefined
1 The association status of a pointer becomes undefined when

(10) execution of an instance of a subprogram completes, the pointer is associated with a dummy argument of the procedure, and
(a) the effective argument does not have the TARGET attribute or is an array section with a vector subscript, or
(b) the dummy argument has the VALUE attribute

INST (of TEST_PROGRAM) is the effective argument in GET_SELF_PTR and does not have the TARGET attribute. Therefore, on exit from GET_SELF_PTR, PTR’s (of TEST_PROGRAM) association status is Undefined and must not be referenced.

There are Compilers that can detect such dangling pointers at runtime.

Marking INST (of TEST_PROGRAM) with the TARGET attribute makes the code conforming (and the answer 42).

1 Like

Seems like a task for the processor.

@themos Thanks. Actually, I indeed became first aware of the problem because one great compiler (and unfortunately only that one), flagged it up when all checks where turned on. Now, my question is: Is there any way to rewrite the code above, so that forgetting the target attribute becomes a compile-time error? As explained above, for usual subroutines I would add the pointer attribute to the dummy argument (instead of target), which would enforce the target (or the pointer) attribute in the callers scope. But I can not do it, because this seems not be allowed for type bound procedures. Is there any reason why it is not allowed? Is there any other “failsafe” strategy?

1 Like

I think, the compile-time check is non-trivial. The target attribute on the dummy argument does not automatically mean, that the target/pointer attribute must be set in the callers scope for the actual argument. If the pointer, pointing to the dummy argument does not leave the scope of the subroutine, things are well defined and safe. The problem only occurs, if the pointer leaves the scope of the subroutine. Checking for that at compile time may not be straightforward, I guess.

If I could set the pointer attribute for the dummy argument as in

class(container_t), pointer, intent(in) :: this

things were fail-safe again. But for some reasons, that is not allowed, and I don’t understand, why.

1 Like

The gist of this has been discussed elsewhere in the past and a de facto request for better support in the language has been made here:

Fortran is truly a multiparadigm language and it should see itself as such. Yet there are aspects in the language - object-oriented paradigm being one - that fall woefully short when it comes to authoring of modern libraries in Fortran particularly with the goals of efficient and convenient and safe consumption of such libraries. I really believe the situation mentioned in the original post here is an example of this, the issues highlighted by @aradi are all genuine concerns in professional scenarios and are among the reasons hindering the use of Fortran in many commercial environments with new codebases and the refactoring of old codes.

My suggestion will be for practitioners to make better and stronger proposals to address such issues at the Fortran proposals site.