Pointer dummy to target dummy

The code below has no chance to work, because:

  • in foobar2() the target dummy argument array a(n) has an explicit shape, therefore it is contiguous
  • in foobar1() the actual argument array a is non contiguous (as it corresponds to a(::2) from the main program), forcing the compiler to make a temporary copy when calling foobar2()
  • the pointer p in foobar2() therefore points to this temporary copy, which is deallocated on return
  • after return, the pointer p in foobar1() therefore points to garbage memory instead of pointing to a

And indeed no compiler prints the “expected” result. However, no compiler (gfortran, ifx, nvfortran, flang, lfortran) complains, even with all warnings and checkings enabled.

Question: although it has no chance to work, is this code standard-conforming (which would be weird)?

module foo

contains

    subroutine foobar1(a)
    integer, intent(inout), target :: a(:)
    integer, pointer :: p(:)
    a(:) = 0
    call foobar2(size(a),a,p)
    a(:) = [1,2]
    print*, p   ! unreasonnable expectation: 1  2
    end subroutine

    subroutine foobar2(n,a,p)
    integer, intent(in) :: n
    integer, intent(in), target :: a(n)
    integer, pointer :: p(:)
    p => a
    end subroutine

end module

program test
use foo

    integer :: a(4)
    call foobar1( a(::2) )

end

You want us to find the Standard paragraph that forbids this? The compiler that catches the most things catches this one (with -C=dangling).

Nobody “has to”…

I don’t have access to this one. What does it report?

> nagfor -C=dangling test_pointer_foo.f90
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
[NAG Fortran Compiler normal termination]
> ./a.out
Runtime Error: test_pointer_foo.f90, line 11: Reference to dangling pointer P
Target was RETURNed from procedure FOO:FOOBAR2
Program terminated by fatal error
Aborted (core dumped)
1 Like

So, the NAG compiler is doing what it is supposed to do here, with some housekeeping on the pointers.

Still, it’s really unclear to me if the code formally violates the standard of not. In “19.5.2.5 Events that cause the association status of pointers to become undefined” I cannot really find a case that corresponds to this one. And actually I cannot see how it would be described, as the target of the pointer is a temporary object that is created by the compiler, and the standard doesn’t address these temporary objects.

I think 15.5.2.5 starting at line 35 (2023 standard draft) is apropos: “f the dummy argument has the TARGET attribute and is an explicit-shape array […] and the effective argument has the TARGET attribute but is not simply contiguous […] then […] when execution of the procedure completes, the pointer association status of any pointer that is pointer associated with the dummy argument is processor dependent.”

My understanding is that “processor dependent” means invalid, but the compiler isn’t required to detect it.

2 Likes

Good find! That seems like a fairly specific carve-out to cover this situation.

Excellent, thanks! This is really an edge case in the standard.

I wish compilers would issue some warning in such a situation, because it’s very easy to mess things up and it’s not easy to immediately understand why:

  • target contiguous dummy array
  • pointer dummy that is associated to the target
    “Warning: the pointer may get undefined after return in the case of an actual argument that is not contiguous”

I read in the past on this forum a recommendation to not use a target dummy array for such situations, but rather a pointer. This eliminates the problem we are talking about in this discussion, but also the risk of forgetting the target attribute on the actual argument. The price is the need of an additional pointer association before the call. The above code would be then (this would be totally meaningless in this code, this is just for illustration):

module foo

contains

    subroutine foobar1(a)
    integer, intent(inout), target :: a(:)
    integer, pointer :: p(:), aa(:)
    a(:) = 0
    aa => a; call foobar2(size(aa),aa,p)
    a(:) = [1,2]
    print*, p   ! expectation: 1  2
    end subroutine

    subroutine foobar2(n,a,p)
    integer, intent(in) :: n
    integer, pointer :: a(:), p(:)
    p => a
    end subroutine

end module

program test
use foo

    integer :: a(4)
    call foobar1( a(::2) )

end

I still have some reservations about a pointer dummy argument being associated with a nonpointer actual argument. I understand that this is just a shortcut within the subroutine for a target attribute on the dummy array, followed by a local pointer being assigned to that target. But that shortcut still has kind of a funny overall feel to it.

As explained in the original post, the reason the original code did not work was because it was an explicit shape dummy array, declared as a(n). That declaration means it must be contiguous. If the actual argument is not contiguous, then copy-in/copy-out argument association must occur. That eventually means that the pointer assignment is to that copy rather than to the original array, which I think is what was desired.

There are probably many ways for a compiler to make all that work, but I can imagine that the foobar2() routine alone cannot tell whether the actual argument was contiguous. It only sees the copy, which is contiguous. The calling routine foobar1() cannot necessarily tell that an illegal pointer assignment occurred within foobar2(). This simple case is an exception perhaps because the compiler can see both routines at the same time, but in the general case, when only the interface of the callee is available to the caller, it could not know that.

One wonders what kind of tests could be done by foobar1() to warn the user at run time that an undefined pointer is referenced. It knows that copy-in/copy-out was done, so it knows that something fishy might occur. It could look at the stack pointers used for that temporary copy, and after return it could look at that pointer to see if it points into that part of the stack. I guess this is the kind of test that nagfor is doing to catch this error. Presumably that part of the stack has been popped by the time p is referenced in the print statement. So in this case, I think it would be possible for foobar1() to detect the illegal reference. However, in more general cases, say where the pointer is just passed back to its caller, or maybe the stack is pushed for some other reason before p is referenced, then a runtime test might return a false negative.

There is also the situation where the explicit shape dummy a(n) is associated with a contiguous actual argument. In this case, the pointer assignment points to the right actual array, but upon return, the pointer is still undefined. To the programmer, this would appear to work correctly, but it would still be processor dependent, meaning it is not defined by the standard to work as expected.

One can imagine other possible problem situations too. Suppose the dummy array is assumed shape with target and contiguous attributes (or the shortcut, with contiguous and pointer attributes). I think this would also trigger copy-in/copy-out, so the pointer assignment would not work in this case either.

So the problem all along was that explciit shape declaration. If that is eliminated, then the pointer assignment works as expected.

LLVM flang with flag -pedantic gives you a good deal of hints towards this is not going to work:

$ flang -pedantic pointer-to-dummy.F90 
./pointer-to-dummy.F90:18:5: warning: Pointer target is not a definable variable [-Wpointer-to-undefinable]
      p => a
      ^^^^^^
./pointer-to-dummy.F90:17:25: Declaration of 'p'
      integer, pointer :: p(:)
                          ^
./pointer-to-dummy.F90:18:5: because: 'a' is an INTENT(IN) dummy argument
      p => a
      ^^^^^^
./pointer-to-dummy.F90:16:36: Declaration of 'a'
      integer, intent(in), target :: a(n)
                                     ^
./pointer-to-dummy.F90:27:19: warning: Any pointer associated with TARGET dummy argument 'a=' during this call must not be used afterwards, as 'a(::2_8)' is not a target [-Wnon-target-passed-to-target]
      call foobar1( a(::2) )
1 Like

Nice! BTW, is there a way to enable all warnings in flang without using -pedantic ?

Most of these warnings are actually related to the fact that a is intent(inout) in foobar1() but only intent(in) in foobar2(). Changing the intent in foobar2() suppresses them, and we are left with:

`./pointer-to-dummy.F90:27:19: warning: Any pointer associated with TARGET dummy argument 'a=' during this call must not be used afterwards, as 'a(::2_8)' is not a target [-Wnon-target-passed-to-target]
      call foobar1( a(::2) )

But this one is related to the fact that a has not the target attribute in the main program. Although this is correct to not have the target attribute there in my opinion, I’ve put it to suppress the warning: no more warning is issued then, but the code is still wrong. So, flang does actually not catch that the pointer gets undefined upon returning from foobar2()