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