Behaviour of pointer to allocatable array with SAVE attribute

Dear all,

I found the following different behavior between Fortran compilers, concerning a pointer without the SAVE attribute, after it points to an allocated array with SAVE attribute (if both have SAVE attribute, the behavior is consistent between compilers), in a subroutine which is called more than once. If I add the SAVE attribute to the pointer, the outputs are consistent (always T T after the first call).

program p
  implicit none
  call bla()
  call bla()
contains
  subroutine bla
    real,              pointer,       dimension(:,:,:) :: aa
    real, allocatable, target , save, dimension(:) :: buf
    print*,'Allocated, Associated?',allocated(buf),associated(aa)
    if(.not.allocated(buf)) then
      allocate(buf(1000))
      aa(1:10,1:10,1:10) => buf(1:1000)
      print*,'This should print only once.'; print*,''
    endif
  end subroutine bla
end
$ gfortran test.f90 && ./a.out
 Allocated, Associated? F F
 This should print only once.

 Allocated, Associated? T T
nvfortran test.f90 && ./a.out
 Allocated, Associated?  F  F
 This should print only once.

 Allocated, Associated?  T  F
ifort test.f90 && ./a.out
 Allocated, Associated? F F
 This should print only once.

 Allocated, Associated? T F

I wonder if there is a correct output according to the Standard?

Thanks!

Before you can use associated(aa) in an expression, you have to make sure that aa points to something, or has been initialized using nullify().

1 Like

Thanks! Now the program gives consistent results (T T) for all compilers.

program p
  implicit none
  call bla()
  call bla()
contains
  subroutine bla
    !*EDIT*: Note: assigning the pointer to null() also implies the save attribute
    real,              pointer,       dimension(:,:,:) :: aa => null() ! changed this line
    real, allocatable, target , save, dimension(:) :: buf
    print*,'Allocated, Associated?',allocated(buf),associated(aa)
    if(.not.allocated(buf)) then
      allocate(buf(1000))
      aa(1:10,1:10,1:10) => buf(1:1000)
      print*,'This should print only once.'; print*,''
    endif
  end subroutine bla
end

There is no such thing in Fortran, array of pointers. I understand that you refer here to
real, pointer, dimension(:,:,:) :: aa
but aa is a pointer to a rank-3 array, not an array of pointers.

2 Likes

Indeed, thanks! I edited my post accordingly.

When you initialize the pointer with null() your are giving it an implicit save attribute.
Without the save attribute the pointer is in a undefined status and the result of associated is meaningless.

1 Like

Thanks, I was actually wondering if that were the case. All clear! I edited the code with a note.

The correct solution to this depends on the behavior you desire. Do you want the pointer to remember what it points to between calls, or should it begin each invocation anew? Beware, if you give it the save attribute (which => null() does implicitly), do not point at anything that does not also have the save attribute. For example, the following will crash

program bad_idea
  implicit none
  call bar()
  call bar()
contains
  subroutine foo(bad)
    integer, intent(in), target :: bad
    integer, pointer, save :: a => null()
    logical, save :: first = .true.
    if (first) then
      a => bad
    end
    print *, bad
  end subroutine
  subroutine bar
    integer, target :: x
    x = 42
    call foo(x)
  end subroutine
end program

because when x goes out of scope, it disappears and thus a will remain pointing at something that doesn’t exist. Note that the associated intrinsic will not save you in this case either, because the pointer is associated with something, it’s just random memory. A simpler example that suffers from the same problem

program bad_idea
  implicit none
  call foo()
  call foo()
contains
  subroutine foo()
    integer, target :: bad
    integer, pointer, save :: a => null()
    logical, save :: first = .true.
    bad = 42
    if (first) then
      a => bad
    end
    print *, bad
  end subroutine
end program

Thanks!

I tested the code on my machine with recent versions of gfortran, ifort and nvfortran and in all cases the code runs fine. Also, if I substitute,
print *, bad
with
print *, a
the code prints 42 twice, suggesting that a appears to remain pointing at bad… Here’s a revised version of your second example:

program bad_idea
  implicit none
  call foo()
  call foo()
contains
  subroutine foo()
    integer, target :: bad
    integer, pointer, save :: a => null()
    logical, save :: first = .true.
    bad = 42
    if (first) then
      a => bad
      first = .not.first
    endif
    print *, a, bad, first
  end subroutine
end program

which prints

          42          42 F
          42          42 F

This is what happens when you don’t actually test your code. Here is a version of my first example that I would expect to demonstrate the problem, but testing with the handful of compilers I have seems to indicate I don’t quite understand how pointing to a dummy argument is intended to work, and possibly that ifort does it wrong.

program bad_idea
  implicit none
  call bar()
  call baz()
contains
  subroutine foo(bad)
    integer, intent(in), target :: bad
    integer, pointer, save :: a => null()
    logical, save :: first = .true.
    if (first) then
      a => bad
      first = .false.
    end if
    print *, a
  end subroutine
  subroutine bar
    integer, target :: x
    x = 42
    call foo(x)
  end subroutine
  subroutine baz
    integer, target :: y
    y = 5
    call foo(y)
  end subroutine
end program

produces

[pop-os:~/tmp] nagfor bad_pointers.f90 -o bad_pointers
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7102
[NAG Fortran Compiler normal termination]
[pop-os:~/tmp] ./bad_pointers                         
 42
 5
[pop-os:~/tmp] gfortran bad_pointers.f90 -o bad_pointers
[pop-os:~/tmp] ./bad_pointers                           
          42
           5
[pop-os:~/tmp] ifort bad_pointers.f90 -o bad_pointers 
[pop-os:~/tmp] ./bad_pointers                        
          42
          42
[pop-os:~/tmp] nvfortran bad_pointers.f90 -o bad_pointers
/usr/bin/ld: warning: /opt/nvidia/hpc_sdk/Linux_x86_64/21.1/compilers/lib/nvhpc.ld contains output sections; did you forget -T?
[pop-os:~/tmp] ./bad_pointers                            
           42
            5

The intended version of my second example also doesn’t seem to do what I expected. Again, maybe there’s some nuances that I’m not understanding.

program bad_idea
  implicit none
  call foo()
  call foo()
contains
  subroutine foo()
    integer, target :: bad
    integer, pointer, save :: a => null()
    logical, save :: first = .true.
    if (first) then
      bad = 42
      a => bad
      first = .false.
    end if
    print *, a
  end subroutine
end program
[pop-os:~/tmp] nagfor bad_pointers.f90 -o bad_pointers  
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7102
[NAG Fortran Compiler normal termination]
[pop-os:~/tmp] ./bad_pointers                         
 42
 42
[pop-os:~/tmp] gfortran bad_pointers.f90 -o bad_pointers
[pop-os:~/tmp] ./bad_pointers                           
          42
          42
[pop-os:~/tmp] ifort bad_pointers.f90 -o bad_pointers    
[pop-os:~/tmp] ./bad_pointers                           
          42
          42
[pop-os:~/tmp] nvfortran bad_pointers.f90 -o bad_pointers
/usr/bin/ld: warning: /opt/nvidia/hpc_sdk/Linux_x86_64/21.1/compilers/lib/nvhpc.ld contains output sections; did you forget -T?
[pop-os:~/tmp] ./bad_pointers                            
           42
           42

I think your results are misleading because there is nothing happening between the subsequent calls to foo(), so the memory the save-d pointer a points does not change. Consider the following slightly modified code:

program bad_idea
  implicit none
  real :: dum=0.0
  call foo()
  call bar(dum)
  call foo()
  print *,dum
contains
  subroutine foo()
    integer, target :: bad
    integer, pointer, save :: a => null()
    logical, save :: first = .true.
    if (first) then
      bad = 42
      a => bad
      first = .false.
    end if
    print *, a
  end subroutine foo
  subroutine bar(dummy)
    real, intent(inout) :: dummy
    real :: tab(100)
    call random_number(tab)
    dummy = dummy+sum(tab)
  end subroutine bar
end program bad_idea

which output, when compiled with gfortran (lines 2 and 3 somewhat vary):

          42
  1064238383
   50.3185577

Interestingly, ifort-compiled version still outputs 42 twice.

2 Likes

Thanks @everythingfunctional @msz59, this issue of consistency in the save attribute is a valuable lesson for me. You may have saved me from some possible future headaches :smiley:.

yeah, this is the kind of thing I was expecting to see. Thanks for the improvement to the example.

@pcosta, as you will know, in order to save yourself from a lot of headaches whilst working with objects of POINTER attribute so as to gain from shape remapping facilities in Fortran, you can either use object-based approaches (a la Akin circa 1990s and still very effective) or the object-oriented one. Either way, being very careful with target<-> pointer association and being disciplined with PRIVATE (and PROTECTED) attributes can pay off.

For the sake of any other readers coming anew to Fortran, arguably the 'canonical` approach with the object-based approach with Fortran can be as shown below.

module m
   private
   integer, allocatable, protected, target :: buf(:)
   integer, protected, pointer             :: aa(:,:,:) => null()
   public :: setup, do_work, clean
contains
   subroutine setup
     if ( .not. allocated(buf) ) then
        allocate(buf(8))
        aa(1:2,1:2,1:2) => buf(1:)
     end if
   end subroutine
   subroutine clean
     if ( allocated(buf) ) then
        deallocate( buf )
     end if
     aa => null()
   end subroutine
   subroutine do_work()
      ! checks elided for setup status
      buf = [( i, integer :: i = 1, size(buf) )]
      print *, "aa = ", aa 
   end subroutine 
end module
   use m
   call setup()
   call do_work()
   call clean()
end 

C:\Temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.29.30038.1
Copyright (C) Microsoft Corporation. All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\Temp>p.exe
aa = 1 2 3 4 5 6
7 8

1 Like