Clicky

Fortran Wiki
getvals (changes)

Skip the Navigation Links | Home Page | All Pages | Recently Revised | Authors | Feeds | Export |

Showing changes from revision #5 to #6: (追記) Added (追記ここまで) | (削除) Removed (削除ここまで) | (削除) Chan (削除ここまで)(追記) ged (追記ここまで)

reading an arbitrary number of values from a line

I have often seen questions on how to read an arbitrary number of numeric values from an input line. I have a collection of parsing routines I have used for this task, but decided to revisit the problem using list-directed input, internal reads, and Fortran 2003. It ends up it is relatively straight-forward to read a line with an arbitrary number of values, to use repeat counts, to allow for inline comments (using the fact that the slash seperator is really not a seperator on list-directed input but an input terminator).

Using the module and example program below this input file:

10,20 30.4 
 1 2 3 
 1 
 
 3 4*2.5 8 
 32.3333 / comment 1 
 30e3;300, 30.0, 3
 even 1 like this! 10

produces this output:

 VALUES= 10.0000000 20.0000000 30.3999996 
 VALUES= 1.00000000 2.00000000 3.00000000 
 VALUES= 1.00000000 
 VALUES=
 VALUES= 3.00000000 2.50000000 2.50000000 2.50000000 2.50000000 8.00000000 
 VALUES= 32.3333015 
 VALUES= 30000.0000 300.000000 30.0000000 3.00000000 
 *getvals* WARNING:[even] is not a number
 *getvals* WARNING:[like] is not a number
 *getvals* WARNING:[this!] is not a number
 VALUES= 1.00000000 10.0000000 

Lines with single and double quotes in the input could cause some surprises, but this ends up being a very flexible way to read a list of numeric values. Complex numbers can be supported too. Add some allocatable arrays and a routine for reading a line of arbitrary length and this could be made even more generic.

Note that if you want to do something like this you should look at NAMELIST input too; which can now also read from an internal file.

After a careful read of the definition of list-directed input I am convinced this is standard f2003. If I’m wrong let me know. Enjoy ...


NAME

getvals(3f) - [M_getvals] read arbitrary number of values from a character variable up to size of VALUES() array

SYNOPSIS

subroutine getvals(line,values,icount,ierr)

character(len=*),intent(in) :: line
real,intent(out) :: values(:)
integer,intent(out) :: icount
integer,intent(out),optional :: ierr

DESCRIPTION

GETVALS(3f) reads a relatively arbitrary number of numeric values from a character variable into a REAL array using list-directed input.

NOTE: In this version null values terminate the reading of the line.

 1,,,,,,,2 / stops after reading first value because of null values

Per list-directed rules when reading values, allowed delimiters are comma, semi-colon and space.

the slash seperator can be used to add inline comments.

 10.1, 20.43e-1 ; 11 / THIS IS TREATED AS A COMMENT

Repeat syntax can be used up to the size of the output array. These are equivalent input lines:

 4*10.0
 10.0, 10.0, 10.0, 10.0

OPTIONS

LINE
A character variable containing the characters representing a list of numbers

RETURNS

VALUES()
array holding numbers read from string
ICOUNT
number of defined numbers in VALUES()
IERR
zero if no error occurred in reading numbers. Optional. If not supplied and an error occurs, program is terminated.

EXAMPLES

Sample program:

 program tryit
 use M_getvals, only: getvals
 implicit none
 character(len=256) :: line
 real :: values(256/2+1)
 integer :: ios,icount,ierr
 INFINITE: do
 read(*,'(a)',iostat=ios) line
 if(ios.ne.0)exit INFINITE
 call getvals(line,values,icount,ierr)
 write(*,*)'VALUES=',values(:icount)
 enddo INFINITE
 end program tryit

Sample input lines

 10,20 30.4
 1 2 3
 1
 3 4*2.5 8
 32.3333 / comment 1
 30e3;300, 30.0, 3
 even 1 like this! 10
 11,,,,22,,,,33 / as written, GETVALS(3f) stops on first null value

Expected output:

 VALUES= 10.0000000 20.0000000 30.3999996
 VALUES= 1.00000000 2.00000000 3.00000000
 VALUES= 1.00000000
 VALUES=
 VALUES= 3.00000000 2.50000000 2.50000000 2.50000000 2.50000000 8.00000000
 VALUES= 32.3333015
 VALUES= 30000.0000 300.000000 30.0000000 3.00000000
 *getvals* WARNING:[even] is not a number
 *getvals* WARNING:[like] is not a number
 *getvals* WARNING:[this!] is not a number
 VALUES= 1.00000000 10.0000000
 VALUES= 11.0000000

Module Source

This module code was tested with gfortran 5.4.3, using

 gfortran -std=f2003 -Wall -c M_getvals.f90
 gfortran -std=f2003 -Wall tryit.f90 M_getvals.o -o tryit 

~

!-----------------------------------------------------------------------------------------------------------------------------------
module M_getvals
private
public getvals
contains
!-----------------------------------------------------------------------------------------------------------------------------------
subroutine getvals(line,values,icount,ierr)
implicit none
character(len=*),parameter :: ident='@(#)getvals: read arbitrary number of values from a character variable up to size of values'
! JSU 20170831
character(len=*),intent(in) :: line
real :: values(:)
integer,intent(out) :: icount
integer,intent(out),optional :: ierr
 character(len=:),allocatable :: buffer
 character(len=len(line)) :: words(size(values))
 integer :: ios, i, ierr_local
 ierr_local=0
 words=' ' ! make sure words() is initialized to null+blanks
 buffer=trim(line)//"/" ! add a slash to the end so how the read behaves with missing values is clearly defined
 read(buffer,*,iostat=ios) words ! undelimited strings are read into an array
 icount=0
 do i=1,size(values) ! loop thru array and convert non-blank words to numbers
 if(words(i)(1:1).eq.' ')exit
 read(words(i),*,iostat=ios)values(icount+1)
 if(ios.eq.0)then
 icount=icount+1
 else
 ierr_local=ios
 write(*,*)'*getvals* WARNING:['//trim(words(i))//'] is not a number'
 endif
 enddo
 if(present(ierr))then
 ierr=ierr_local
 elseif(ierr_local.ne.0)then ! error occurred and not returning error to main program to print message and stop program
 write(*,*)'*getval* error reading line ['//trim(line)//']'
 stop 2
 endif
end subroutine getvals
end module M_getvals
!-----------------------------------------------------------------------------------------------------------------------------------

Allowing ARRAYS() to be of various types

This is a variant that allows the ARRAYS() value to be of type INTEGER, REAL, or DOUBLEPRECISION ...

module M_getvals
private
public getvals
contains
subroutine getvals(line,values,icount,ierr)
implicit none
character(len=*),parameter :: ident='@(#)getvals: read arbitrary number of values from a character variable up to size of values'
! JSU 20170831
character(len=*),intent(in) :: line
class(*),intent(in) :: values(:)
integer,intent(out) :: icount
integer,intent(out),optional :: ierr
 character(len=:),allocatable :: buffer
 character(len=len(line)) :: words(size(values))
 integer :: ios, i, ierr_local,isize
 select type(values)
 type is (integer); isize=size(values)
 type is (real); isize=size(values)
 type is (doubleprecision); isize=size(values)
 type is (character(len=*)); isize=size(values)
 end select
 ierr_local=0
 words=' ' ! make sure words() is initialized to null+blanks
 buffer=trim(line)//"/" ! add a slash to the end so how the read behaves with missing values is clearly defined
 read(buffer,*,iostat=ios) words ! undelimited strings are read into an array
 icount=0
 do i=1,isize ! loop thru array and convert non-blank words to numbers
 if(words(i).eq.' ')cycle
 select type(values)
 type is (integer); read(words(i),*,iostat=ios)values(icount+1)
 type is (real); read(words(i),*,iostat=ios)values(icount+1)
 type is (doubleprecision); read(words(i),*,iostat=ios)values(icount+1)
 type is (character(len=*)); values(icount+1)=words(i)
 end select
 if(ios.eq.0)then
 icount=icount+1
 else
 ierr_local=ios
 write(*,*)'*getvals* WARNING:['//trim(words(i))//'] is not a number of specified type'
 endif
 enddo
 if(present(ierr))then
 ierr=ierr_local
 elseif(ierr_local.ne.0)then ! error occurred and not returning error to main program to print message and stop program
 write(*,*)'*getval* error reading line ['//trim(line)//']'
 stop 2
 endif
end subroutine getvals
!===================================================================================================================================
!()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()!
!===================================================================================================================================
end module M_getvals
(追記) (追記ここまで)(追記)
(追記ここまで)
(追記) (追記ここまで)(追記)

Reading a file of integers

(追記ここまで)
(追記) (追記ここまで)(追記)

Here is a slightly different method that solves the most frequently asked question I saw – how to read a file of integers into an array without knowing how many values are on a line or how many values are in the file.

(追記ここまで)
(追記) (追記ここまで)(追記)

Not sure why this is asked about so often. I hope I am not doing a frequently assigned homework problem.

(追記ここまで)
(追記) (追記ここまで)(追記)

This is a self-contained example. It requires Fortran 2003+.

(追記ここまで)
(追記) (追記ここまで)(追記)

There is quite a bit of re-allocation used, which means this might be slow on large files (hundreds of thousands of values) in some programming environments.

(追記ここまで)
(追記) (追記ここまで)(追記)

Sample input file "data":

(追記ここまで)
(追記) (追記ここまで)(追記)
 10 20 30
 40
 50 60
 1,2,3
 11 22 33
 44, 55 ; 66
(追記ここまで)
(追記) (追記ここまで)(追記)

Sample output:

(追記ここまで)
(追記) (追記ここまで)(追記)
 new line=10 20 30
 read 3 values=10,20,30
 new line=40
 read 1 values=40
 new line=
 read 0 values=
 new line=50 60
 read 2 values=50,60
 new line=1,2,3
 read 3 values=1,2,3
 new line=11 22 33
 read 3 values=11,22,33
 new line= 44, 55 ; 66
 read 3 values=44,55,66
 total values read=15
 10,20,30,40,50,60,1,2,3,11,22,33,44,55,66
(追記ここまで)
(追記) (追記ここまで)(追記)
program readfile
implicit none
integer,parameter :: line_length=80
character(len=line_length) :: line
character(len=line_length) :: word
integer :: a(line_length/2+1)
integer :: i,io,icount
integer,allocatable :: total(:)
allocate(total(0))
open(100, file='data')
FILEREAD: do
 read(100,'(a)',IOSTAT=io)line ! read a line into character variable
 if(io.ne.0) exit FILEREAD
 write(*,*)'new line=',trim(line)
 do i=1,len(line) ! replace comma and semicolon delimiters with spaces
 select case(line(i:i))
 case(',',';'); line(i:i)=' '
 end select
 enddo
 icount=0 ! initialize count of values found on line
 do
 line=adjustl(line) ! remove leading spaces
 read(line,*,IOSTAT=io)word ! read next token from line
 if (io.ne.0) exit
 read(word,*,IOSTAT=io) a(icount+1) ! convert token to a number
 if (io.ne.0) exit
 icount=icount+1
 line=line(len_trim(word)+1:) ! remove token just read
 enddo
 write(*,'(1x,a,i0,a,*(i0:,","))')' read ',icount,' values=', a(:icount)
 total=[total,a(:icount)]
enddo FILEREAD
write(*,'(a,i0)')'total values read=',size(total)
write(*,'(*(i0:,","))')total
end program readfile
(追記ここまで)

category: code

Revised on September 2, 2017 21:30:15 by urbanjost (73.40.218.30) (12197 characters / 5.0 pages)
Edit | Back in time (5 revisions) | Hide changes | History | Views: Print | TeX | Source | Linked from: Code

AltStyle によって変換されたページ (->オリジナル) /