Bug in AMD Fortran or linked list program?

Having recently downloaded the AMD compiler I tried it on the linked list program by @RonShepard,
which compiled and ran with gfortran and ifort.
Below are the program and the error message that AMD Fortran gave when I tried to compile it. Is the bug in the program or the AMD compiler?

program linked_read_1 ! by Ron Shepard 3 Oct 2023
   implicit none
   type list_member_type
      integer :: i  ! value
      type(list_member_type), allocatable :: prev
   end type list_member_type
   type(list_member_type), allocatable :: list, new
   integer :: i, n, istat
   integer, allocatable :: array(:)  ! final target array.
   allocate( list )  ! begin with an empty slot.
   n = 0  ! list length.
   do
      write(*,'(a)',advance='no')  'enter a positive integer: '
      i = -1
      read(*,*,iostat=istat) i
      if ( istat < 0 ) exit
      if ( i <= 0 ) exit
      n = n + 1  ! new value.
      list%i = i
      allocate ( new )
      call move_alloc( from=list, to=new%prev )
      call move_alloc( from=new, to=list )
   enddo
   allocate( array(n) )   ! single allocation of the final target array.
   do i = n, 1, -1        ! extract and deallocate one member at a time.
      call move_alloc( from=list, to=new )
      call move_alloc( from=new%prev, to=list )
      array(i) = list%i
   enddo
   deallocate( list )  ! all done with the temp linked list.
   write(*,'(*(i0,1x))') array
end program linked_read_1
  • /home/john/AMD/aocc-compiler-4.1.0/bin/flang -ansi -O0 -g -Wall -o linkedlist.f90of linkedlist.f90
    F90-S-0155-Derived type component must have the POINTER attribute - prev (linkedlist.f90: 5)
    0 inform, 0 warnings, 1 severes, 0 fatal for linked_read_1

No, it seems to me that the AMD compiler is simply not adhering to the latest standard. It used to be that such recursive data types required the recursive component to be a pointer, but at least since Fortran 2003 IIRC it is allowed to be allocatable instead.

Thank you @Arjen. Following your hint, I looked up old standards. Fortran 95 (p.311, C1.3) and 2003 (p.444, C1.5) required recursive components to be pointers. Fortran 2008 (p.xiii Introduction, section 2, fourth bullet point) says that recursive components could now be allocatable. AMD’s AOCC User Guide (p.10 bulletpoint 3) claims partial support of Fortran 2008, but not coarrays.

I have detested bullet points instead of numbered items in documents ever since I was in a meeting many years ago and had to hurriedly count before speaking about bullet point 9 on unnumbered page 13. I’m glad the standards and AMD gave page numbers.

I was not sure whether it was Fortran 2003 or 2008 that introduced the allocatables option. But it reduces one more need for pointers :).

derived types appeared in Fortran 2003, so allocatable components were in 2003.

Uh, no. Derived types appeared in Fortran 90. If you mean type bound procedures, they appeared in Fortran 2003. Although I think you are correct about allocatable components not officially being part of the standard before F2003, I believe there was a separate TR released around the time of F95 that defined allocatable components in derived types. I remember some compilers supporting them prior to F2003 but don’t remember which ones.

I am apparently not awake yet. I’m going to delete my comment.