从文本文件中提取特定参数及其数量

Extracting specific parameter and its amount from a text file

我有一个文本文件 (S.txt),其中包含某个参数及其在每个间隔中的数量。像这样:

-
-
x=a
-
-
x=b
-
-
x=c
-
-

.
.
.

我想编写 Fortran 代码来打开文本文件 (S.txt) 并读取它,以便找到每个 'x' 并将其数量读入参数。像这样:

一个

b

c

。 . .

我想出了这个代码,但它不起作用:

PROGRAM  deter

IMPLICIT  NONE 
real,Dimension(2) :: value
open(unit=40,file='D:\S.txt',action='read')
READ(40,fmt='(2X,f3.3)') value

close(40)

END PROGRAM  deter

当我 运行 这个程序时,我没有得到任何错误,但它也不起作用。

有什么建议吗?

program extract_value

implicit none
integer :: ios
character(len=200), allocatable :: command(:)
character(len=200), allocatable :: word(:)
real, allocatable :: x(:), deter(:)
character(len=200) :: line
integer :: n, i, j, r
character (len=5), parameter :: sstr='x='

open(unit=50, file='D:\S.txt', iostat=ios)
if ( ios /= 0 ) stop "Error opening file S.txt"

n = 0

do
    read(50, '(A)', iostat=ios) line
    if (ios /= 0) exit
    n = n + 1
end do

allocate(command(n))
allocate(word(n))
rewind(50)

j=0

do i = 1, n
    read(50,'(A)') command(i)
    read (command(i),'(a2)') word(i)
    if (word(i)==sstr) then
    j=j+1
    end if
end do

allocate(x(n))
allocate(deter(j))

x=0

do i = 1, n
if (word(i)==sstr) then 

read(command(i), fmt='(2X,f5.2)') x(i)

end if
end do 

deter=0
deter=pack(x, x /= 0)
close(50)


open(unit=100, file='D:\R.txt', action="write",status="replace")
WRITE(100,fmt='(2X,f5.2)')(deter(r), r=1,j)
close(100)


end program extract_value