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…)