Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
28381 Discussions

Determining whether a pointer array has been explicitly allocated or is host associated with a target

avinashs
New Contributor I
1,166 Views

I have a variable that is a pointer array. In certain cases, there is a target that can be associated with the pointer. In other cases, I have to explicitly allocate it. At the end of the program, I would like to nullify or deallocate the array. Is there an elegant way to determine how the pointer array was born in Fortran 2008 apart from the brute-force (and cumbersome) approach of keeping track of what was done? This has not been possible previously and I am unable to find any recent development that allows one to do so. The pseudo-code below explains the situation.

  ! Declarations
  
  integer :: n, choice
  real, dimension(:), pointer :: p => null()
  real, dimension(:), allocatable, target :: a
  logical :: host

  ! ..........

  print *, 'Specify size of array?'
  read *, n

  print *, 'use existing target? (0 = no, 1 = yes)'
  read *, choice

  if (choice > 0) then
     allocate(a(n))
     p => a
     host = .true.
  else
     allocate(p(n))
     host = .false.
  end if

  ! ..........

  ! Clean up as a good programming practice

  ! Wish-list code using hypothetical functions "is_host_associated" and "was_explicitly_allocated"
  !
  ! if (is_host_associated(p)) then
  ! 	nullify(p)
  ! elseif (was_explicitly_allocated(p)) then
  ! 	deallocate(p)
  ! end if
  !

  ! Brute force code

  if (host) then
     if (associated(p)) nullify(p)
  else
     deallocate(p)
  end if

  if (allocated(a)) deallocate(a)

 

 

0 Kudos
17 Replies
Steve_Lionel
Honored Contributor III
1,166 Views

No, there is no elegant way to do this. You might want to consider a derived type that has the pointer and a flag.

0 Kudos
mecej4
Honored Contributor III
1,166 Views

Avinash, if your intent is to avoid memory leaks, and you do not have a well-defined need to use pointer variables, avoid pointer variables!

Even if the wished-for function is_host_associated() were available, the code section

if (is_host_associated(p)) then
     nullify(p)
...

would be limited in usefulness because, even after nullify(p) was  executed, the former target of p, would continue to exist. That might be another pointer variable, or a target. The ultimate target variable persists and continues to occupy as much memory as it did before nullify(p) was executed. Thus, the desired status functions would not really solve the memory leak problems that can be caused by the use of pointer variables.

Please clarify if you think that I have missed your point.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,166 Views

A potential hack that you can exploit is consider that

p => array or slice of array

produces a lower bound of 1

whereas

allocate(p(0:nItems))

produces an array, one larger than required, but with a lower bound of 0

Then you can test the lbound(p).

This is not bullet proof as it requires the remainder of the code to be aware that "p" may or may not contain this additional element.

do I=1,nItems
  p(I) = ...

works

  call foo(p) ! oops
  call foo(p(1,nItems)) ! works
  call foo(p(1,ubound(p)) ! works

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor II
1,166 Views

avinashs wrote:

.. Is there an elegant way to determine how the pointer array  ..

"elegant way" may be a problem, unachievable even depending on how one defines it ..

Anyways almost all aspects involving pointers are generally part of coders' responsibilities and should the code in the original post be an indication of "actual code" meaning the variable with POINTER attribute such as p has *certain defined TARGETs* such as array a, one can consider ASSOCIATED intrinsic along with the second optional dummy argument for TARGET for a somewhat better handle on the situation e.g.,

if ( associated(p, a) ) then
   ! implies "host association"
   ..

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,166 Views

FF,

The (a) problem with that is p might be pointing to something other than a.

A problem with using a container is then one needs to use p%p (since Fortran does not have an anonymous union). Here is an alternative:

module my_pointers
  real, pointer :: p(:)
  logical :: p_isAllocated = .false.
  real, pointer :: q(:)
  logical :: q_isAllocated = .false.
  ...
contains
  logical function allocate_p(n)
    integer :: n
    p_isAllocated = allocate(p(n))
    allocate_p = p_isAllocated
  end function allocate_p

  logical function deallocate_p()
    deallocate_p = associated(p)
    if(deallocate_p) then
      if(p_isAllocated) then
        p_isAllocated = .false.
        deallocate(p)
      endif
      nullify(p)
    end function deallocate_p
    ...
end module my_pointers

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor II
1,166 Views

jimdempseyatthecove wrote:

FF,

The (a) problem with that is p might be pointing to something other than a...

Jim,

Read carefully what I wrote: to the extent the variables with POINTER attribute in one's code is pointing at *known and named* targets, the coder can take responsibility to "check" them out as needed during the "clean up" process which is what is of interest to OP after all.  But now an issue with OP is the dual mode where an object such as 'p' can possibly point to a named target such as 'a' and also an anonymous target.  The language offers no intrinsic facility to distinguish between these 2 possibilities; no built-in reference counting mechanism unfortunately.

So I think the real problem here is with the language and what it has wrought starting with Fortran 90 in the form of including an ALLOCATE(p) statement that effectively allocates an *anonymous" target and associates the variable p with a POINTER attribute with it.  This can cause issues for coders with potentially disastrous consequences a la "Give 'em enough rope, and they'll hang themselves."

Fortran, given it was always going to be rather limited in the facility it was going to provide to coders in the form of pointers, might have been better off if it had not allowed ALLOCATE intrinsic with pointers and only allowed objects with POINTER attribute to *point at* named objects that have the TARGET attribute; the enhanced facilities with the ALLOCATABLE attribute may then have made it into the language sooner rather than coders having to wait all the way until Fortran 2003 (and later) to get the feature right.

Anyways an option for OP now can be to *refactor the code* and move away from POINTERs altogether.

0 Kudos
avinashs
New Contributor I
1,166 Views

Thanks for all the useful responses. As summarized by Steve, this is not directly possible and one may have to resort to other hacks to work around it. That being said, I tested the following method. If p is associated, we can attempt to deallocate it with the stat = option to see if an error is generated. If p is host associated or allocated, then the test associated(p) is always true but an attempt to deallocate it will generate an error if p is host associated. The method works and is compatible with IVF except that p is nullified automatically even though the deallocate generated an error so there does not appear a need to nullify it. The code appears below:

program main
  
  integer :: n, choice, info
  real, dimension(:), pointer :: p => null()
  real, dimension(:), allocatable, target :: a

  print *, 'Specify size of array?'
  read *, n

  print *, 'use existing target? (0 = no, 1 = yes)'
  read *, choice

  if (choice > 0) then
     allocate(a(n))
     a = 1
     p => a
  else
     allocate(p(n))
     p = 2
  end if

  if (associated(p)) then
     deallocate(p, stat = info) ! ... Generates an error if p is host associated
     if (info > 0) then
        nullify(p) ! ... but p is nullified in the deallocate statement even though an error is generated
     end if
  end if

  if (allocated(a)) deallocate(a)

end program main

 

0 Kudos
avinashs
New Contributor I
1,166 Views

mecej4 wrote:

Avinash, if your intent is to avoid memory leaks, and you do not have a well-defined need to use pointer variables, avoid pointer variables!

Even if the wished-for function is_host_associated() were available, the code section

if (is_host_associated(p)) then
     nullify(p)
...

would be limited in usefulness because, even after nullify(p) was  executed, the former target of p, would continue to exist. That might be another pointer variable, or a target. The ultimate target variable persists and continues to occupy as much as it did before nullify(p) was executed. Thus, the desired status functions would not really solve the memory leak problems that can be caused by the use of pointer variables.

Please clarify if you think that I have missed your point.

Your response is correct in that I am trying to avoid a memory leak at the very end. There was a time when pointers were the only choice with arrays that were structure members or those that were passed as unallocated arguments to a subroutine. While pointers are not necessary due to the enhancements of the scope of allocate/deallocate, this method is very important for memory saving as well in general purpose numerical methods. It would be best if I gave an example as shown below.

0 Kudos
avinashs
New Contributor I
1,166 Views

The following is an example of where pointers must be used and the information regarding the pointer (host associated or allocated) is important. I have a general purpose numerical method encapsulated as a class (my_numerical_method_definition) whose public member is the user-defined structure (my_numerical_method_variable). The numerical method requires several 1-D and 2-D arrays that are defined to be part of the type. When called from a parent program, some of these arrays may be already defined. In that case, I would want the numerical method to share the same memory. In other cases, the parent program must depend entirely on the class to define all the arrays. A code snippet that is "quasi-pseudocode" is given below along with a main program explaining its use.

module my_numerical_method_definition

    type :: my_numerical_method_variable

       integer :: n
       integer, pointer :: indx(:)
       real, pointer :: x(:), a(:), b(:), matrix(:,:)

     contains

       procedure, pass(self) :: initialize
       procedure, pass(self) :: finalize
       procedure, pass(self) :: worker_bee

    end type my_numerical_method_variable

  contains

    subroutine initialize(self, n)
      class(my_numerical_method_variable) :: self
      Me%n = n
      ! Allocate arrays if not associated with targets from a main program.
      if (.not.associated(self%indx)) allocate(self%indx(n))
      if (.not.associated(self%x)) allocate(self%x(n))
      if (.not.associated(self%a)) allocate(self%a(n))
      if (.not.associated(self%b)) allocate(self%b(n))
      if (.not.associated(self%matrix)) allocate(self%matrix(n,n))
    end subroutine initialize

    subroutine finalize(self)
      class(my_numerical_method_variable) :: self
      ! Here we need to know whether the arrays and matrices are host associated or explicitly allocated in order to avoid possible memory leaks
    end subroutine finalize

    subroutine worker_bee(self)
      class(my_numerical_method_variable) :: self
      ! Implement the numerical method
    end subroutine worker_bee

  end module my_numerical_method_definition

  program main
    use my_numerical_method_definition
    integer :: m
    real, target :: y(5), a(5,5)
    type(my_numerical_method_variable) :: Me
    ! y and a are available as targets so avoid duplicating memory
    Me%x => y
    Me%matrix => a
    ! (indx, a, b) are undefined so will be allocated when Me is initialized.
    call Me%initialize(5)
    call Me%worker_bee()
    call Me%finalize()
  end program main

 

0 Kudos
mfinnis
New Contributor II
1,166 Views

You could use allocatable arrays in your type that are allocated if your pointers are not associated and are then pointed to, so avoiding the need to allocate the pointers themselves.

0 Kudos
Steve_Lionel
Honored Contributor III
1,166 Views

I don't recommend relying on an error from deallocate to tell you whether the pointer was allocated or assigned. This could lead to data corruption.

0 Kudos
FortranFan
Honored Contributor II
1,166 Views

avinashs wrote:

.. have a general purpose numerical method encapsulated as a class (my_numerical_method_definition) .. I would want the numerical method to share the same memory. In other cases, the parent program must depend entirely on the class to define all the arrays. ..

Another option is follow the essential principle of OO which is for the "class" to truly "hold" as well as "enscapsulate" all the data.  So then if duplication of memory is to be avoided and memory is to be shared in many cases, the "caller" in those cases can use pointers to point to "data" within the class; other cases remain the same.  Then with the parameterized derived type (PDT) facility, further code simplification can be achieved:

module my_numerical_method_definition

   type :: my_numerical_method_variable(n) !<-- PDT
      integer, len :: n
      private
      integer :: indx(n)
      real :: m_x(n), a(n), b(n), m_matrix(n,n)
   contains
      private
      ! private methods operating on data of the class can go here
      procedure, pass(self), public :: worker_bee
      procedure, pass(self), public :: x => get_pointer_to_x
      procedure, pass(self), public :: matrix => get_pointer_to_matrix
   end type my_numerical_method_variable

contains

   subroutine worker_bee(self)
      class(my_numerical_method_variable(n=*)), intent(inout) :: self
      ! Implement the numerical method
      print *, "self%x = ", self%m_x
      print *, "self%matrix(1,1) = ", self%m_matrix(1,1)
   end subroutine worker_bee
   
   function get_pointer_to_x( self ) result( px )
      class(my_numerical_method_variable(n=*)), intent(in), target :: self
      real, pointer :: px(:)
      px => self%m_x
   end function
   
   function get_pointer_to_matrix( self ) result( pm )
      class(my_numerical_method_variable(n=*)), intent(in), target :: self
      real, pointer :: pm(:,:)
      pm => self%m_matrix
   end function
end module my_numerical_method_definition

program main
   use my_numerical_method_definition
   integer, parameter :: n = 5
   ! y and a are available as pointers so avoid duplicating memory
   real, pointer :: y(:), a(:,:)
   type(my_numerical_method_variable(n=n)), target :: Me
   integer :: i
   y => Me%x()
   a => Me%matrix()
   y = [( real(i), i=1,n )]
   a = 99.0
   ! (indx, a, b) are undefined so will be allocated when Me is initialized.
   call Me%worker_bee()
   y => null()
   a => null()
end program main

Upon execution with Intel Fortran,

 self%x =  1.000000 2.000000 3.000000 4.000000
 5.000000
 self%matrix(1,1) =  99.00000

 

0 Kudos
mecej4
Honored Contributor III
1,166 Views

jimdempseyatthecove wrote:

... Here is an alternative:

  ...
contains
  logical function allocate_p(n)
    integer :: n
    p_isAllocated = allocate(p(n))   ! not quite OK!
    allocate_p = p_isAllocated
  end function allocate_p
    ...
end module my_pointers

This is probably untested code, and the use of ALLOCATE as a function could cause the linker to report ALLOCATE as an undefined external symbol. To make the code work, one would have to use the ALLOCATE statement with a "STAT = <istat>" clause, and set the value of p_isAllocated based on the value of the status indicator <istat>.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,166 Views

The function name is allocate_p

Steve,

Pointers can be (undefined), NULLIFIED, => pointed to, or allocated. Assuming the case is .NOT. (undefined).

The formal way to determine if the pointer references valid data is to use ASSOCIATED. I seem to recall that newer Fortran language features now (nor sure) support ALLOCATED with pointers. What is to be said about:

if(associated(p)) then
  if(allocated(p)) then
    deallocate(p)
  else
    nullify(p)
  endif
endif

Jim Dempsey

0 Kudos
Steve_Lionel
Honored Contributor III
1,166 Views

You can't use ALLOCATED on a pointer. This is a common point of misunderstanding. ALLOCATED is for allocatables only.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,166 Views

Steve,

This is something you could bring up at the Fortran Standards committee meeting.

Given that:

Pointers can be (undefined), NULLIFIED, => pointed to, or allocated. Assuming the case is .NOT. (undefined).

Given that in the case of the pointer being that to an array, an array descriptor is constructed at both instances of => association, and allocation. Note, depending on implementation the descriptor itself may be allocated from heap, stack, or static. Additionally, for a non-pointer allocatable array, the descriptor is (implementation dependent) allocated from stack, or static (but not heap). The descriptor used to have (and for IVF still has) a flag indicating if the storage was allocated or not (iow fixed allocation). This used to be in the forth entry, 32 or 64 bits as the case may be, the second low order bit (note V19 developer guide is mis-numbering bits, starting at bit 1 not traditional bit 0). It doesn't appear that gfortran used this. If the descriptor were to be required by standards to contain this flag bit, then the code presented in #15 would resolve the issue presented by the OP. The flag bit could be contained in the msb of the element size field (or other scheme).

I am not sure what the situation for a pointer to a scalar has, iow is there a descriptor or no descriptor.

Jim Dempsey

0 Kudos
Steve_Lionel
Honored Contributor III
1,166 Views

The standard doesn't get into implementation details such as descriptors, and there would be wide objection if it did.

I think that for scalars, Intel Fortran just uses a bare address.

0 Kudos
Reply