Computing Arithmetic, Geometric and Harmonic Means: Revisited

Problem Statement

The arithmetic mean (i.e., average), geometric mean and harmonic mean of a set of n numbers x1, x2, ..., xn is defined as follows:

Since computing geometric mean requires taking root, it is further required that all input data values must be positive. As a result, this program must be able to ignore those non-positive items. However, this may cause all input items ignored. Therefore, before computing the means, this program should have one more check to see if there are valid items.

Unlike a previous example, this program does not know the number of input items and must handle incorrect input data and ignore them.

Solution

! -----------------------------------------------------------
! This program can read an unknown number of input until the
! end of file is reached.  It calculates the arithmetic,
! geometric, and harmonic means of these numbers.
!
! This program uses IOSTAT= to detect the following two
! conditions:
!    (1)  if the input contains illegal symbols (not numbers)
!    (2)  if the end of input has reached
! -----------------------------------------------------------

PROGRAM   ComputingMeans
   IMPLICIT  NONE

   REAL    :: X
   REAL    :: Sum, Product, InverseSum
   REAL    :: Arithmetic, Geometric, Harmonic
   INTEGER :: Count, TotalValid
   INTEGER :: IO                        ! this is new variable

   Sum        = 0.0
   Product    = 1.0
   InverseSum = 0.0
   TotalValid = 0
   Count      = 0

   DO
      READ(*,*,IOSTAT=IO)  X            ! read in data
      IF (IO < 0)  EXIT                 ! IO < 0 means end-of-file reached
      Count = Count + 1                 ! otherwise, there are data in input
      IF (IO > 0) THEN                  ! IO > 0 means something wrong
         WRITE(*,*)  'ERROR: something wrong in your input'
         WRITE(*,*)  'Try again please'
      ELSE                              ! IO = 0 means everything is normal
         WRITE(*,*) 'Input item ', Count, ' --> ', X
         IF (X <= 0.0) THEN
            WRITE(*,*) 'Input <= 0.  Ignored'
         ELSE
            TotalValid = TotalValid + 1
            Sum        = Sum + X
            Product    = Product * X
            InverseSum = InverseSum + 1.0/X
         END IF
      END IF
   END DO

   WRITE(*,*)
   IF (TotalValid > 0) THEN
      Arithmetic = Sum / TotalValid
      Geometric  = Product**(1.0/TotalValid)
      Harmonic   = TotalValid / InverseSum

      WRITE(*,*)  '# of items read --> ', Count
      WRITE(*,*)  '# of valid items -> ', TotalValid
      WRITE(*,*)  'Arithmetic mean --> ', Arithmetic
      WRITE(*,*)  'Geometric mean  --> ', Geometric
      WRITE(*,*)  'Harmonic mean   --> ', Harmonic
   ELSE
      WRITE(*,*)  'ERROR: none of the input is positive'
   END IF

END PROGRAM  ComputingMeans
Click here to download this program.

Program Input and Output

The input consists of a number of real values, one on each line. The program will count the number of input data items and ignore those illegal ones.

Discussion