Fortran pointers, and aliasing

In C, the restrict keyword allows a programmer to make a promise to the compiler, saying approximately “I promise that this pointer doesn’t overlap with memory referred to by other pointers that are passed to this function”. That’s the default state in Fortran, for assumed-shape arrays, for example. But what bout when actually using pointers in Fortran? If the programmer knows that there is no aliasing, is there a way to communicate that to the compiler? Or is it unnecessary, since only targets could possibly alias, so if you pass a pointer to a function that has no target dummy arguments, there’s no chance of aliasing?

4 Likes

I don’t know the answer for aliasing between variables.

But when using pointers or assumed-shape arrays it can be handy to use the attribute contiguous which makes it easier for the compiler to enable certain optimizations:

See also:

3 Likes

A similar question occurred previously at the Intel Fortran forum:

Searching for “aliasing” in the Intel Fortran compiler documentation, does give some suggestions:

If I understood your question accurately enough, a minimum working example would be something like this:

program pointer_alias
implicit none

real, target :: a(10)
real, pointer :: b(:) => null(), c(:) => null()

a = [1,2,3,4,5,6,7,8,9,10]

b(1:5) => a(1:5)
c(1:5) => a(5:9) 

! b and c both alias element a(5), potential flow dependency
call add_in_place(b,c)
print *, b

a = [1,2,3,4,5,6,7,8,9,10]
b(1:5) => a(1:5)
c(1:5) => a(6:10) 
call add_in_place_v2(b,c)
print *, b

contains

! unsafe if executed in parallel due to write/read order of array b
subroutine add_in_place(b,c)
real, intent(inout) :: b(:)
real, intent(in) :: c(size(b))
!$omp parallel workshare
b = b + c  
!$omp end parallel workshare
end subroutine

! "restrict" version, use of do concurrent implies no data dependencies
! between elements of b and c
subroutine add_in_place_v2(b,c)
real, intent(inout) :: b(:)
real, intent(in) :: c(size(b))
integer :: i
do concurrent (i=1:size(b))
b(i) = b(i) + c(i)
end do
end subroutine

end program
2 Likes

Thanks @ivanpribec for helping to look into this. It’s ironic that this question arises at all, since restrict was introduced into C in order to enable optimizations that fortran compilers could already make! But it sounds like at the end of the day, while the compiler can work out some cases of possible aliasing and prove that there is none, that’s not the case always, and there’s no in-standard way to tell the compiler to make that assumption (other than to avoid the use of pointers).

I ran into this issue today where the compiler (ifort 16) would not vectorise a loop with array pointers because it could not guarantee the arrays weren’t pointing to overlapping memory regions. (Memory allocation is handled elsewhere, so I can’t use allocatables unfortunately :confused: )

I was able to get around this by passing the pointer arrays as dummy arguments (without the pointer or target attributes) to a subroutine after which the compiler performed the vectorisation. My understanding is that this is because aliasing dummy arguments that get defined or redefined are not standard conforming and so ifort assumes by default that this will not occur (unless -assume dummy_alias is given).

So perhaps one way to indicate this to the compiler is to pass the pointers to dummy arguments (without the pointer or target attributes). In my case, this was rather tedious because I had to unpack a structure of arrays to many subroutine arguments, so a noalias attribute could be useful here as discussed in the forum thread linked above.

1 Like

A good reason to not use pointers whenever possible…

1 Like

This has been more or less the standard way to do it in fortran since pointers were introduced in the language in f90. This usually works even with a contained procedure, so there is no need to introduce external subroutines to achieve this. However, there is now an ASSOCIATE block construct that achieves the same thing as a contained subroutine, but it is in-line and avoids the overhead of a call. So now, if it is an operation that is done in several places in the code, one could write a contained subroutine to do it, while if it is just a one-time operation, one could also use ASSOCIATE.

I also agree with the general comment above to use ALLOCATABLE rather than POINTER when possible. The fortran programmer can do many of the standard algorithms that require pointers in other languages with allocatable arrays and scalars. This includes shallow copies (with move_alloc) and tree structures (with recursive derived types).

Do you mean that the associate names shall not alias?

Thanks @RonShepard - I did not think to try an associate block! It is still quite verbose for a large number of arrays.

Yes, I completely agree with regards to preferring allocatables over pointers, but in my situation this is not possible since the memory is managed outside of my code by the calling program.

Having something like integer, pointer, noalias :: p(:) would be useful in this scenario.

I don’t know the answer for certain, but I think the associate names behave the same as dummy argument names. I guess the practical answer is to see if the compiler optimizes the expressions the way it would with no aliasing.