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

sequential pointer problem

uwave
Beginner
744 Views

Problem occurs with IFORT and IFX (when it doesnt give "internal compiler error")

I have a defined two types : t_sensor and t_ovioid

there is an array of t_ovoid objects.

Within each t_ovoid object there is an array of t_sensor objects.

 

IFORT & IFX both get confused when using a sequential pointer to access a field within a t_sensor object.

 

Below is sample code that reproduces the problem: (Problem line is identified by comment)

 

module t_ovoid_mod

integer, parameter :: FSOLIMIT = 7

type :: t_sensor
real(8) :: vel_nm1(3) = 0
real(8) :: vel(3) = 0
real(8) :: local_coors(3) = 0
real(8), allocatable :: fieldVars(:)
end type t_sensor


type :: t_ovoid

real(8) :: SPDist = 0
!type(t_sensor) :: sensors(7)
type(t_sensor), allocatable :: sensors(:)

type(t_sensor), pointer :: cs ! Center
type(t_sensor), pointer :: fs ! For
type(t_sensor), pointer :: as ! Aft
type(t_sensor), pointer :: ls ! left
type(t_sensor), pointer :: rs ! righr
type(t_sensor), pointer :: ts ! top
type(t_sensor), pointer :: bs ! bottom

contains

procedure :: update_vels => t_ovoid_update_vels

end type t_ovoid


interface t_ovoid
module procedure :: t_ovoid_ctor
end interface


type(t_ovoid), allocatable, target :: ovoids(:)


contains


function t_ovoid_ctor(NTecFieldVar) result(this)

integer, intent(in) :: NTecFieldVar

type(t_ovoid), target :: this

allocate(this%sensors(7))

this%cs => this%sensors(1) ! Center
this%fs => this%sensors(2) ! For
this%as => this%sensors(3) ! Aft
this%ls => this%sensors(4) ! left
this%rs => this%sensors(5) ! right
this%ts => this%sensors(6) ! top
this%bs => this%sensors(7) ! bottom

do n=1, 7
allocate(this%sensors(n)%fieldVars(NTecFieldVar))
this%sensors(n)%fieldVars = 0
enddo

end function t_ovoid_ctor


subroutine t_ovoid_update_vels(this)
class(t_ovoid), target :: this
integer :: n

do n=1, FSOLIMIT
this%sensors(n)%vel_nm1(:) = 3.0_8 ! Downshift to previous timestep
this%sensors(n)%vel(:) = 5.0_8 ! Assign current velocities
enddo

end subroutine t_ovoid_update_vels

end module t_ovoid_mod

module t_ovoid_mod

integer, parameter :: FSOLIMIT = 7

type :: t_sensor
real(8) :: vel_nm1(3) = 0
real(8) :: vel(3) = 0
real(8) :: local_coors(3) = 0
real(8), allocatable :: fieldVars(:)
end type t_sensor


type :: t_ovoid

real(8) :: SPDist = 0
!type(t_sensor) :: sensors(7)
type(t_sensor), allocatable :: sensors(:)

type(t_sensor), pointer :: cs ! Center
type(t_sensor), pointer :: fs ! For
type(t_sensor), pointer :: as ! Aft
type(t_sensor), pointer :: ls ! left
type(t_sensor), pointer :: rs ! righr
type(t_sensor), pointer :: ts ! top
type(t_sensor), pointer :: bs ! bottom

contains

procedure :: update_vels => t_ovoid_update_vels

end type t_ovoid


interface t_ovoid
module procedure :: t_ovoid_ctor
end interface


type(t_ovoid), allocatable, target :: ovoids(:)


contains


function t_ovoid_ctor(NTecFieldVar) result(this)

integer, intent(in) :: NTecFieldVar

type(t_ovoid), target :: this

allocate(this%sensors(7))

this%cs => this%sensors(1) ! Center
this%fs => this%sensors(2) ! For
this%as => this%sensors(3) ! Aft
this%ls => this%sensors(4) ! left
this%rs => this%sensors(5) ! right
this%ts => this%sensors(6) ! top
this%bs => this%sensors(7) ! bottom

do n=1, 7
allocate(this%sensors(n)%fieldVars(NTecFieldVar))
this%sensors(n)%fieldVars = 0
enddo

end function t_ovoid_ctor


subroutine t_ovoid_update_vels(this)
class(t_ovoid), target :: this
integer :: n

do n=1, FSOLIMIT
this%sensors(n)%vel_nm1(:) = 3.0_8 ! Downshift to previous timestep
this%sensors(n)%vel(:) = 5.0_8 ! Assign current velocities
enddo

end subroutine t_ovoid_update_vels

end module t_ovoid_mod

program P1

use t_ovoid_mod

implicit none

integer, parameter :: NumOvoids = 10
integer, parameter :: NumSensors = 7
integer, parameter :: NTecFieldVar = 4

type(t_ovoid), pointer :: ovoid
type(t_sensor), pointer :: cs

integer :: m, n

call AllocateOvoids(NumOvoids)

call InitializeOvoidSensors(NumOvoids, NumSensors)



ovoid => ovoids(1)
cs => ovoids(1)%sensors(1)

write(*,*) ovoid%sensors(1)%vel(3)
write(*,*) ovoid%cs%vel(3)

write(*,*) ovoid%sensors(1)%fieldVars(3)
write(*,*) cs%fieldVars(3)                                                    !<--- "singular" pointer WORKS
write(*,*) ovoid%cs%fieldVars(3)                                      !<--- "sequential" pointers DONT WORK

print *, 'Bye World'

contains

subroutine AllocateOvoids(NumSensors)
implicit none
integer :: n
integer :: NumSensors

allocate(ovoids(NumSensors))

do n=1,NumSensors
ovoids(n) = t_ovoid(NTecFieldVar) ! the t_ovoid "CTOR"
enddo

end subroutine AllocateOvoids


subroutine InitializeOvoidSensors(numOvoids, numSensors)
implicit none
integer :: numOvoids
integer :: numSensors
integer :: i,j,k

do i=1, numOvoids
call ovoids(i)%update_vels()
enddo

do i=1, numOvoids
do J = 1, NumSensors
do k = 1, NTecFieldVar
ovoids(i)%sensors(j)%fieldVars(k) = i+j+k
enddo
enddo
enddo

end subroutine InitializeOvoidSensors

end program P1



program P1

use t_ovoid_mod

implicit none

integer, parameter :: NumOvoids = 10
integer, parameter :: NumSensors = 7
integer, parameter :: NTecFieldVar = 4

type(t_ovoid), pointer :: ovoid
type(t_sensor), pointer :: cs

integer :: m, n

call AllocateOvoids(NumOvoids)

call InitializeOvoidSensors(NumOvoids, NumSensors)



ovoid => ovoids(1)
cs => ovoids(1)%sensors(1)

write(*,*) ovoid%sensors(1)%vel(3)
write(*,*) ovoid%cs%vel(3)

write(*,*) ovoid%sensors(1)%fieldVars(3)
write(*,*) cs%fieldVars(3)                                                    !<--- "singular" pointer WORKS
write(*,*) ovoid%cs%fieldVars(3)                                      !<--- "sequential" pointers DONT WORK

print *, 'Bye World'

contains

subroutine AllocateOvoids(NumSensors)
implicit none
integer :: n
integer :: NumSensors

allocate(ovoids(NumSensors))

do n=1,NumSensors
ovoids(n) = t_ovoid(NTecFieldVar) ! the t_ovoid "CTOR"
enddo

end subroutine AllocateOvoids


subroutine InitializeOvoidSensors(numOvoids, numSensors)
implicit none
integer :: numOvoids
integer :: numSensors
integer :: i,j,k

do i=1, numOvoids
call ovoids(i)%update_vels()
enddo

do i=1, numOvoids
do J = 1, NumSensors
do k = 1, NTecFieldVar
ovoids(i)%sensors(j)%fieldVars(k) = i+j+k
enddo
enddo
enddo

end subroutine InitializeOvoidSensors

end program P1

 

 

I an running the latest oneAPI fortran compiler

 

0 Kudos
12 Replies
jimdempseyatthecove
Honored Contributor III
674 Views
write(*,*) cs%fieldVars(3) !<--- "singular" pointer WORKS
! add
if(associated(cs, ovoid%cs)) print *,"associated"
print *,loc(cs), loc(ovoid%cs)
! end add
write(*,*) ovoid%cs%fieldVars(3) <--- "sequential" pointers DONT WORK

Place a break point on the DONT WORK line and report back the output.

Also, at the break point (provided the output looks as it should) can the debugger quick watch "ovoid%cs%fieldVars(3)"?

 

Jim Dempsey

0 Kudos
uwave
Beginner
655 Views

Traps on the following line:

write(*,*) ovoid%cs%fieldVars(3) !<--- "sequential" pointers DONT WORK

 

Exception thrown at xxx in P1.exe: 0xC000005:

Access violation reading location 0x000000000000010

0 Kudos
uwave
Beginner
653 Views

the line: write(*,*) cs%fieldVars(3) !<--- "singular" pointer WORKS

 

is executed and writes out the true value.

 

The debugger shows the true value also.

 

The line: ovoid%cs%fieldVars(3) 

 

Traps - the debugger says the variable is "undefined pointer/array"

 

0 Kudos
FortranFan
Honored Contributor II
616 Views

@uwave ,

A quick glance at your code suggests this is a compiler bug.  Hopefully you can get Intel Support team to check your reproducer and give you feedback.

By the way, it will be much easier for readers to look at your code if you can mark it up using the "</>" option for "insert code" when you click on "..." on the window in edit mode.

uwave
Beginner
611 Views

" get Intel Support team to check "

 

I thought they read this forum - how do I get Intel to check this?

 

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
516 Views

as a work around, instead of using a pointer (cs), which requires the pointee to have target attribute, consider using the associate statement:

associate(cs=>ovoid%cs)
write(*,*) cs%fieldVars(3)                                                    
end associate

 

Jim Dempsey

Devorah_H_Intel
Moderator
483 Views

@uwave  Thank you for the report. I was able to reproduce it internally. This issue will be fixed in future compiler releases. 

0 Kudos
Devorah_H_Intel
Moderator
200 Views

After further review, the compiler engineering determined this is not a compiler bug. 

0 Kudos
Ron_Green
Moderator
192 Views

Investigation Notes:

Here's the assignment statement that would later lead to problems accessing allocatable components inside pointer components. 

 ovoids(n) = t_ovoid(NTecFieldVar) ! the t_ovoid "CTOR"

In the assignment statement, the function result is stored into a TEMP and then stored in LHS. The TEMP is then deallocated and thus freeing any allocatable components nested inside the pointer. We cannot reallocate the allocatable components inside the pointer because pointer assignment is just a memcpy of address.

 a comment about the Fortran standard.

"In 15.6.2.2 of the F2023 standard, there is a note:

The function result is similar to any other entity (variable or procedure pointer) local to a function subprogram.
Its existence begins when execution of the function is initiated and ends when execution of the function is
terminated. However, because the final value of this entity is used subsequently in the evaluation of the
expression that invoked the function, an implementation might defer releasing the storage occupied by that
entity until after its value has been used in expression evaluation.

So we should not expect pointers to parts of a function result to be valid after returning from that function call."

 

A workaround for this issue is to do the pointer assignments after we are done with the above assignment statement OR pass the LHS to the CTOR routine by reference so that a TEMP is not used.

Ron_Green
Moderator
189 Views

You may refer to a similar issue in this post

Follow the discussion.  Ignore Barbara's note at the bottom of this thread - the bug she reported was also closed as 'not a bug' for the same reasons as this one.  But the discussion by @FortranFan gives insight into Constructors in Fortran which may prove helpful.

 

 

FortranFan
Honored Contributor II
176 Views

@uwave  and Intel Support team,

My bad I failed to follow the original post closely enough and implied there was a compiler bug.

@uwave , now that you've completed some editing of your original post and introduced code highlighting, another glance suggests to me your code does not conform and, as such, the program response is not one upon which you can rely.

In essence, the design behind the code you post hinges upon pointer association along particular lines, however the following is a simpler scenario you can review and see the response with the last "is associated" check.  The code you have posted relies upon this result being true but you can see that's not the case.

 

   type :: t
      integer, allocatable :: n
      integer, pointer :: pn => null()   
   end type
   type(t), target :: x
   call sub( x )
   print *, "Is x%n allocated? ", allocated(x%n)   
   print *, "Is x%pn associated? ", associated(x%pn)
   if ( allocated(x%n) .and. associated(x%pn) ) then
      print *, "Is x%pn associated with x%n? ", associated(x%pn, x%n)
   end if
contains
   subroutine sub( a )
      type(t), intent(inout), target :: a
      type(t), target :: l
      l%n = 42
      l%pn => l%n
      print *, "In sub: is l%pn associated with l%n? ", associated(l%pn, l%n)
      a = l
   end subroutine
end 
C:\temp>ifx /free /standard-semantics p.f
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.1.0 Build 20240308
Copyright (C) 1985-2024 Intel Corporation. All rights reserved.

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

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

C:\temp>p.exe
 In sub: is l%pn associated with l%n?  T
 Is x%n allocated?  T
 Is x%pn associated?  T
 Is x%pn associated with x%n?  F

C:\temp>gfortran -ffree-form p.f -o p.exe

C:\temp>p.exe
 In sub: is l%pn associated with l%n?  T
 Is x%n allocated?  T
 Is x%pn associated?  T
 Is x%pn associated with x%n?  F

C:\temp>

 

  • You can see with two different compilers, the result with "Is x%pn associated with x%n?" is false.

Effectively you have a problem with your `CS` component not being associated with the target you expect in your program.

jimdempseyatthecove
Honored Contributor III
151 Views

FWIW, further explanation of @FortranFan 

Inside subroutine sub

      type(t), target :: l ! l located on stack of sub
      l%n = 42             ! l%n located on stack of sub
      l%pn => l%n          ! l%pn points to l%n located on stack of sub
...
      a = l ! copies l located on stack of sub to a located in caller
            ! a%n = l%n = copy of 42 from stack of sub
            ! a%pn = l%pn = copy of pointer (not its content)
            ! (note a = l copies the pointer l%pn as-is to a%pn)
            ! which points to l%n located on stack of sub
      end subroutine sub
      ! l goes out of scope
      ! a of former caller has a%pn pointing to former stack location
      ! of l%pn within sub

IOW a%pn, though not null, is not defined (in Fortran sense).

 

Jim Dempsey

Reply