Contiguous/strided pointer bounds issue

I am posting this here because I believe this test may be useful for other compilers as well,
as I have tracked that down from a far larger code. Live testing is available here.

It seems like pointer arrays cannot be used reliably in gfortran for array operations (even simple ones such as sum or size). I believe there are no issues with the attached code, as other compilers work well with it, but I am surprised there is no evidence of it even in the GNU bugzilla, which means pointer arrays are not very much used in the Fortran community I guess?

But maybe instead there is some problem with the code, in which case I defer to the sharp eyes and help from the community.

module classes
   implicit none
   type, public :: fixed
       integer :: data(8)
       integer(1) :: a(8)
   end type fixed

   type, public :: element
       integer :: data
       integer(1) :: a
   end type    

   type, public :: variable 
       type(element), allocatable :: n(:)
   end type variable

   type, public :: container
      type(fixed), allocatable :: f(:)
      type(variable), allocatable :: v(:)
      contains    
        procedure get_data
   end type container  

   contains

   function get_data(this,i) result(data)
       class(container), intent(inout), target :: this
       integer, intent(in) :: i
       integer, pointer :: data(:)
       if (.not.(allocated(this%f) .and. allocated(this%v))) then 
          nullify(data)
       elseif (i>0 .and. i<=size(this%f)) then 
          ! Contiguous
          data => this%f(i)%data
       elseif (i<=size(this%f)+size(this%v)) then 
          ! strided
          data => this%v(i-size(this%f))%n%data 
       else
          nullify(data) 
       endif
    end function get_data

end module        

program p
   use classes
   implicit none
   type(container), target :: c

   integer :: i,j,array_sum,loop_sum
   integer, pointer :: dd(:)
   integer, allocatable :: field(:)

   ! Allocate whole structure
   allocate(c%f(3),c%v(5))
   do i=1,3
      c%f(i)%data = 8*(i-1)+[1,2,3,4,5,6,7,8]
   end do
   do i=4,8
      allocate(c%v(i-3)%n(8))
      c%v(i-3)%n%data = 8*(i-1)+[1,2,3,4,5,6,7,8]
   end do 

   allocate(field(64),source=[(i,i=1,64)])

   array_sum = 0
   loop_sum  = 0
   do i=1,8
      dd => c%get_data(i)      
      array_sum = array_sum + sum(field(dd))
      do j=1,size(dd)
         loop_sum = loop_sum+field(dd(j))
      end do   
   end do 

   print *, 'expected =',sum(field)
   print *, 'array_sum=',array_sum
   print *, ' loop_sum=', loop_sum

   if (array_sum/=sum(field)) error stop 'array sum result is wrong'
   if ( loop_sum/=sum(field)) error stop 'loop sum result is wrong'
   stop 0

end program

1 Like

if add -g -fbacktrace -fcheck=all

At line 35 of file /app/example.f90
Fortran runtime error: Index '1' of dimension 1 of array 'this%f' below lower bound of 60129542157

Error termination. Backtrace:
#0  0x7d48a747494b in ???
#1  0x7d48a74755e9 in ???
#2  0x7d48a7475bc9 in ???
#3  0x402b73 in __classes_MOD_get_data
	at /app/example.f90:35
#4  0x40421f in p
	at /app/example.f90:70
#5  0x404bd0 in main
	at /app/example.f90:47
          data => this%f(i)%data

Yep: bounds checking triggers an error that is however not justified.
The issue seems only triggered when the stride comes from data being from a structure array, not when it is from a same array

this error for x86-64 gfortran(trunk),

for x86-64 gfortran(15.2)

 line 70 of file /app/example.f90
Fortran runtime error: Index '0' of dimension 1 of array 'field' outside of expected range (1:64)

Error termination. Backtrace:
#0  0x7c9404e0f655 in ???
#1  0x7c9404e10219 in ???
#2  0x7c9404e107a9 in ???
#3  0x403f65 in p
	at /app/example.f90:70
#4  0x4047b4 in main
	at /app/example.f90:46
1 Like

this link contains a stripped down version of the same program: the error message changes with flags, which I believe means the pointer descriptor is malformed (i.e., pointing to wrong/unallocated memory)

program pointer_array_to_struct
   implicit none

   type :: str
       integer :: data
       integer(1) :: a
   end type  

   type(str), target :: e(8)

   integer :: i,j,array_sum,loop_sum
   integer, pointer :: dd(:)
   integer, parameter :: idx(8) = [(i,i=1,8)]

   ! Set data
   e%data = idx

   dd=>e%data

   array_sum = sum(idx(dd))
   loop_sum  = 0
   do j=1,size(dd)
       loop_sum = loop_sum+idx(dd(j))
   end do 

   print *, 'expected =',sum(idx)
   print *, 'array_sum=',array_sum
   print *, ' loop_sum=', loop_sum

   if (array_sum/=sum(idx)) error stop 'array sum result is wrong'
   if ( loop_sum/=sum(idx)) error stop 'loop sum result is wrong'
   stop 0

end program

I am an infrequent user of pointers, but
am confused by “dd=>e%data”,
then " array_sum = sum(idx(dd))“,
as isn’t " e%data” an integer variable, not an array ?

I also avoid pointers, as I find contiguous arrays/vectors are essential forf efficient avx usage.

edit:
Was I confused by "e%data = idx " could be written as e(:)%data = idx ?

I modified the code example to replace dd with a non-pointer vector “jdx” to get the correct result.
This code also shows that “dd” is non-contiguous, which may show why Gfortran is failing ?

program pointer_array_to_struct
   implicit none

   type :: str
       integer :: data
       integer(1) :: a
   end type  

   type(str), target :: e(8)

   integer :: i,j,array_sum,loop_sum, jdx(8)
   integer, pointer :: dd(:)
!   integer, parameter :: idx(8) = [(i,i=1,8)]
   integer  :: idx(8) = [(i,i=1,8)]

   ! Set data
   e%data = idx

   dd=>e%data

   array_sum = sum(idx(dd))
   loop_sum  = 0
   do j=1,size(dd)
       write (*,*) loc(dd(j)), loc ( e(j)%data ), loc (idx(j))        ! ### new output
       loop_sum = loop_sum+idx(dd(j))
   end do 

   print *, 'expected =',sum(idx)
   print *, 'array_sum=',array_sum
   print *, ' loop_sum=', loop_sum

   jdx = e%data
   print *, 'jdx_sum  =', sum(idx(jdx))       ! ### new contiguous "dd"

   if (array_sum/=sum(idx)) error stop 'array sum result is wrong'
   if ( loop_sum/=sum(idx)) error stop 'loop sum result is wrong'
   stop 0

end program

I’d rather think that array indexing using a non contiguous array pointer is something that is not common, and I’m not completely surprised if nobody reported the problem yet, all the more than it’s quite easy to workaround the problem. Nonetheless it’s worth reporting, of course.

A slightly modified code below (in which I’ve added more integer components with initialized values)

program pointer_array_to_struct
   implicit none

   type :: str
       integer :: data = -999
       integer :: a = 1
       integer :: b = 2
       integer :: c = 300
       integer :: d = 400
       integer :: e = 500
   end type  

   type(str), target :: e(8)

   integer :: i,j,array_sum,loop_sum
   integer, pointer :: dd(:)
   integer, parameter :: idx(8) = [(i,i=1,8)]

   ! Set data
   e%data = idx

   dd=>e%data

   print *, size(dd), lbound(dd), ubound(dd)
   print *, "dd(:) = ", dd(:)

   print *, "sum(idx(dd)) = ", sum(idx(dd))
   
   associate (ee => e% data)
     print *, "sum(idx(ee)) = ", sum(idx(ee))
   end associate
    
   
   loop_sum  = 0
   do j=1,size(dd)
       loop_sum = loop_sum+idx(dd(j))
   end do 

   print *, 'expected =',sum(idx)
   print *, ' loop_sum=', loop_sum

end program

gives this error:

           8           1           8
dd(:) =        1       2       3       4       5       6       7       8

Program stderr

At line 27 of file /app/example.f90
Fortran runtime error: Index '300' of dimension 1 of array 'idx' outside of expected range (1:8)

so maybe the compiler assumes stride=1 (or something) erroneously when evaluating idx(dd) via vector indexing? (The same error occurs also when I use associate (ee => e% data) and evaluate idx(ee).) I wonder if this bug is also related to the issue of complex arrays (and .span thing)

FWIW, Lfortran0.5.2 gives (for the same code)

8    1    8
dd(:) =     1    1    2    300    400    500    2    1
sum(idx(dd)) =     7
sum(idx(ee)) =     36
expected =    36
loop_sum=    7

which seems also assume stride=1, but here when making an array descriptor (?) itself (while the associate seems to be working correctly). Other compilers (ifx, ifort, flang, nvfortran) give the expected results (36) in all cases.

Yes and yes, I think we’re on the right track. Consider this example where the pointer has the same 8-byte stride, either on a structure or on an integer array: the pointer-to-array version works. (ps. the integer(1) version would not change byte pattern due to padding)

program pointer_array_to_struct
   implicit none

   type :: str
       sequence
       integer :: data 
       integer :: a 
   end type  

   type(str), target :: e(8)
   integer, target :: f(16)

   integer :: i,j,array_sum,loop_sum
   integer, pointer :: dd(:),ff(:)
   integer, parameter :: idx(8) = [(i,i=1,8)]

   ! Set data
   e%data = idx
   f = [(i,0,i=1,8)]

   dd=>e%data
   ff=>f(::2) ! same byte pattern, but on an array

   print *, "sum(idx(dd)) = ", sum(idx(dd))
   print *, "sum(idx(ff)) = ", sum(idx(ff)) 
   print *, 'expected =',sum(idx)

end program

It has taken a while to identify this bug in Gfortran. It does not appear in my codes

I would rather say the opposite. Pointer arrays are often used in fortran when the use of allocatable arrays would be more efficient and more robust. The reason for this is that most other languages do not have something like allocatable arrays, which in this context can be regarded as “safe” pointer arrays, so when code is translated literally from these lesser languages into fortran, allocatables are not even considered. There is also a historical reason for this. F90 had very limited support for allocatable variables (they could not be dummy arguments, or components of derived types, and so on). This was mostly fixed in the “allocatable TR” which was published in 1995, but this TR functionality was not incorporated into f95. Compilers of that era could, and did, claim to support f95 without supporting this enhanced allocatable functionality. It was not until f2003 compilers were available, almost 15 years after f90, that programmers could use these new capabilities in a portable way.

Even now allocatable variables are limited within the language in a couple of ways. First, they cannot be initialized. Many code errors could be eliminated and many algorithms could be simplified if allocatables (scalars and arrays) could be initialized. Second, the allocatate() statements needs to be generalized to allow conditional reallocation of arrays. Now, the programmer must duplicate this repetitive task manually, and if not done correctly it leads to inefficiencies and latent code errors.

Compiler errors for pointer arrays should of course be corrected, but fortran programmers should focus more on using allocatable arrays and on enhancing their functionality within the language.

1 Like

I agree. I proposed what should be a simple modification to ALLOCATE a few years ago to add a DEALLOCATE or REALLOCATE optional argument to ALLOCATE to eliminate the requirement that you have to manually DEALLOCATE an array before you try to reallocate it using the ALLOCATE statement. Since most implementations of ALLOCATE will throw an error if you try to ALLOCATE a currently allocated array, the check for allocation status must currently be there. Basically I just want to replace

If (ALLOCATED(a)) DEALLOCATE(a)
ALLOCATE(a(ni,nj)

with

ALLOCATE(a(ni,nj), DEALLOCATE=.TRUE) (or REALLOCATE=.TRUE.)

I presume this could be extended to do what you would consider “conditional allocation”

Yes I know you can use allocation on assignment but thats one the things that I don’t trust the compiler developers to ever implement correctly without triggering an ICE or temporary arrays that can destroy performance.

1 Like

Yes, allocation on assignment does work, but you need something already to put on the rhs of the expression. If you don’t already have an array of the right type, size, and bounds, then you need to do something like

      alloc = .true.
      if ( allocated(a) ) then
         if ( (lbound(a,dim=1) .ne. low) .or. (ubound(a,dim=1) .ne. high) ) then
            deallocate(a)   ! must reallocate.
         else
            alloc = .false.   ! just keep the same allocation and values.
         endif
      endif
      if ( alloc ) allocate( a(low:high) )  ! values are undefined.

I actually have several of these for 1D, 2D, and 3D arrays and for various types. All of that logic should be folded into the allocate() statement, with an optional flag so that past behavior occurs for backwards compatibility with legacy code. And this should work also for user defined types, not just for arrays of simple intrinsic types.

There should also be a way to change the bounds for an existing allocated array without actually reallocating the memory (which is the expensive step). I think this should be general enough to reallocate a 3x4 array into a 2x6 array, and with arbitrary lower bounds.

To me this all seems like low hanging fruit. It would make the language much more flexible and easy to use without really requiring much effort by the compiler writers.

1 Like

100% in agreement. Being able to reduce your 9 lines of code to just one would be a major improvement in dynamic memory management in Fortran. Unfortunately, your example and my proposed mod above would probably just be dismissed by some (not all) committee members as “syntactic sugar”.

1 Like