forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

How to modify the code to run it for several files

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General
View previous topic :: View next topic  
Author Message
pban92



Joined: 23 Nov 2009
Posts: 38

PostPosted: Mon Dec 21, 2009 10:18 pm    Post subject: How to modify the code to run it for several files Reply with quote

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

Code:
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!


Last edited by pban92 on Tue Dec 22, 2009 10:16 am; edited 1 time in total
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7925
Location: Salford, UK

PostPosted: Tue Dec 22, 2009 8:18 am    Post subject: Reply with quote

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.
Back to top
View user's profile Send private message AIM Address
pban92



Joined: 23 Nov 2009
Posts: 38

PostPosted: Tue Dec 22, 2009 12:52 pm    Post subject: Reply with quote

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!
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7925
Location: Salford, UK

PostPosted: Tue Dec 22, 2009 6:29 pm    Post subject: Reply with quote

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.
Back to top
View user's profile Send private message AIM Address
DanRRight



Joined: 10 Mar 2008
Posts: 2816
Location: South Pole, Antarctica

PostPosted: Wed Dec 23, 2009 4:49 pm    Post subject: Reply with quote

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



Code:

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
Back to top
View user's profile Send private message
pban92



Joined: 23 Nov 2009
Posts: 38

PostPosted: Wed Feb 03, 2010 7:17 pm    Post subject: Reply with quote

@DanRRight

Did you mean i2.2 or f2.2?

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


How do I apply the same trick if I have subroutines as in http://forums.silverfrost.com/viewtopic.php?t=1555&view=previous

Thank you so much to all.
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2816
Location: South Pole, Antarctica

PostPosted: Thu Feb 04, 2010 4:38 am    Post subject: Reply with quote

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 Smile
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Thu Feb 04, 2010 12:11 pm    Post subject: Reply with quote

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

Code:
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
Back to top
View user's profile Send private message
pban92



Joined: 23 Nov 2009
Posts: 38

PostPosted: Thu Feb 04, 2010 2:26 pm    Post subject: Reply with quote

@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.


Code:
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!
Back to top
View user's profile Send private message
pban92



Joined: 23 Nov 2009
Posts: 38

PostPosted: Thu Feb 04, 2010 4:12 pm    Post subject: Reply with quote

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

Code:
!
.
.
.
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!
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General All times are GMT + 1 Hour
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group