Does this program conform to the standard?

I am curious about the validity and conformity of the program below:

program point_expr
    implicit none

    integer, dimension(:), pointer :: ptr
    integer                        :: i

    ! This does not work: not a target or pointer, as expected
    !ptr => [(i, i = 1,10)]

    !
    ! This gives the "right" results with gfortran, but with Intel Fortran oneAPI
    ! some entries are corrupted.
    !
    call assign_ptr( ptr, [(i, i = 1,10)] )
    write(*,*) ptr
contains
subroutine assign_ptr( p, a )
    integer, pointer :: p(:)
    integer, target  :: a(:)

    p => a
end subroutine assign_ptr
end program point_expr

The background: I am looking for ways to reduce the amount of temporary memory and the copying of temporary arrays, while still using array operations. The program runs fine with gfortran and apparently does the “right” thing, but with Intel Fortran oneAPI I get rubbish:

           1           2           3           4 -2088435968         288
           7           8    13630048         223

So I wonder if the fact that it seems to work with gfortran is merely a coincidence. In neither case I get a warning or something. I suspect it is not conforming, but if it is, then I stumbled on a compiler error.

No, it is not standard conforming.

  1. You have a temporary expression, which does not exist after the call.
  2. Pointers to a target dummy arguments are invalid after the end of the routine, if the actual argument did not have the target attribute. (See among others the discussion Is pointing to a target dummy argument safe after return?)

Actually, turning your dummy argument integer, target :: a into integer, pointer, intent(in) :: a would have triggered a meaningful error message… But again, as you can see on the long discussion referenced above (read maybe the short summary in Is pointing to a target dummy argument safe after return? - #28 by aradi), it is a personal preference, whether one likes the automatic conversion of target actual arguments into pointer dummies or not.

1 Like

This instruction does not conform. The object ptr has an undefined association and the reference in the write instruction is not permitted. But the onus is on the programmer, a processor is not required to detect and report this.

I don’t know if your program conforms to the standard. But you can tell the difference between gfortran and ifort with a print statement. Consider

program point_expr
  implicit none

  integer, dimension(:), pointer :: ptr
  integer                        :: i

  call assign_ptr( ptr, [(i, i = 1,10)] )
  write(*,*) ptr
contains
subroutine assign_ptr( p, a )
  integer, pointer :: p(:)
  integer, target  :: a(:)

  p => a
  print*,p
end subroutine assign_ptr
end program point_expr

When run with gfortran,

           1           2           3           4           5           6           7           8           9          10
           1           2           3           4           5           6           7           8           9          10

When run with ifort:

           1           2           3           4           5           6
           7           8           9          10
           0           0   213786752           3   213786800           3
   213786752           3   213786992           3

In the case of gfortran, the compiler is making a buffer of memory that with a lifetime/scope of the main program. In the case of ifort, the program allocates a buffer of memory, then enters the function assign_ptr, then maybe deallocates the memory, so the pointer is now pointing to a deallocated buffer.

Anyway, the program would make more sense if you explicitly made the array that is being pointed to (see below). It makes it clear to people and the compiler that this array aa is destroyed at the end of the main function.

program point_expr
  implicit none

  integer, pointer :: ptr(:)
  integer, target, allocatable :: aa(:)
  integer :: i
  
  aa = [(i, i = 1,10)]
  call assign_ptr(ptr, aa)
  write(*,*) ptr
contains
subroutine assign_ptr( p, a )
  integer, pointer, intent(inout) :: p(:)
  integer, target, intent(in)  :: a(:)
  p => a
end subroutine assign_ptr
end program point_expr

It may look like that from the output, but it could also be that gfortran returned the memory but it has not yet been overwritten with anything else before it is illegally referenced by the dangling pointer. You might be able to tell by putting some statements in between the call and the write statements that use stack memory (which is almost certainly where that temporary array lives).

Thanks everyone, that is what I suspected. Like I said I was looking for a way to reduce the amount of memory that is being created and copied.