I have long wondered how to read lines from a file in Fortran. The obvious
character (len=1000) :: text
! connect file to unit iu
read (iu,"(a)") text
is often good enough but truncates lines that are longer than 1000 characters, and you don’t know
if trailing blanks in text
are actually in the file. Using a code by Jacob Williams to read a file into an allocatable string and then searching the string for newline characters, it is possible to recover the lines of a file. Here is the program read_file.f90:
module read_mod
implicit none
contains
function pos_char(str,char) result(ipos)
character (len=*), intent(in) :: str
character (len=*), intent(in) :: char ! should have len = 1
integer , allocatable :: ipos(:)
integer :: i,nlen,nfound
nlen = len(str)
nfound = 0
allocate (ipos(nlen),source=0)
ipos = 0
do i=1,nlen
if (str(i:i) == char) then
nfound = nfound + 1
ipos(nfound) = i
end if
end do
ipos = pack(ipos,ipos>0)
end function pos_char
!
subroutine read_file(filename, str)
! slightly modified from code by Jacob Williams at
! https://community.intel.com/t5/Intel-Fortran-Compiler/Text-file-to-allocatable-string/td-p/1033082
character(len=*) , intent(in) :: filename
character(len=:), allocatable, intent(out) :: str
! local variables:
integer :: iunit,istat,filesize
character (len=1) :: c
open (newunit=iunit,file=filename,status="old",action="read", &
form="unformatted",access="stream",iostat=istat)
if (istat==0) then
! how many characters are in the file:
inquire(file=filename, size=filesize)
if (filesize>0) then
! read the file all at once:
allocate (character(len=filesize) :: str)
read(iunit,pos=1,iostat=istat) str
if (istat==0) then
! make sure it was all read by trying to read more:
read (iunit,pos=filesize+1,iostat=istat) c
if (.not. IS_IOSTAT_END(istat)) &
print*,"Error: file was not completely read."
else
print*,"Error reading file."
end if
close (iunit, iostat=istat)
else
print*,"Error getting file size."
end if
else
print*,"Error opening file."
end if
end subroutine read_file
end module read_mod
!
program read_file_into_string
use read_mod, only: pos_char, read_file
character (len=:), allocatable :: text
integer :: i1,i2,ipos
integer , allocatable :: ipos_new(:)
integer , parameter :: max_lines_print = 3
call read_file("read_file.f90",text)
print*,"len(text) =",len(text)
ipos_new = pos_char(text,new_line(" "))
print*,"#new_line =",size(ipos_new)
print "(/,'first few lines with length:')"
i1 = 1
do i=1,min(max_lines_print,size(ipos_new))
i2 = ipos_new(i)
print "(i4,1x,a)", i2-i1+1,"'" // text(i1:i2-1) // "'"
i1 = i2 + 1
end do
end program read_file_into_string
output:
len(text) = 2478
#new_line = 74
first few lines with length:
17 'module read_mod'
21 'implicit none '
10 'contains'
(The line with trailing blanks is present for demonstration.) The output is consistent with
wc read_file.f90
, which gives
74 261 2478 read_file.f90