Fortran how to read double precision data in input text file to real no output text file

INPUT TEXT FILE

time isobaric lat lon u-component_of_wind_isobaric
0.0 10000.0 0.0 45.0 2.3169289
0.0 10000.0 0.0 45.119998931884766 2.4106789
0.0 10000.0 0.11999999731779099 45.0 2.2231789
0.0 10000.0 0.11999999731779099 45.119998931884766 2.3481789
0.0 10000.0 0.11999999731779099 45.2400016784668 2.3169289
0.0 100000.0 0.11999999731779099 45.36000061035156 -2.984314
0.0 100000.0 0.11999999731779099 45.47999954223633 -2.734314
0.0 100000.0 0.0 45.0 -2.890564
0.0 100000.0 0.0 45.119998931884766 -2.781189

OUT PUT TEXT FILE CONTENT
time isobaric lat lon u-component_of_wind_isobaric
0.0 10000.00 0.00 45.00 2.32

 0.0 10000.00     0.00    45.84     1.91

 0.0 10000.00     0.00    46.80     2.91

Welcome to the forum. Could you show your code where you tried to open the text file, read it, and then write it, and say what specific problem you encountered? If you have an array of character strings called words(:) you can read all of them with

read (input_unit,*) words

You can read one row of a matrix x(:,:) with

read (input_unit,*) x(irow,:)

and write it in a similar manner. If the output for numbers should have one decimal point for the first column and two for the remaining, you could do something like

write (ouput_unit,"(f0.1,*(1x,f0.2))") x(irow,:)

2 Likes

I Thank you
i put the code in fortran 95 silver frost version as given below

and it compiles ok. But run time error format/data mismatch error shows line 25 error
that is WRITE(14,"(F0.1,5(1X,F0.2))")X(IROW,:)

The format string is only valid if X is declared real. In your code it is an array of type character. Here is a program that works with gfortran or Intel Fortran that reads the data into an array and writes it to a file.

program main
implicit none
integer, parameter   :: nfields = 5, max_rows = 1000, dp = kind(1.0d0)
character (len=1000) :: title ! use a long length -- it will be trimmed later
real(kind=dp)        :: x(max_rows, nfields)
integer              :: ierr,irow, in_unit, out_unit
open (newunit=in_unit, file = "test4.txt", action = "read", status = "old")
open (newunit=out_unit, file = "result4.txt", action = "write", status = "replace")
read (in_unit,"(a)") title
write (out_unit,"(a)") trim(title)
do irow=1,max_rows
   read (in_unit,*,iostat=ierr) x(irow,:)
   if (ierr /= 0) exit
   write (out_unit,"(f10.1,*(1x,f10.2))") x(irow,:)
end do
end program main

The output file contains

time	isobaric	lat	lon	u-component_of_wind_isobaric
       0.0   10000.00       0.00      45.00       2.32
       0.0   10000.00       0.00      45.12       2.41
       0.0   10000.00       0.12      45.00       2.22
       0.0   10000.00       0.12      45.12       2.35
       0.0   10000.00       0.12      45.24       2.32
       0.0  100000.00       0.12      45.36      -2.98
       0.0  100000.00       0.12      45.48      -2.73
       0.0  100000.00       0.00      45.00      -2.89
       0.0  100000.00       0.00      45.12      -2.78

If you don’t need to store all the data the program could be simplified.

Thank you once again for wonderful help
The program works well in fortran95 silver frost version
as given below

PROGRAM MAIN
IMPLICIT NONE
INTEGER, PARAMETER :: NFIELDS =5, MAX_ROWS =1000, DP = KIND(1.0D0)
CHARACTER (LEN =1000) :: TITLE
REAL(KIND = DP) :: X(MAX_ROWS,NFIELDS)
INTEGER :: IERR,IROW, IN_UNIT=10, OUT_UNIT =14
OPEN ( IN_UNIT, FILE="TEST4.TXT", ACTION = "READ", STATUS = "OLD")
OPEN ( OUT_UNIT, FILE="RESULT4.TXT", ACTION = "WRITE", STATUS = "REPLACE")
READ (IN_UNIT,"(A)")TITLE
WRITE (OUT_UNIT,"(A)")TRIM(TITLE)
DO IROW = 1,MAX_ROWS
  READ(IN_UNIT,*,IOSTAT = IERR) X(IROW,:)
  IF (IERR /=0 ) EXIT
    IF (IROW .EQ. 1  .OR. mod(IROW,8) .EQ. 0) THEN
      WRITE (OUT_UNIT, "(F10.1,5(1X,F10.2))") X(IROW,:)
    END IF
END DO
CLOSE(IN_UNIT)
CLOSE(OUT_UNIT)
END PROGRAM MAIN

I’m glad it worked. I suggest writing code in lower case for legibility. Some Fortran best practices are listed here.

You probably replaced the newunit=in_unit with setting in_unit to a parameter because Silverfrost does not support newunit, which was not in Fortran 95. Silverfrost is fine for Fortran 95, but gfortran and Intel Fortran are both free for Windows and support more recent Fortran standards. I suggest using one of them as your main compiler.

A posting tip is that using the </> icon in the toolbar at the top formats the code in a message.

1 Like

`Hello , help me to write find the values for the following differential equation
-1/g ∫_(Y_1)^(Y_2)β–’βˆ«_(p_1)^(p_2)β–’γ€–( u^2)(_X_1^(X_2))dy dp γ€—

`Hello , help me to write find the values for the following differential equation
-1/g ∫_(Y_1)^(Y_2)β–’βˆ«_(p_1)^(p_2)β–’γ€–( u^2)(_X_1^(X_2))dy dp  γ€—

   -1/g ∫_(Y_1)^(Y_2)β–’βˆ«_(p_1)^(p_2)β–’γ€–( u^2)(_X_1^(X_2))dy dp  γ€—
With values dy=0.12 dp =p(n+1)-p(n) g=9.806
Where  (x,y) is same grid points of a 3 dimensional rectangular box (1,1),(111,111),(222,222)…(888,888) 
X	Y	P	T	U
1	1	1	1	1.32
2	2	1	1	2.32
-	-	-	-	-
110	110	1	1	1.25
111	111	1	1	3.47
112	112	2	1	-25.45
-	-	-	-	-
222	222	3	1	3.34
-	-	-	-	-
333	333	4	1	-3.21
-	-	-	-	-
888	888	8	1	-4.20



---
u is given
pr(1)=100(.ie. p=1)
pr(2)=200(ie p=2,3,4,..8)
PR(1)= 100.;PR(2)= 200.;PR(3)=300.;PR(4)=500.;PR(5)=700.;PR(6)=800.;PR(7)=900.;PR(8)=1000.
long =111 or total 888 
lat =111 or 888
day=1, dyy=0.12,phi1=5.04 
subroutine ewflx(u,pr,long,lat,day,dyy,phi1,rmewfl)
---
return;end

Thank you for your advice