I have 16 txt files each containing 10,000 data. Now I am trying to calculate average value of each file and put the results in one single file. The result file should have 3 columns and 8 rows. The first column with a predefined values (0.25,0.5 to 3.0) and two columns (2nd and 3rd) with results.
Following codes are just showing errors. (I did not attempt to add the predefined column to keep it simple for me). So any suggestion would be highly appreciated. Many thanks!
PROGRAM test
IMPLICIT NONE
INTEGER::n,seqnum,ierr
DOUBLE PRECISION,DIMENSION(11000000)::y
CHARACTER (LEN=11)::seqfilein
ierr = 0
seqfilein = 'caseXXX.txt'
DO seqnum = 1,16
WRITE(seqfilein(5:7),'(I3.3)')seqnum
WRITE(*,*)seqfilein
OPEN(UNIT=10,FILE=seqfilein,STATUS='OLD',ACTION='READ',IOSTAT=ierr)
CALL READDATA(y,n,seqfilein)
CALL MEAN(y,n,seqfilein)
ENDDO
CLOSE (UNIT = 10)
END
!&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&
SUBROUTINE READDATA(y,n,seqfname)
IMPLICIT NONE
INTEGER::i,ierr
INTEGER,INTENT(out)::n
DOUBLE PRECISION,INTENT(INOUT),DIMENSION(n)::y
CHARACTER(LEN=11),INTENT(IN)::seqfname
ierr = 0
OPEN (UNIT=3,FILE=seqfname,STATUS='OLD',ACTION='READ',IOSTAT=ierr)
DO i = 1, size(y)
READ(3,*,IOSTAT=ierr)y(i)
if (ierr /=0) exit
END DO
n=i-1
CLOSE (UNIT = 3)
RETURN
END SUBROUTINE
!$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$
SUBROUTINE MEAN(y,n,seqfileout)
IMPLICIT NONE
INTEGER::i,j,ierr
DOUBLE PRECISION::sum1
INTEGER,INTENT(IN)::n
DOUBLE PRECISION,INTENT(IN),DIMENSION(n)::y
DOUBLE PRECISION,DIMENSION(96)::avg
CHARACTER(LEN=11),INTENT(IN)::seqfileout
CHARACTER(LEN=11)::seqfout
ierr = 0
seqfout = seqfileout(1:7)
sum1 = 0
DO i = 1, n
sum1 = sum1 + y(i)
avg(i) = sum1/REAL(n)
END DO
DO i=1,16
DO j=1,8
OPEN(UNIT=9,FILE='s1c.avg',STATUS='REPLACE',ACTION='WRITE',IOSTAT=ierr)
WRITE(9,'(F5.2)')avg(j)
CLOSE(UNIT=9)
ENDDO
ENDDO
RETURN
END SUBROUTINE