I’ve have to read in a list of strings which is terminated with a blank line.
Here’s a simplified version of the code:
module testmod
integer nx
character(256), allocatable :: x(:)
end module
program test
use testmod
implicit none
integer i
call readfile
print *,'nx',nx
do i=1,nx
write(*,'(A)') trim(x(i))
end do
end program
subroutine readfile
use testmod
implicit none
character(256) str
if (allocated(x)) deallocate(x)
allocate(x(0))
nx=0
do
read(50,'(A)') str
if (trim(str) == '') exit
nx=nx+1
x=[x,str]
end do
end subroutine
I created a file fort.50 as follows (blank line at the end):
line 1
line 2
line 3
This works fine on GFortran, NAG Fortran, Nvidia Fortran and the new generation of Intel Fortran (ifx).
However, all the versions of classic Intel Fortran (ifort) I’ve tried return gibberish.
Is the above code OK, or is this a compiler bug? If it is a bug, then is there a simple work-around for ifort?
subroutine readfile
use testmod
implicit none
character(256) str
character(256), allocatable :: tmp(:)
integer :: i
if (allocated(x)) deallocate(x)
allocate(x(0))
nx=0
do
read(50,'(A)') str
if (trim(str) == '') exit
nx=nx+1
allocate(tmp(nx))
do i = 1, nx-1
tmp(i) = x(i)
end do
tmp(nx) = str
call move_alloc(tmp,x)
end do
end subroutine
Was hoping to avoid that approach because x=[x,str] is just so elegant…
In the meantime, I’ve found that using a local allocatable array works:
subroutine readfile
use testmod
implicit none
character(256) str
character(256), allocatable :: y(:)
allocate(y(0))
nx=0
do
read(50,'(A)') str
if (trim(str) == '') exit
nx=nx+1
y=[y,str]
end do
if (allocated(x)) deallocate(x)
allocate(x(nx))
x(:)=y(:)
deallocate(y)
end subroutine
Indeed. My bad, i didn’t pay attention to the fact that x was an allocatable array. I should have also got it from the [ ... ] reallocation on assignment syntax.
Then forget about it, and sorry for the misleading.
Beauty is in the eyes of the beholder. To me, this is the ugliest way to read a string of unknown length. It reallocates the array and copies the previous data on every assignment, O(n**2) effort to construct a string of length n.
If your strings are long, or if this code is executed often enough to be nontrivial, then you should read the string into a linked list and then move the linked list into the string. In the simple case, it requires O(n) effort to construct the string of length n. Although this is trivial code to write in fortran, I think the language itself should include this functionality so that a programmer does not need to reinvent this wheel for this common task. Here is a short program that demonstrates how to do this for integers.
program linked_read_1
implicit none
type list_member_type
integer :: i = -1 ! value
type(list_member_type), allocatable :: prev
end type list_member_type
type(list_member_type), allocatable :: list, tmp
integer :: j, 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: '
read(*,*,iostat=istat) list%i
if ( istat < 0 ) exit
if ( list%i <= 0 ) exit
n = n + 1 ! new value.
allocate ( tmp )
call move_alloc( from=list, to=tmp%prev )
call move_alloc( from=tmp, to=list )
enddo
allocate( array(n) ) ! single allocation of the final target array.
do j = n, 1, -1 ! extract and deallocate one member at a time.
call move_alloc( from=list, to=tmp )
call move_alloc( from=tmp%prev, to=list )
array(j) = list%i
enddo
deallocate( list ) ! all done with the temp linked list.
write(*,'(*(i0,1x))') array
end program linked_read_1
I think I’ve found a better solution which is to include an explicit index range.
Thus
...
nx=nx+1
x=[x,str]
...
should be replaced with
...
x=[x(1:nx),str]
nx=nx+1
...
and the Intel compiler works with ‘-ipo’.
Incidentally, this is not the first time we’ve had to work around erroneous Intel compiler optimizations. In our code we have the oddity:
do ik=1,nkpt
do ist=1,nstsv
...
if (e > ei0) then
! transfer is a workaround for a bug in Intel Fortran versions 17 and 18
ikgap(1)=transfer(ik,ik)
end if
...
end do
end do
Instead of ikgap(1)=ik because this fails with certain Intel compiler optimizations. It’s not even a particularly complicated loop.