Search code examples
file-iofortranintel-fortrandata-extraction

Extracting specific parameter and its amount from a text file


I have a text file (S.txt) which contains a certain parameter with its amount in each interval. Something like this:

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

.
.
.

I want to write Fortran code to open the text file (S.txt) and read it in order to find each 'x' and read its amount into a parameter. something like this:

a

b

c

. . .

I have come up with this code but it does not work:

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

when I run this program I get NO ERROR, but it doesn't work either.

any suggestion?


Solution

  • 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