Behavior of associate construct in gfortran

I have discovered some strange behavior when using the associate construct compiled with gfortran.

The code implements an integer list supporting insertion at end, and retrieval from any position within the list. It is just an experimental substitute for the string list type being designed by @Arjen at String list new by arjenmarkus · Pull Request #311 · fortran-lang/stdlib · GitHub. Press expand to see the full code:

Expand
module integer_list_mod

  implicit none
  private

  public :: integer_list
  public :: list_index, as_int

  type :: list_index
    private
    integer :: idx
  end type

  ! This container has a fixed maximum-size of 100 elements
  type :: integer_list
    integer :: n = 0
      !! Actual size
    integer :: values(100)
      !! The underlying integer storage
    integer :: index_ref = 0
      !! Integer pointer to index array.
  contains
    procedure :: insert_int
    procedure :: insert_index
    generic :: insert => insert_int, insert_index
    procedure :: get_int
    procedure :: get_index
    generic :: get => get_int, get_index
    procedure :: end => list_end
  end type

  type(list_index), allocatable, target :: index_array(:)
  integer :: next_free = 0

contains

  subroutine insert_int(list,num)
    class(integer_list), intent(inout) :: list
    integer, intent(in) :: num

    if (list%index_ref > 0) then
      associate(pos => list%n + 1)
        if (pos > 100) then
          print *, "List full."
          return
        end if
        list%n = pos
        list%values(pos) = num
        index_array(list%index_ref)%idx = list%n
      end associate
    else

      list%index_ref = free_index_array_position()
      list%n = 1
      list%values(1) = num
      index_array(list%index_ref)%idx = list%n
    end if

  end subroutine

  integer function free_index_array_position() result(ref)

    if (allocated(index_array)) then

      if (next_free > size(index_array)) then
        resize: block
          type(list_index), allocatable :: new_index_array(:)
          allocate(new_index_array(2*size(index_array)))
          new_index_array(1:size(index_array)) = index_array
          call move_alloc(from=new_index_array,to=index_array)
        end block resize
      end if
      ref = next_free
      next_free = next_free + 1
    else
      allocate(index_array(10))
      next_free = 1
      ref = next_free
    end if

  end function

  subroutine insert_index(list,idx)
    class(integer_list), intent(inout) :: list
    type(list_index), intent(in) :: idx

    call insert_int(list,idx%idx)
  end subroutine

 integer function get_int(list,i)
    class(integer_list), intent(in) :: list
    integer, intent(in) :: i

    get_int = list%values(i)
  end function

 integer function get_index(list,idx)
    class(integer_list), intent(in) :: list
    type(list_index), intent(in) :: idx

    get_index = get_int(list,idx%idx)
  end function

  function list_end(list) result(index_ptr)
    class(integer_list), intent(inout) :: list
    type(list_index), pointer :: index_ptr

    if (list%index_ref == 0) then
      list%index_ref = free_index_array_position()
    end if

    index_ptr => index_array(list%index_ref)
  end function

  pure integer function as_int(self)
    type(list_index), intent(in) :: self
    as_int = self%idx
  end function

end module

The main thing I was interested in was using the associate construct to retrieve a pointer to an index object, which could be used to access the last value in the list:

program test_integer_list
  
  use integer_list_mod
  implicit none

  type(integer_list) :: ilist
  integer :: i

  associate(end => ilist%end())

    call ilist%insert(1)
    call ilist%insert(2)
    call ilist%insert(3)

    print '(A,I0)', "Last element:         ", ilist%get(end) ! prints "3"

    call ilist%insert(4)

    print '(A,I0)', "Last element (index): ", ilist%get(end)
    print '(A,I0)', "Last element (int):   ", ilist%get(as_int(end))
    print '(A,I0)', "End index: ", as_int(end)

    do i = 1, as_int(end)
      call ilist%insert(i+4)
    end do

  print '(A,*(I0,2X))', "Full list: ", ilist%values(1:as_int(end))

  end associate

  ! More dangerous way of accesing end index
  block
    type(list_index), pointer :: end => null()
    end => ilist%end()
    do i = 1, as_int(end)
      print *, ilist%get(i)
    end do
  end block

end program

With ifort I get the following output in agreement with my expectations:

~/fortran$ ifort -warn all integer_list_mod.f90 test_integer_list.f90 
~/fortran$ ./a.out
Last element:         3
Last element (index): 4
Last element (int):   4
End index: 4
Full list: 1  2  3  4  5  6  7  8
           1
           2
           3
           4
           5
           6
           7
           8

However, with gfortran (v 10.1.0) I get

~/fortran$ gfortran -Wall integer_list_mod.f90 test_integer_list.f90 
~/fortran$ ./a.out
Last element:         3
Last element (index): 4
Last element (int):   4
End index: 0
Full list: 
           1
           2
           3
           4

Interestingly, the as_int(end) appears to be evaluated correctly when used in the call to get. When used locally within the scope of the main program scope the value is frozen to the initial value of zero and the do insertion loop is never executed.

Which compiler is correct?

1 Like

The type-bound end() method is supposed to return a pointer:

  function list_end(list) result(index_ptr)
    class(integer_list), intent(inout) :: list
    type(list_index), pointer :: index_ptr

    if (list%index_ref == 0) then
      list%index_ref = free_index_array_position()
    end if

    index_ptr => index_array(list%index_ref)
  end function

I noticed without the associate construct, and using an explicit pointer object instead, gfortran also appears to work correctly. However one pitfall of this approach is that both compilers allow either form of assignment:

type(integer_list) :: ilist
type(list_index), pointer :: end => null()
end = ilist%end()
! or
end => ilist%end()

when only the second does what is expected (the first one segfaults). In this situation gfortran at least raises a warning: Warning: POINTER-valued function appears on right-hand side of assignment at (1) [-Wsurprising]

If the associate construct were to work correctly, the list_index type could be made a private type of the module.

As you might expect, I reckon Intel Fortran is the correct one; a while ago, I had filed a few bug reports with Intel support involving ASSOCIATE and selectors being functions returning pointers that were later fixed by Intel. By the way, there might open GCC Bugzilla incident(s) toward this.

You can try the following MWE:

module m
   type :: t
      private
      integer :: n
   contains
      procedure :: get_n => get_ptr_n 
   end type
   character(len=*), parameter :: fmth = "(g0,1x,z0)"
contains
   function get_ptr_n( this ) result(ptr_n)
      class(t), intent(in), target :: this
      integer, pointer :: ptr_n
      print fmth, "address of this%n (hex): ", loc(this%n)
      ptr_n => this%n
   end function 
end module
   use m
   type(t), target :: foo
   associate ( n => foo%get_n() )
      print fmth, "address of n inside ASSOCIATE (hex): ", loc(n)
   end associate
end

Program behavior showing the issue with gfortran:

C:\Temp>ifort a.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.1.2 Build 20201208_000000
Copyright (C) 1985-2020 Intel Corporation. All rights reserved.

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

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

C:\Temp>a.exe
address of this%n (hex): 7FF78AE1C820
address of n inside ASSOCIATE (hex): 7FF78AE1C820

C:\Temp>gfortran a.f90 -o gcc-a.exe

C:\Temp>gcc-a.exe
address of this%n (hex): 87FDEC
address of n inside ASSOCIATE (hex): 87FDE8

C:\Temp>

1 Like

That makes sense. I will still refrain from using functions returning pointers.