I imagined that there are already a lot of split
routines available from other libraries, but if a minimal / simple (stand-alone) routine is desired, it may be convenient to prepare it in a local library, for example…
module strmod
implicit none
contains
subroutine split( line, words, nw )
character(*), intent(in) :: line
character(*), intent(out) :: words(:)
integer, intent(out) :: nw
character(len(words)) :: buf( size(words) )
integer :: k, ios
nw = 0 ; words(:) = ""
do k = 1, size(words)
buf( 1 : k ) = ""
read( line, *, iostat=ios ) buf( 1 : k )
if ( ios /= 0 ) exit
nw = k
words( 1 : nw ) = buf( 1 : nw )
enddo
end
subroutine get_last_reals( words, vals )
character(*), intent(in) :: words(:)
real, intent(out) :: vals(:)
integer :: k, ios, ir
real :: x
ir = size(vals)
vals(:) = -99999 !! dummy value for "not found" (NaN may be better)
do k = size(words), 1, -1
read( words( k ), *, iostat=ios ) x
if ( ios /= 0 ) cycle
vals( ir ) = x
ir = ir - 1
if ( ir == 0 ) exit
enddo
end
end module
program main
use strmod
implicit none
character(80) :: line, words( 50 )
integer :: nw, k
real :: vals( 2 )
line = "( v= 1) w = 2.843 unit1 = 5.867 unit2 4.567 1.232 )"
!! line = "a abc, 12.34 -23"
!! line = "a; 4 b; 3, c,; abc,12.34, g, -23;"
call split( line, words, nw )
print *, "line = ", trim(line)
print *, "number of words = ", nw
print *, "words in line:"
do k = 1, nw
print "('len = ',i0,' val = ',a)", len_trim( words(k) ), trim( words(k) )
enddo
call get_last_reals( words, vals )
print *, "last two reals in line:", vals
end
$ gfortran-10 test.f90 && ./a.out
line = ( v= 1) w = 2.843 unit1 = 5.867 unit2 4.567 1.232 )
number of words = 13
words in line:
len = 1 val = (
len = 2 val = v=
len = 2 val = 1)
len = 1 val = w
len = 1 val = =
len = 5 val = 2.843
len = 5 val = unit1
len = 1 val = =
len = 5 val = 5.867
len = 5 val = unit2
len = 5 val = 4.567
len = 5 val = 1.232
len = 1 val = )
last two reals in line: 4.56699991 1.23199999
(This Stackoverflow Q/A may also be related)
But, if the line
has something like “123.45)” (no space between reals and parentheses), this kind of method may just fail. In that case, I guess it may be necessary to first remove parenthesis from the line
(e.g. by using a replace()
like routine based on index()
). If the line
has a trailing comment that begins with #
or !
etc, that part may also be needed to be dropped from the line
first, I guess… (again, e.g. via index()
).