program SeriesToFile ! ! Filename: SeriesToFile.f90 ! ! Author: Br. David Carlson ! ! Date: March 14, 2010 ! ! This program prints out partial sums for the geometric series 1 + x + x^2 + x^3 + ... ! In particular, the program reads from the text file SeriesToFile.in lines of data of ! the form: ! x value number of terms ! For example, a line might contain this data: ! 0.5 4 ! For such a line, the program would print to the text file SeriesToFile.out the ! following report: ! For x value 0.5 the first 4 partial sums are: ! 0.10000000E+01 ! 0.15000000E+01 ! 0.17500000E+01 ! 0.18750000E+01 ! For each line of input data, a similar report is printed. A blank line is placed ! between reports. IMPLICIT NONE CHARACTER (len=15)::INPUTFILENAME = 'SeriesToFile.in' CHARACTER (len=16)::OUTPUTFILENAME = 'SeriesToFile.out' REAL::x, term, sum, sumold INTEGER::n, NumTerms, InStatus, OutStatus OPEN (UNIT=7, FILE=INPUTFILENAME, STATUS='OLD', ACTION='READ', IOSTAT=InStatus) IF (InStatus /= 0) THEN WRITE (*, *) 'Error trying to open file ', INPUTFILENAME, ' IOSTAT = ', InStatus ELSE OPEN (UNIT=8, FILE=OUTPUTFILENAME, STATUS='REPLACE', ACTION='WRITE', IOSTAT=OutStatus) IF (OutStatus /= 0) THEN WRITE (*, *) 'Error trying to open file ', OUTPUTFILENAME, ' IOSTAT = ', OutStatus ELSE ! Both files opened OK. DO READ (7, *, IOSTAT=InStatus) x, NumTerms IF (InStatus /= 0) THEN ! read error or end of file EXIT END IF WRITE (8, 20) x, NumTerms term = 1.0 sum = 0.0 DO n = 1, NumTerms sum = sum + term WRITE (8, 40) sum ! We will assume that the write works and not check it. term = term * x END DO END DO IF (InStatus > 0) THEN WRITE (*, *) 'A read error has occured.' END IF CLOSE (UNIT= 8) END IF CLOSE (UNIT=7) END IF WRITE (*, *) 'Look for the results in the file ', OUTPUTFILENAME 20 FORMAT (' ', /, 'For x value ', F8.5, ' the first ', I2, ' partial sums are:') 40 FORMAT (' ', T5, E16.8) END PROGRAM