7

In order to traverse a linked list in Fortran, I use a pointer to the current element that is moved to the next one inside a loop. Trying to apply this inside a pure function that operates on said linked list results in an error.

Example:

module list
  implicit none

  ! Node
  type n_list
    integer               :: val
    type(n_list),pointer  :: next => NULL()
  end type

  ! Linked list
  type t_list
    type(n_list),pointer  :: head
  end type

contains

  pure function in_list( list, val ) result(res)
    implicit none
    class(t_list),intent(in)  :: list
    integer,intent(in)        :: val
    logical                   :: res
    type(n_list),pointer      :: cur

    res = .true.
    ! Traverse the list
    cur => list%head
    do while ( associated(cur) )
      if ( cur%val == val ) return 
      cur => cur%next
    enddo

    ! Not found
    res = .false.
  end function
end module

Results in

    cur => list%head
         1
Error: Bad target in pointer assignment in PURE procedure at (1)

I am aware of the rationale behind the error/warning, and that it is difficult to ensure that the arguments of the function are not changed when using pointers (Fortran 2008, ch. 12.7 "Pure procedures", esp. C1283). In this case, though, list is never changed.

Is it possible to tell the compiler (ifort and gfortran) that intent(in) is not violated?

Alexander Vogt
  • 17,879
  • 13
  • 52
  • 68
  • Yes, of course... I copied the wrong line ;-) Thanks! – Alexander Vogt Apr 16 '15 at 16:51
  • I've no idea about an answer, but if I guess "no", could you lie with an interface block? – francescalus Apr 16 '15 at 17:32
  • 1
    It appears that one can use an interface block around a non-matching external function to get a desirable effect. That's ugly and has limits, but has the advantage that you are _clearly_ doing something that you know is wrong (more so than an arcane compiler flag asking a constraint check to be ignored). – francescalus Apr 16 '15 at 17:51
  • @francescalus Could you post that as a solution? It is working better than using recursive functions (factor ~5), and shows no break-down for large lists! – Alexander Vogt Apr 16 '15 at 18:14
  • 1
    I suppose you could just delete the `pure` attribute. If you have a bang-up-to-date compiler you could even replace the pointer components of your types with allocatables of the parent type. – High Performance Mark Apr 16 '15 at 18:56
  • @HighPerformanceMark If I could, I would... Unfortunately, the calling subroutine is supposed to be pure. – Alexander Vogt Apr 16 '15 at 19:00
  • @HighPerformanceMark I the pointers were `allocatable`, how could I traverse the list in a non-recursive manner? – Alexander Vogt Apr 16 '15 at 19:10

3 Answers3

6

The relevant part of the constraint you come up against (C12831) is

In a pure subprogram any designator with a base object that is .. a dummy argument with the INTENT (IN) attribute .. shall not be used

  • ..

  • as the data-target in a pointer-assignment-stmt

The note below that constraint description motivates it

The above constraints are designed to guarantee that a pure procedure is free from side effects

What you want to say is "I guarantee that there are no side effects, we don't need the constraints for that". The constraints are sufficient but not necessary for this guarantee and you can analyse your code well.

However, a conforming processor/compiler must be able to detect breaches of constraints not just the overall goal of the constraints, so you don't just need to say "it's pure really", but also "and I don't need to be told of violations of C1283". That seems like a lot of effort for the compiler vendor to go to for very little benefit.

I guess, then, that the answer is "no": there isn't a way to compile your code. This isn't definitive, as we're really into implementation-specific areas. You asked about gfortran and ifort in particular, so a "use -nocheck c1283" refutes my "answer".

Now, if there is an option you're in the realms of "trust me" (and non-standard Fortran). So, let's go there anyway. It's just that we're going to lie. As usual, interface blocks will be our means.

module list_mod
  implicit none

  ! Node
  type n_list
    integer               :: val
    type(n_list),pointer  :: next => NULL()
  end type

  ! Linked list
  type t_list
    type(n_list),pointer  :: head
  end type

  interface
    pure logical function in_list(list, val)
      import t_list
      class(t_list), intent(in) :: list
      integer, intent(in) :: val
    end function
  end interface

end module

! Interface mismatch in the external function
function in_list(list, val) result(res)
  use list_mod, only : t_list, n_list
  implicit none
  class(t_list),intent(in)  :: list
  integer,intent(in)        :: val
  logical                   :: res
  type(n_list),pointer      :: cur

  res = .true.
  ! Traverse the list
  cur => list%head
  do while ( associated(cur) )
    if ( cur%val == val ) return 
    cur => cur%next
  enddo

  ! Not found
  res = .false.
end function

  use list_mod
  type(t_list) testlist
  type(n_list), pointer :: ptr
  integer i
  logical :: res(5) = .FALSE.

  allocate(testlist%head)
  ptr => testlist%head

  do i=1,5
    allocate(ptr%next)
    ptr => ptr%next
    ptr%val = i
  end do

  ! in_list is pure, isn't it?
  forall(i=1:5:2) res(i)=in_list(testlist,i)
  print*, res
end

This is pure nastiness and is limiting: you no longer have a module procedure; you're not standard conforming; the compiler may be clever and check interfaces (even though it needn't). If the compiler hates you as a result you have only yourself to blame.

Finally, it's all rather a lot of effort to get the procedure pure.


1 This is in Fortran 2008 corresponding to the language revision at the time of asking. In Fortran 2018 the corresponding constraint is C1594.

francescalus
  • 30,576
  • 16
  • 61
  • 96
  • 1
    The last line is a general warning: I'm sure asker is experienced enough to determine the value of the `pure` attribute but I can't understate just how evil this approach is. – francescalus Apr 16 '15 at 19:11
  • It might be evil, but it does the job ;-) In fact, I could the external function from a module procedure, so I still have that benefit. By the way: `gfortran` issues a warning (*"Warning: Interface mismatch in global procedure..."*), `ifort` doesn't notice a thing... – Alexander Vogt Apr 16 '15 at 19:21
  • Sorry to un-accept your answer, but I found a better solution using the `transfer` intrinsic... – Alexander Vogt Apr 17 '15 at 09:40
  • @HighPerformanceMark Well, better suited for my task... Not better in terms of conforming to the Standard. – Alexander Vogt Apr 17 '15 at 10:09
5

I have found a solution using recursive functions that is at least Standard conforming. It is neither elegant nor fast, and is limited be the stack depth, but it is working. I'll post it as an answer, although I hope some-one has a better solution...

module list
  implicit none

  ! Node
  type n_list
    integer               :: val
    type(n_list),pointer  :: next => NULL()
  end type

  ! Linked list
  type t_list
    type(n_list),pointer  :: head
  end type

contains

  pure function in_list( list, val ) result(res)
    implicit none
    class(t_list),intent(in)  :: list
    integer,intent(in)        :: val
    logical                   :: res

    if (  associated(list%head) ) then
      res = in_list_node( list%head, val ) 
    else
      res = .false.
    endif
  end function

  recursive pure function in_list_node( node, val ) result(res)
    implicit none
    class(n_list),intent(in)  :: node
    integer,intent(in)        :: val
    logical                   :: res

    if ( node%val == val ) then
      res = .true.
    elseif ( associated(node%next) ) then
      ! Recurse
      res = in_list_node( node%next, val ) 
    else
      res = .false.
    endif
  end function
end module

program test
  use list
  implicit none
  integer,parameter     :: MAXELEM = 100000
  integer               :: i
  type(t_list)          :: lst
  type(n_list),pointer  :: cur

  ! Fill list
  lst%head => NULL()
  allocate( lst%head )
  lst%head%val = 1

  cur => lst%head
  do i=2,MAXELEM
    allocate( cur%next )
    cur%next%val = i
    cur => cur%next
  enddo !i

  print *,'is MAXELEM/2 in list? ', in_list( lst, MAXELEM/2 )
  print *,'is MAXELEM+1 in list? ', in_list( lst, MAXELEM+1 )
end program
Alexander Vogt
  • 17,879
  • 13
  • 52
  • 68
2

OK, I found a solution using the transfer intrinsic. The main idea is to clone the list struct (without the data, I checked), and use the pointer to the first node (unchanged) as a start value. Yeah, it is a loop-hole, but both ifort and gfortran accept this without warnings.

module list_mod
  implicit none

  ! Node
  type n_list
    integer               :: val
    type(n_list),pointer  :: next => NULL()
  end type

  ! Linked list
  type t_list
    type(n_list),pointer  :: head
  end type

contains

  pure function getHead(list) result(res)
    implicit none
    class(t_list),intent(in)  :: list
    type(n_list),pointer      :: res
    type(t_list),pointer      :: listPtr

    ! Create a copy of pointer to the list struct
    allocate( listPtr )
    listPtr = transfer( list, listPtr )

    ! Set the pointer
    res => listPtr%head

    ! Free memory
    deallocate( listPtr )
  end function

  pure function in_list( list, val ) result(res)
    implicit none
    class(t_list),intent(in)  :: list
    integer,intent(in)        :: val
    logical                   :: res
    type(n_list),pointer      :: cur

    res = .true.

    ! Traverse the list
    cur => getHead(list)
    do while ( associated(cur) )
      if ( cur%val == val ) return
      cur => cur%next
    enddo

    ! Not found
    res = .false.
  end function

end module

program test
  use list_mod
  implicit none
  integer,parameter     :: MAXELEM = 10000000
  integer               :: i
  type(t_list)          :: list
  type(n_list),pointer  :: cur

  ! Fill list
  list%head => NULL()
  allocate( list%head )
  list%head%val = 1

  cur => list%head
  do i=2,MAXELEM
    allocate( cur%next )
    cur%next%val = i
    cur => cur%next
  enddo !i

  print *,'is MAXELEM/2 in list? ', in_list( list, MAXELEM/2 )
  print *,'is MAXELEM+1 in list? ', in_list( list, MAXELEM+1 )
end program
Alexander Vogt
  • 17,879
  • 13
  • 52
  • 68
  • It is indeed a circumvention of the compiler check because just copying the node is also not allowed. I would hesitate to call it a Standard conforming solution, I would consider it to be at the same level as the francescalus's solution. – Vladimir F Героям слава Apr 17 '15 at 09:50
  • @VladimirF True, but I do not need an external function with mis-matching interface and I keep everything contained in one module. Since the snippet is used for templates (arbitrary lists), the is a huge improvement. – Alexander Vogt Apr 17 '15 at 09:52
  • I see, in my lists I gave up and not only I do not use pure procedures, I also do not specify intent in some of them. – Vladimir F Героям слава Apr 17 '15 at 09:54