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