PROGRAM series2 ! ! Author: Br. David Carlson ! ! Date: December 31, 1999 ! ! Revised: May 2, 2004 ! ! This program prints out partial sums for a series, stopping when no further ! change is found by adding on another term (or when a set number of terms ! have been added -- to prevent an infinite loop). The particular series ! used is the well-known series for sin(x). IMPLICIT NONE REAL::x, xsquared, term, sum, sumold INTEGER::n, count WRITE (*, 20) 20 FORMAT (1X, 'Program to investigate a series') WRITE (*, *) 'Enter an angle in radians: ' READ (*, *) x sum = 0.0 count = 0 n = 1 term = x xsquared = x * x WRITE (*, 50) 50 FORMAT (' ', T5, 'count', T15, 'term', T35, 'partial sum') DO count = count + 1 sumold = sum sum = sum + term WRITE (*, 100) count, term, sum IF ((sum == sumold) .OR. (count == 200)) THEN EXIT END IF term = -term * xsquared / ((n + 1) * (n + 2)) n = n + 2 END DO 100 FORMAT (' ', T5, I3, T15, E16.8, T35, E16.8) WRITE (*, 200) SIN(x) 200 FORMAT (1X, 'The built-in sine function gives: ', E16.8) END PROGRAM