I know how to change numbers in text in a one file, but I need to use table like this (lets say file=word):
1 # K
2 # L
3 # M
and in another file text.dat:
1 1
1 2
1 3
in the second column change the numbers 1, 2, 3 in text K, L, M using Fortran program. I know I can use arrays or I can read it like a line with index. Does anyone has an idea how to do it taking the text from different file? I have problem how to combine changing numbers in one file to text employing two files.
My starting code:
program prevod
implicit none
integer :: i, k, maxgrps, a, p
character(LEN=40):: afile, line, lmpline
parameter (maxgrps=10)
character*10 :: atom, blank, atpname(maxgrps)
logical :: elements, first
afile="t2.dat"
open(20, file = "text.dat",status='old')
open(11,file="res",status='unknown')
do i=1,3
read(20,fmt='(a)') line
read(unit=line,fmt='(i2)') p
if(index(line,'element')==0) then
open(12,file=afile,status='old')
do a=1,3
read(unit=12,fmt='(a)') lmpline
k=index(lmpline,'#');if(k==0) goto 90
atom=lmpline(k:k+6)
k=len_trim(atom)
90 write(11,'(i2,a)') k, atom
enddo
write(11,'(i2,a)') atom
endif
close(12)
enddo
end program prevod
The result I want should look like:
1 K
1 L
1 M
I need to from second file this change of three numbers to K, L, M.
Before we do anything else, let's get rid of that goto. Nothing good can come of it. The lines
read(unit=12,fmt='(a)') lmpline
k=index(lmpline,'#');if(k==0) goto 90
atom=lmpline(k:k+6)
k=len_trim(atom)
90 write(11,'(i2,a)') k, atom
are equivalent to
read(unit=12,fmt='(a)') lmpline
k=index(lmpline,'#')
if (k/=0) then
atom=lmpline(k:k+6)
k=len_trim(atom)
endif
write(11,'(i2,a)') k, atom
but it looks like you're trying to to error handling, which should probably instead be
read(unit=12,fmt='(a)') lmpline
k=index(lmpline,'#')
if (k==0) then
write(11,'(i2,a)') k, atom
stop
endif
atom=lmpline(k:k+6)
k=len_trim(atom)
The next thing to note is that it's not generally a good idea to read through the same file lots of times in the same code. Instead, let's pull your code for reading word (which I believe you call t2.dat in your code?) out of the loop for reading text.dat, and store each atom in an array, as per Ian Bush's comments:
program prevod
implicit none
integer :: i, k, maxgrps, a, p
character(LEN=40):: afile, line, lmpline
parameter (maxgrps=10)
character*10 :: atoms(3), blank, atpname(maxgrps)
logical :: elements, first
afile="t2.dat"
open(12,file=afile,status='old')
do a=1,3
read(unit=12,fmt='(a)') lmpline
k=index(lmpline,'#')
if (k==0) then
write(*, *) k, atom
stop
endif
atoms(a)=lmpline(k:k+6)
enddo
close(12)
open(20, file = "text.dat",status='old')
open(11,file="res",status='unknown')
do i=1,3
read(20,fmt='(a)') line
read(unit=line,fmt='(i2)') p
if(index(line,'element')==0) then
do a=1,3
k=len_trim(atoms(a))
write(11,'(i2,a)') k, atoms(a)
enddo
write(11,'(i2,a)') atoms(3)
endif
enddo
end program prevod
Note that I've replaced the last atom with atoms(3) as you're writing it outside the loop, so it will take the final value. This is probably not what you want.
Now we can look at your loop for reading text.dat and writing res. First off, you're only reading one integer from each line of text.dat. You probably want to read both integers from each line. Also, it's generally better to use list-directed reads rather than formatted reads for this kind of task, as they are more flexible to file format. So your line
read(unit=line,fmt='(i2)') p
would become
read(unit=line, *) a, p
Now you can look for the atom which matches p. Rather than scrolling through a file and finding the match, you can simply access this as atoms(p). And so your code would become
program prevod
implicit none
integer :: i, k, maxgrps, a, p
character(LEN=40):: afile, line, lmpline
parameter (maxgrps=10)
character*10 :: atoms(3), blank, atpname(maxgrps)
logical :: elements, first
afile="t2.dat"
open(12,file=afile,status='old')
do a=1,3
read(unit=12,fmt='(a)') lmpline
k=index(lmpline,'#')
if (k==0) then
write(*, *) k, atom
stop
endif
atoms(a)=lmpline(k:k+6)
enddo
close(12)
open(20, file = "text.dat",status='old')
open(11,file="res",status='unknown')
do i=1,3
read(20,fmt='(a)') line
read(unit=line, *) a, p
write(11,'(i2,a)') a, atoms(p)
enddo
end program prevod
Related
I am trying to read a text file using a Fortran code. I have a file with 1999 rows and the number of columns vary with each row. Can someone please tell me how one can code such a problem. This is my code for reading a 4*2 text file but I am using do loops which I can't use in my current case.
PROGRAM myread2
IMPLICIT NONE
INTEGER, DIMENSION(100) :: a, b
INTEGER :: row,col,max_rows,max_cols
OPEN(UNIT=11, file='text.txt')
DO row = 1,4
READ(11,*) a(row), b(row)
END DO
PRINT *, a(1)
PRINT *, a(4)
PRINT*, b(4)
END PROGRAM myread2
The best way of reading a file like this depends on how you want to store the data. I'm going to use a ragged array as it's probably simplest, although other container types may be better suited depending on your requirements.
Fortran doesn't have ragged arrays natively, so first you need to define a type to hold each row. This can be done as
type :: RowData
integer, allocatable :: cols(:)
end type
type(RowData), allocatable :: rows(:)
When this container is filled out, the value in the i'th column of the j'th row will be accessed as
value = rows(j)%cols(i)
We can then write a program to read the file, e.g.
type :: RowData
integer, allocatable :: cols(:)
end type
type(RowData), allocatable :: rows(:)
integer :: no_rows
integer :: i
open(unit=11, file='text.txt')
no_rows = count_lines(11)
allocate(rows(no_rows))
do i=1,no_rows
rows(i)%cols = read_row(11)
enddo
Now we just need to write the functions count_lines, which counts the number of lines in the file, and read_row, which reads a line from the file and returns the contents of that line as an array of integers.
Following this question, count_lines can be written as
! Takes a file unit, and returns the number of lines in the file.
! N.B. the file must be at the start of the file.
function count_lines(file_unit) result(output)
integer, intent(in) :: file_unit
integer :: output
integer :: iostat
output = 0
iostat = 0
do while (iostat==0)
read(file_unit, *, iostat=iostat)
if (iostat==0) then
output = output+1
endif
enddo
rewind(file_unit)
end function
Writing read_row, to parse a line of unknown length from a file, can be done by following this question.
I am trying to read values from two files and write only the same values in the new(third) file. Is there any code or function I can use? What I have tried is that reading two files with DO statement and named them variable1(i), variable2(j), however I think comparing them is not easy for me, which is not working in the way of variable1(i) = variable (j)
Example:
file 1:
a1,b1,c1,d1,e1,a2,b2,c2,d2,e2,.........
f(a1),f(b1),f(c1),.......
Obviously I don't know the function, I just know the results.
file 2:
e2,e2,c1,c1,c1,c1,a2,a1,..........
new file 3:
f(e2),f(e2),f(c1),f(c1),f(c1),f(a2),f(a1)......
here's my code and the error is occurring because the number of data in two file is different
real*8 refjd(64285),pha(64285)
real*8 timejd(55436),epha(55436)
real*8 phs
format(47x,f10.2)
open(4,file="neic56.out")
do j=1,55436
read(4,55)timejd(j)
close(4)
format(f10.2,1x,f8.4)
open(3,file="74-17.out")
do i=1,64285
read(3,44)refjd(i),pha(i)
close(3)
end do
if(timejd(j) .EQ. refjd(i)) then
epha(j)=pha(i)
phs=epha(j)/360.
open(5,file="ejplphase.dat")
write(5,66)phs
end if
format(f6.4)
end do
end
A naive algorithm that would do the job is the following:
program filesOut
implicit none
integer :: i, j
real*8 :: refjd(64285), pha(64285)
real*8 :: timejd(55436)
real*8 :: phs
100 format(47x,f10.2)
open(15, file="neic56.out", status='old')
do j=1,55436
read(15,100) timejd(j)
end do
close(15)
200 format(f10.2,1x,f8.4)
open(25,file="74-17.out", status='old')
do i=1,64285
read(25,200) refjd(i), pha(i)
end do
close(25)
300 format(f6.4)
open(35,file="ejplphase.dat", status='unknown')
outerloop: do i = 1, size(timejd)
do j = 1, size(refjd)
if (timejd(i) == refjd(j)) then
phs = pha(j)/360.
write(35,300) phs
cycle outerloop
end if
end do
end do outerloop
close(35)
end program
There are some improvements that could be made to increase the efficiency depending on the specifications of your problem.
I am having trouble reading exponential from a text file using Fortran.
The entry in the text file looks like the following
0.02547163e+06-0.04601176e+01 0.02500000e+02 0.00000000e+00 0.00000000e+00 3
And the code that I am using looks like the following
read(iunit,'(ES20.8,ES20.8,ES20.8,ES20.8,ES20.8,I2)') dummy1, dummy2, Thermo_DB_Coeffs_LowT(iS,1:3),temp
The error I am getting is
Fortran runtime error: Bad value during floating point read
How can I read these values?
Well here is what I usually do when it is too painful to hand edit the file...
CHARACTER(LEN=256) :: Line
INTEGER, PARAMETER :: Start = 1
INTEGER :: Fin, Trailing_Int, I
DOUBLE, DIMENSION(6) :: Element
...
Ingest_All_Rows: DO WHILE(.TRUE.)
READ(...) Line ! Into a character-string
<if we get to the end of the file, then 'EXIT Ingest_All_Rows'>
Start =1
Single_Row_Ingest: DO I = 1, 6
Fin = SCAN(Line,'eE')+3 !or maybe it is 4?
IF(I ==6) Fin = LEN_TRIM(Line)
READ(Line(Start:Fin),*) Element(I) !fron the string(len-string) to the double.
Line = Line((Fin+1):)
IF(I ==6) Trailing_Int = Element(6)
ENDDO Single_Row_Ingest
<Here we shove the row's 5 elements into some array, and the trailing int somewhere>
ENDDO Ingest_All_Rows
You will have to fill in the blanks, but I find that SCAN and LEN_TRIM can be useful in these cases
I have a program that creates values for the matrix u, and this changes for every iteration f, I want to write out the value of u(2,2) for every iteration f. So for example u(2,2)=5 f=1, u(2,2)=9 f=2, and so on.
Now test(u,n,f) only writes the last value.When it have met my criteria to stop the do loop. I don't want my subroutine to overwrite the file plot.txt every time, I want it to keep u(2,2) for every iterations. I want it to look like this
5 1
9 2
10 3
but not it only writes
15 25
How can this be fixed?
subroutine test(u,n,f)
!input
integer :: n,f,write_unit
real(8) :: u(n+2,n+2)
!lokale
integer :: i,j
real(8) :: vek_x,vek_y
!Skriver vektor verdier til fil som gnuplot skal bruke
open(newunit=write_unit,access='sequential',file='plot.txt',status='unknown')
write(write_unit,*)'# x y vx vy'
vek_x=u(2,2)
!write(write_unit,*) vek_x,f
write(write_unit,*) vek_x,f
write(write_unit,*)''
close(write_unit,status='keep')
"Program" that creates different values for u
do f=1,1000
do j=2,n+1
do i=2,n+1
u(i,j)=(u(i+1,j)+u(i-1,j)+u(i,j+1)+u(i,j-1))/4
!u(i,j)=(1-omega)*u(i,j)+omega*1/4*(u(i+1,j)+u(i-1,j)+u(i,j+1)+u(i,j-1))
end do
end do
if (u(2,2) .eq. 15) then
exit
end if
call test(u,n,f)
end do
Just open the file for appending
open(newunit=write_unit,access='sequential',file='plot.txt',position='append',status='old',action='write')
if that is what you wanted.
For the first time to may want to just create it empty
open(newunit=write_unit,access='sequential',file='plot.txt',status='replace')
close(write_unit)
I imagine this is something silly I've missed but I've asked my whole class and noone can seem to work it out. Making a simple program calling in a subroutine and I'm having trouble with the do loop reading in the entries of the matrix.
program Householder_Program
use QR_Factorisation
use numeric_kinds
complex(dp), dimension(:,:), allocatable :: A, Q, R, V
integer :: i, j, n, m
print *, 'Enter how many rows in the matrix A'
read *, m
print *, 'Enter how many columns in the matrix A'
read *, n
allocate(A(m,n), Q(m,n), R(n,n), V(n,n))
do i = 1,m
do j = 1,n
Print *, 'Enter row', i, 'and column', j, 'of matrix A'
read *, A(i,j)
end do
end do
call Householder_Triangularization(A,V,R,n,m)
print *, R
end program
It will ask me for A(1,1) but when I type in a number it will not ask me for A(1,2), it will leave a blank line. When I try to put in a 2nd number it will error and say :
Enter row 1 and column 1 of matrix A
1
2
At line 22 of file HouseholderProgram.f90 (unit = 5, file = 'stdin')
Fortran runtime error: Bad repeat count in item 1 of list input
Your variable A is (an array) of type complex. This means that when you attempt to do the list-directed input of the element values you cannot just specify a single number. So, in your case the problem is not with the program but with the input.
From the Fortran 2008 standard, 10.10.3
When the next effective item is of type complex, the input form consists of a left parenthesis followed by an ordered pair of numeric input fields separated by a comma (if the decimal edit mode is POINT) or semicolon (if the decimal edit mode is COMMA), and followed by a right parenthesis.
Input, then, must be something like (1., 12.).
You are trying to read in complex numbers (A is complex)! As such, you should specify complex numbers to the code... Since you are providing just one integer, the program does not know what to do.
Providing (1,0) and (2,0) instead of 1 and 2 will do the trick.
In case the user input is always real, and you want to read it into a complex type array you can do something like this:
Print *, 'Enter row', i, 'and column', j, 'of matrix A'
read *, dummy
A(i,j)=dummy
where dummy is declared real. This will save the user from the need to key in the parenthesis required for complex numbers. ( The conversion to complex is automatic )