Is this allocate statement with pointer standard conforming?

Hi Discourse,

I’m using W10, cygwin 3.3.3, and GCC 11.2.0 .

Is the allocate statement (commented out below) standard conforming?

Thank you

subroutine  pointer_05()

  implicit none (type, external)

  integer, target  :: A_trgt
  integer, pointer :: A_ptr  => null()
  integer          :: ierr

  write(*,'(/,1x,60a)') 'pointer_05                                                 '

  write(*,*) '1 A_ptr  =', A_ptr
  write(*,*) '1 A_trgt =', A_trgt

  allocate (A_ptr, stat=ierr )
  write(*,*) ' ierr =', ierr

  write(*,*) '2 A_ptr  =', A_ptr
  write(*,*) '2 A_trgt =', A_trgt

  deallocate(A_ptr)

  write(*,*) '3 A_ptr  =', A_ptr
  write(*,*) '3 A_trgt =', A_trgt

  A_ptr  => A_trgt

  write(*,*) '4 A_ptr  =', A_ptr
  write(*,*) '4 A_trgt =', A_trgt

  allocate (A_ptr, stat=A_trgt )

  write(*,*) '5 A_ptr  =', A_ptr
  write(*,*) '5 A_trgt =', A_trgt

  A_ptr  => null()

  write(*,*) '6 A_ptr  =', A_ptr
  write(*,*) '6 A_trgt =', A_trgt

  A_ptr  => ff()

  write(*,*) '7 A_ptr  =', A_ptr
  write(*,*) '7 A_trgt =', A_trgt

!  allocate (A_ptr, stat=ff() ) ! <-- standard conforming?
  write(*,*) '8 A_ptr  =', A_ptr
  write(*,*) '8 A_trgt =', A_trgt

contains

  function ff()
    implicit none
    integer, pointer :: ff
    ff => A_trgt
  end function ff

end subroutine pointer_05

@dustydeck ,

Welcome to Fortran Discourse.

Your statement itself, allocate ( A_ptr, stat=ff() ), conforms to the current standard i.e., Fortran 2018. Note though your program as a whole does not conform - as pointed out to you upthread. But the rest of your code may not be of as much interest to you given the nature of your inquiry with the commented out line.

With the code in the commented line, you may have in mind the enhancement introduced in the Fortran standard starting with Fortran 2008 revision (circa 2010), “A pointer function reference can denote a variable in any variable definition context.”

Please note though the compiler support for this particular Fortran 2008 feature is still nowhere widespread, in my experience Intel Fortran compiler (IFOR) is about the only one that functions as to expected per the standard in most use cases involving this Fortran 2008 feature. YMMV applies with the other compilers.

Listed below is an example usage you can try with the freely downloadable IFORT compiler as part of Intel oneAPI HPC toolkit that does not carry any licensing software requirements to use - see this thread and download link.

Note this example tries the same aspect as the one in your commented out ALLOCATE statement but using an object that has an ALLOCATABLE attribute, a much safer attribute to use than the POINTER one.

Click to see example code
module m
   integer, target :: astat = -999
   character(len=2048), target :: amsg = "default string"
contains
   function pstat() result(r)
      integer, pointer :: r
      r => astat
   end function 
   function pmsg() result(r)
      character(len=:), pointer :: r
      r => amsg
   end function 
   subroutine sub( a )
      integer, allocatable, intent(inout) :: a
      allocate( a, stat=pstat(), errmsg=pmsg() )
   end subroutine
end module
   use m
   integer, allocatable :: x
   x = 42
   call sub( x )
   print *, "astat = ", astat, "; expected is processor-dependent diag code for already allocated object"
   print *, "amsg = ", trim(amsg), "; expected is a string to the effect of an object is already allocated"
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
astat = 151
; expected is processor-dependent diag code for already allocated object
amsg = allocatable array is already allocated
; expected is a string to the effect of an object is already allocated

C:\Temp>