Is the section of a pointer to an array a valid pointer?

Just extending on the pointer discussion in the other topic, I’d like to ask you some help on my original problem. I try to store a pointer to an array in a container, and use it later to manipulate the data it points to. The first call stores the pointer in the container, the second call uses the stored pointer. Is this a valid approach, if the actual argument for the pointer in the first call (which stores it) is a section of a pointer (ptr(:,ii))?

module test
  implicit none

  type :: pointer_wrapper
    real, pointer :: ptr(:) => null()
  end type pointer_wrapper

contains


  subroutine store_pointer(wrapper, ptr)
    type(pointer_wrapper), intent(out) :: wrapper
    real, pointer, intent(in) :: ptr(:)

    wrapper%ptr => ptr

  end subroutine store_pointer


  subroutine use_pointer(wrapper)
    type(pointer_wrapper), intent(inout) :: wrapper

    call random_number(wrapper%ptr)
    ! Bug vanishes, if next line is commented out...
    wrapper%ptr(:) = wrapper%ptr + 1.0

  end subroutine use_pointer

end module test


program testprog
  use test
  implicit none


  real, allocatable, target :: data(:,:)
  real, pointer :: ptr(:,:)

  type(pointer_wrapper) :: wrapper
  integer :: ii

  allocate(data(4, 8))
  ptr => data(:,:)
  data(:,:) = 0.0
  do ii = 1, size(data, dim=2)
    print *, "BEFORE ", ii, maxval(ptr(:,ii))
    call store_pointer(wrapper, ptr(:,ii))
    print *, "BETWEEN", ii, maxval(ptr(:,ii))
    call use_pointer(wrapper)
    print *, "AFTER  ", ii, maxval(ptr(:,ii))
  end do

end program testprog

The code can be compiled with all three compilers I have at hand. The executable does what I expect in two of the cases, but trashes the memory for one of the compilers. So I am wondering, whether it is a compiler bug, or whether the code violates the standard somehow. (Interestingly, if I turn the pointer in store_pointer to intent(inout), all three compilers generate an error, telling me, that ptr(:, ii) is not a valid pointer. So I am somewhat confused…)

I am no expert on standard but I doubt ptr(:,ii) can be considered as a pointer. It represents a section of data array. If the corresponding dummy argument is a pointer with intent(in) attribute, there is (possibly) automatic pointer targetting happening, described in MFE (2018) sec. 7.18.3. Possibly because for this to happen, the actual argument must have target attribute. The data array has it, but I am not sure whether its section referenced through a pointer does inherit the attribute. If it does, the code seems to be OK.

The only case that the actual arg may not have pointer attributre is just when the corrresponding dummy has intent in (MFE 5.7.2). That is why changing the intent to inout breaks the code.

Browsing MFE (2018) left me somewhat unconclusive. Additional to the sections you mention, I’ve found

  • 5.4.7 says: “Copy-in, copy-out is not allowed, when a dummy argument has the target attribute and is either scalar or is an assumed shaped array; and the actual argument is a target other than an array section with a vector subscript.” It describes the ŧarget attritube for the dummy argument, but I would expect, that it is also valid if the dummy argument has the pointer attribute.
  • 3.13 says: The target in a pointer assignment statement may be a subobject of a pointer target (and brings an example, where the section of an array is selected…)
    So, I’d rather tend to think, that the example above is OK, but maybe somebody with a deep knowledge of the standard can point to the relevant sections there. (I’d then report the case as bug report to the affected compiler…)

Not claiming deep knowledge of the Standard!

J3/18-007r1 15.5.2.7 Pointer dummy variables

1 The requirements in this subclause apply to actual arguments that correspond to dummy data pointers.

2 If the dummy argument does not have INTENT (IN), the actual argument shall be a pointer. Otherwise, the actual argument shall be a pointer or a valid target for the dummy pointer in a pointer assignment statement. If the actual argument is not a pointer, the dummy pointer becomes pointer associated with the actual argument.

You pass a section to an INTENT(INOUT) POINTER dummy: No go, you violate the first sentence of 2 above.

You pass a section to an INTENT(IN) POINTER dummy: Good, if the section can be a target for a pointer assignment. Adding in main

real, pointer :: proof(:)
...
proof => ptr(:,ii)
print *, "Proof succeeded", Associated(proof)

Array sections with a vector subscript are explicitly forbidden as targets in

C1025 (R1037) The expr shall be a designator that designates a variable with either the TARGET or POINTER attribute and is not an array section with a vector subscript, or it shall be a reference to a function that returns a data pointer.

and the compiler must detect this constraint violation.

There are a couple of things going on here. First, a slice of a pointer array is not itself a pointer. The slice is a subobject, and the standard specifies the cases where a subobject of something with an attribute also has that attribute; POINTER is not included.

Second, the standard permits passing a non-pointer to an INTENT(IN) dummy pointer, if the actual is a valid target for the pointer (15.5.2.7p2). In this case, the dummy becomes pointer associated with the actual argument. That’s why changing the dummy from INTENT(IN) to INTENT(INOUT) changes the behavior, since that then requires that the actual have the POINTER attribute.

In the program as given, ptr in store_pointer is pointer associated with ptr(:,ii) - this is fine. (Note that the shape of ptr(:,ii) is rank 1, matching that of the dummy.)

2 Likes

@sblionel Thanks a lot for the very clear and detailed answer!