Silverfrost Forums

Welcome to our forums

How to modify the code to run it for several files

21 Dec 2009 9:18 (Edited: 22 Dec 2009 9:16) #5594

I have the following codes to compute average value of 20 random data from an external file and write to another external file.

PROGRAM avgvalue
IMPLICIT NONE
INTEGER:: i,n,average, status, sum1
INTEGER, DIMENSION(20) :: x

sum1 = 0
status = 0
n = 20

OPEN (UNIT=3, FILE='file01_set01.txt', STATUS='OLD', ACTION='READ', IOSTAT=status)
OPEN (UNIT=4, FILE='result_file01_set01.txt',STATUS='REPLACE', ACTION='WRITE', IOSTAT=status)

  	DO i = 1, n
  		READ (3,*,IOSTAT=status) x(i)
	END DO

	DO i = 1,n
   		sum1 = sum1 + x(i)
	END DO
     	average = sum1/n
          	
WRITE (4,*) average 
CLOSE(3)
CLOSE(4)

STOP
END PROGRAM

  

How to run the above program for multiple files with the following names,

file01_set01.txt file01_set02.txt file01_set03.txt file01_set04.txt file01_set05.txt

have been searching everywhere but with no luck. Any hint or suggestion pls?

Many thanks!

22 Dec 2009 7:18 #5596

One way is to pass the file name as a command line argument when running your executable. There are standard routines in the library to enable you to do this. See ftn95.chm.

22 Dec 2009 11:52 #5597

Thanks But what is chm and where can I find it? If it means (just guessing) compiler's help manual, it did not help me actually.

Thanks again!

22 Dec 2009 5:29 #5599

It is the FTN95 help file that can be found in the compiler folder. It can also be accessed from the help menu in Plato.

23 Dec 2009 3:49 #5604

Make the code this way and load a hundred files at ones

character*64 filenames

OPEN (UNIT=4, FILE='result_file01_set01.txt',STATUS='REPLACE', ACTION='WRITE', IOSTAT=status)

filenames = 'file01_setXX.txt'
do k=1,99
   write(filenames(11:12),'(i2.2)')  = k
   write(4,*) filenames
   OPEN (UNIT=3, FILE=filenames, STATUS='OLD', ACTION='READ', IOSTAT=status,err=1000)

...
enddo
1000 continue 
3 Feb 2010 6:17 #5874

@DanRRight

Did you mean i2.2 or f2.2?

write(filenames(11:12),'(i2.2)')  = k 

How do I apply the same trick if I have subroutines as in https://forums.silverfrost.com/Forum/Topic/1289&view=previous

Thank you so much to all.

4 Feb 2010 3:38 #5882

It is i2.2. What it's doing is just changing numbers in filenames. So you have to name the files on your harddrive like that:

file01.txt, file02.txt... file99.txt

not

file1.txt , file2.txt, file99.txt

(i take the names not exactly like you, just to demonstrate the idea)

The way to do your task is almost exactly like i have mentioned above - place all subroutines inside the do loop but before calling them the program will change the filenames for you: first will be called file01.txt, then file02.txt etc

So the do loop will automatically change the filename and do math, change the name - do math etc until the end

Beginning is always hardest. Or that is your school homework project? I hated them so much in my time expecting that i will never do programming in my life... such a twist of destiny 😃

4 Feb 2010 11:11 #5887

The following should work. Do you want the average to be a truncated integer ?

PROGRAM avgvalue 
IMPLICIT NONE 

INTEGER:: i,n, status, file_set_no, file_no, files_read
real*8 sum1
INTEGER, DIMENSION(20) :: x 
character data_name*40, result_name*40
!
file_no = 1
files_read = 0
!
do file_set_no = 0,99
   write (data_name, fmt='(a,i2.2,a,i2.2,a)') 'file', file_no,'_set', file_set_no,'.txt'
   result_name = 'result_' // data_name 
!
   CLOSE (unit=13, iostat=status)
   CLOSE (unit=14, iostat=status)
   OPEN (UNIT=13, FILE=data_name, STATUS='OLD', ACTION='READ', IOSTAT=status)
    if (status /= 0) cycle
   OPEN (UNIT=14, FILE=result_name, STATUS='UNKNOWN', ACTION='WRITE', IOSTAT=status) 
    if (status /= 0) cycle
!
    n = 20 
    DO i = 1, n 
        READ (13,*,IOSTAT=status) x(i) 
        if (status /= 0) exit
    END DO 
    if (i <= n) then
      write (*,fmt='(a,i0,a,a)') 'Only ',i-1,' values recovered from file ',trim (data_name)  
      n = i-1
    end if
!
   sum1 = 0 
   DO i = 1,n 
         sum1 = sum1 + x(i) 
   END DO 
   if (n > 1) sum1 = sum1/n 
!              
   WRITE (14,*) sum1,' is the average of ',n, ' values'
   CLOSE (unit=13, iostat=status)
   CLOSE (unit=14, iostat=status)
   files_read = files_read + 1
   WRITE (*,2001) sum1,' is the average of ',n, ' values from ',trim(data_name)
2001 format (1x,f0.2,a,i0,a,a)
!
 end do
 write (*,*) files_read,' files read'
!
STOP 
END PROGRAM 
4 Feb 2010 1:26 #5890

@JohnCampbell,

It is so amazing how you guys spare your time for others! It was definitely a great help.

@DanRRight,

You are right, that was my school homework except they never asked me to do what I am trying to do. The homework was limited to one file only (life was lot easier of course). But I am learning it for my other interest.

I have now this modified program (with subroutines) to compute the sum of data from multiple files according to your suggestion. I see the do loop is only changing the file name correctly but not passing the file name to the SUBROUTINE READFILE (x,rep). So I am getting the same sum value for all my 6 files. How can I possibly solve this in the simplest way? My files are n401.txt to n406.txt.

PROGRAM sumvalue
IMPLICIT NONE
INTEGER :: n, ierr
REAL :: sum
REAL, DIMENSION(40) :: filename
CHARACTER (LEN=10) :: seqfilename
INTEGER :: seqnum
n = 40
ierr = 0

seqfilename = 'nXXX.txt'

DO seqnum = 401,406
WRITE(seqfilename(2:4),'(I0)') seqnum
WRITE(*,*) seqfilename 
OPEN (UNIT=10, FILE=seqfilename, STATUS='OLD', ACTION='READ', IOSTAT=ierr) 

CALL READFILE(filename,n)
CALL SUMDATA(filename,sum,n)
CALL WRITEDATA(sum)

CLOSE(UNIT = 3)
CLOSE(UNIT = 7)
ENDDO
STOP
END PROGRAM

!&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&
SUBROUTINE READFILE(x,rep)
IMPLICIT NONE
INTEGER :: i,  ierr
INTEGER, INTENT(IN) :: rep 
REAL, INTENT(OUT), DIMENSION(rep) :: x
ierr = 0 
OPEN (UNIT=3, FILE='n401.txt', STATUS='OLD', ACTION='READ', IOSTAT=ierr) !READ from
DO i = 1, rep
READ (3,*,IOSTAT=ierr) x(i)
END DO
RETURN
END SUBROUTINE
!&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&

SUBROUTINE SUMDATA(row,total,rep)
IMPLICIT NONE
INTEGER :: i
INTEGER, INTENT(IN) :: rep 
REAL, INTENT(IN), DIMENSION(rep) :: row
REAL, INTENT(OUT) :: total
total = 0
DO i = 1, rep
total = total + row(i)
END DO
RETURN
END SUBROUTINE
!&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&

SUBROUTINE WRITEDATA(output)
IMPLICIT NONE
!INTEGER :: ierr
REAL, INTENT(IN) :: output
ACTION='WRITE', IOSTAT=ierr) !WRITE TO
WRITE(*,*) 'The sum of the data is ', output

RETURN
END SUBROUTINE

Thank you guys!

4 Feb 2010 3:12 #5891

Ok I managed to work it out in the following way,

!
.
.
.
CALL READFILE(vdata,n,seqfilename)
.
.
.
&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&
SUBROUTINE READFILE(x,rep,seqfname)
IMPLICIT NONE
INTEGER :: i,  ierr
INTEGER, INTENT(IN) :: rep 
REAL, INTENT(OUT), DIMENSION(rep) :: x
CHARACTER(LEN=10), INTENT(IN) seqfname
ierr = 0 
OPEN (UNIT=3, FILE=seqfname, STATUS='OLD', ACTION='READ', IOSTAT=ierr) !READ from
DO i = 1, rep
READ (3,*,IOSTAT=ierr) x(i)
END DO 
RETURN
END SUBROUTINE
!&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&

Thank you guys for your wonderful help!

Please login to reply.