I think this is quite a basic question, but I can\'t seem to find the answer. I\'m trying to read a file of the following form:
1 filedir/i03j12_fort.4
No - you will need to process the file "manually". Read it into a string, go looking for the first non-blank, then go looking for the next blank, then use internal io to read the relevant bits, etc.
As you have found, list directed io (using *
as the format specifier) has some surprising features - one of them being that the slash character (/
) in input means "stop reading here and leave remaining variables in the IO list as they were". This doesn't work well when you have paths that contain slashes!
Just for fun...
PROGRAM read_some_things
IMPLICIT NONE
! Some number bigger than most of the lines to be read.
INTEGER, PARAMETER :: line_buffer_size = 28
! Index of the start of the value of i in filename.
INTEGER, PARAMETER :: pos_i_in_filename = 10
! Index of the start of the value of j in filename.
INTEGER, PARAMETER :: pos_j_in_filename = 13
CALL process_a_file
CONTAINS
SUBROUTINE process_a_file
INTEGER :: unit ! Unit number for IO.
CHARACTER(:), ALLOCATABLE :: line ! A line from the file.
INTEGER :: iostat ! IOSTAT code.
CHARACTER(256) :: iomsg ! IOMSG to go with IOSTAT
INTEGER :: n, i, j ! Numbers of interest.
OPEN( NEWUNIT=unit, FILE='2015-01-09 read_some_things.txt', &
ACTION='READ', STATUS='OLD', POSITION='REWIND' )
DO
CALL read_a_line(unit, line, iostat, iomsg)
IF (IS_IOSTAT_END(iostat)) EXIT
IF (iostat /= 0) THEN
PRINT "('Error number ',I0,' reading file: ',A)", &
iostat, TRIM(iomsg)
ERROR STOP ':('
END IF
! What to do with an empty record?
! IF (LEN_TRIM(line) == 0) CALL Start_WW3
CALL chop_a_line(line, n, i, j)
PRINT "(2X,I0,1X,I0,1X,I0)", n, i, j
END DO
CLOSE(unit)
END SUBROUTINE process_a_file
! Parse a line into numbers of interest.
SUBROUTINE chop_a_line(line, n, i, j)
CHARACTER(*), INTENT(IN) :: line ! The line to chop.
INTEGER, INTENT(OUT) :: n ! Things we got...
INTEGER, INTENT(OUT) :: i
INTEGER, INTENT(OUT) :: j
! Various significnat character positions in the line.
INTEGER :: first_non_blank_pos
INTEGER :: next_blank_pos
INTEGER :: before_filename_pos
! Buffer for assembling a format specification.
CHARACTER(100) :: fmt
! Find start of first non-blank group.
first_non_blank_pos = VERIFY(line, ' ')
! Tolerate its non-existence - this may be zero.
! Find start of the following blank group, starting from after
! the beginning of the first non-blank group.
next_blank_pos = SCAN(line(first_non_blank_pos+1:), ' ')
! It had better exist. If it doesn't, confuse user.
IF (next_blank_pos == 0) ERROR STOP 'I didn''t draw any blanks'
next_blank_pos = next_blank_pos + first_non_blank_pos
! Find start of the second group of non-blanks, backup one.
before_filename_pos = VERIFY(line(next_blank_pos:), ' ')
! It had better exist. If it doesn't, annoy user.
IF (before_filename_pos == 0) ERROR STOP 'Line in file with no file!'
! Note -2 to backup one and remember position before filename.
before_filename_pos = before_filename_pos + next_blank_pos - 2
! This specifies:
! - read all prior to filename as integer,
! - then skip to start of i, read I2,
! - then skip to start of j, read I2.
WRITE (fmt, "('(I',I0,',T',I0,',I2,T',I0,',I2)')") &
before_filename_pos, &
before_filename_pos + pos_i_in_filename, &
before_filename_pos + pos_j_in_filename
READ (line, fmt) n, i, j
END SUBROUTINE chop_a_line
! Read a record into a character variable. Pretty common task...
SUBROUTINE read_a_line(unit, line, iostat, iomsg)
INTEGER, INTENT(IN) :: unit ! Unit to read from.
CHARACTER(:), INTENT(OUT), ALLOCATABLE :: line ! The record read.
INTEGER, INTENT(OUT) :: iostat ! +ve on error, -ve on eof.
CHARACTER(*), INTENT(OUT) :: iomsg ! IOMSG if iostat /= 0
! Buffer to read record fragment.
CHARACTER(line_buffer_size) :: buffer
INTEGER :: size ! Amount read per read.
line = ''
DO
! Read a bit without always advancing to the next record.
READ ( unit, "(A)", ADVANCE='NO', SIZE=size, IOSTAT=iostat, &
IOMSG=iomsg ) buffer
IF (iostat > 0) RETURN ! Bail on fail.
! Philosophical discussion about whether EOF is possible
! and SIZE /= 0 goes here (consider STREAM access).
line = line // buffer(:size) ! Append what we got.
! Exit loop on end of file or end of record.
IF (iostat < 0) EXIT
END DO
! End of record is expected, not a relevant condition to return.
IF (IS_IOSTAT_EOR(iostat)) iostat = 0
END SUBROUTINE read_a_line
END PROGRAM read_some_things
For completeness, here is my chosen solution, which relies on the fact that the string following the integer always starts with '/' (as it's a filepath):
! first determine how much whitespace is around the first integer
! and store this as string ln
read(20, '(a)') filestring
write(ln, "(I1)") INDEX(filestring, ' /')-1
rewind(20)
! use ln to as the integer width
read(filenumber,'(i'//ln//','//ldir//'x,i2,x,i2)') n,pix_i,pix_j