Computing the Median

Problem Statement

The median of a set of values is computed as follows:
  1. Sort the values
  2. If the number of values is odd, the median is the middle value
  3. If the number of values is even, the median is the average of the two middle values.
For example, if the given values are 4, 2, 3 and 1, after sorting we have 1, 2, 3 and 4. Since the number of values is even, the median is the average of 2 and 3 (i.e., (2+3)/2 = 2.5). If the given values are 3, 5, 1, 4 and 2, after sorting we have 1, 2, 3, 4 and 5. Thus, the median is 3.

Write a program that reads a set of values and computes the median. This program should continue until no input value is available.

Solution

! --------------------------------------------------------------------
! PROGRAM  ComputeMedian:
!    This program contains an internal REAL function for computing the
! median of a set of input.  The median of a set of N data values is
! defined as follows.  First, the data values must be sorted.  Then,
! the median is the middle value X(N/2+1) if N is odd; otherwise, the
! median is the average of the middle two values (i.e., (X(n)+X(N/2+1))/2).
! For example, the median of 4, 2, 3, 1 is 2.5 since the sorted data
! values are 1, 2, 3 and 4 and the average of the middle two data 
! values is (2+3)/2.  The median of 5, 3, 4, 1, 2 is 3 since 3 is the
! middle value of the sorted data 1, 2, 3, 4, 5.
! 
! We shall use the sorting subroutine discussed earlier.
! --------------------------------------------------------------------

PROGRAM  ComputeMedian
   USE       Sorting
   IMPLICIT  NONE
   INTEGER, PARAMETER               :: ARRAY_SIZE = 20
   INTEGER, DIMENSION(1:ARRAY_SIZE) :: DataArray
   INTEGER                          :: ActualSize
   INTEGER                          :: IOstatus
   INTEGER                          :: i

   DO
      READ(*,*,IOSTAT=IOstatus) ActualSize, (DataArray(i), i = 1, ActualSize)
      IF (IOstatus < 0) THEN
         WRITE(*,*)  "End of data reached."
         EXIT
      ELSE IF (IOstatus > 0) THEN
         WRITE(*,*)  "Something wrong in your data."
         EXIT
      ELSE
         WRITE(*,*)  "InputData:"
         WRITE(*,*)  (DataArray(i), i = 1, ActualSize)
         WRITE(*,*)
         WRITE(*,*)  "Median = ", Median(DataArray, ActualSize)
         WRITE(*,*)
      END IF
   END DO

CONTAINS

! --------------------------------------------------------------------
! REAL FUNCTION  Median() :
!    This function receives an array X of N entries, copies its value
! to a local array Temp(), sorts Temp() and computes the median.
!    The returned value is of REAL type.
! --------------------------------------------------------------------

   REAL FUNCTION  Median(X, N)
      IMPLICIT  NONE
      INTEGER, DIMENSION(1:), INTENT(IN) :: X
      INTEGER, INTENT(IN)                :: N
      INTEGER, DIMENSION(1:N)            :: Temp
      INTEGER                            :: i

      DO i = 1, N                       ! make a copy
         Temp(i) = X(i)
      END DO
      CALL  Sort(Temp, N)               ! sort the copy
      IF (MOD(N,2) == 0) THEN           ! compute the median
         Median = (Temp(N/2) + Temp(N/2+1)) / 2.0
      ELSE
         Median = Temp(N/2+1)
      END IF
   END FUNCTION  Median

END PROGRAM  ComputeMedian
Click here to download this program.

Here is the sorting module:

! --------------------------------------------------------------------
! MODULE  Sorting:
!    This module can sort a set of numbers.  The method used is 
! usually referred to as "selection" method.
! --------------------------------------------------------------------

MODULE  Sorting
   IMPLICIT  NONE
   PRIVATE   :: FindMinimum, Swap

CONTAINS

! --------------------------------------------------------------------
! INTEGER FUNCTION  FindMinimum():
!    This function returns the location of the minimum in the section
! between Start and End.
! --------------------------------------------------------------------

   INTEGER FUNCTION  FindMinimum(x, Start, End)
      IMPLICIT  NONE
      INTEGER, DIMENSION(1:), INTENT(IN) :: x
      INTEGER, INTENT(IN)                :: Start, End
      INTEGER                            :: Minimum
      INTEGER                            :: Location
      INTEGER                            :: i

      Minimum  = x(Start)          ! assume the first is the min
      Location = Start             ! record its position
      DO i = Start+1, End          ! start with next elements
         IF (x(i) < Minimum) THEN  !   if x(i) less than the min?
            Minimum  = x(i)        !      Yes, a new minimum found
            Location = i                !      record its position
         END IF
      END DO
      FindMinimum = Location            ! return the position
   END FUNCTION  FindMinimum

! --------------------------------------------------------------------
! SUBROUTINE  Swap():
!    This subroutine swaps the values of its two formal arguments.
! --------------------------------------------------------------------

   SUBROUTINE  Swap(a, b)
      IMPLICIT  NONE
      INTEGER, INTENT(INOUT) :: a, b
      INTEGER                :: Temp

      Temp = a
      a    = b
      b    = Temp
   END SUBROUTINE  Swap

! --------------------------------------------------------------------
! SUBROUTINE  Sort():
!    This subroutine receives an array x() and sorts it into ascending
! order.
! --------------------------------------------------------------------

   SUBROUTINE  Sort(x, Size)
      IMPLICIT  NONE
      INTEGER, DIMENSION(1:), INTENT(INOUT) :: x
      INTEGER, INTENT(IN)                   :: Size
      INTEGER                               :: i
      INTEGER                               :: Location

      DO i = 1, Size-1             ! except for the last
         Location = FindMinimum(x, i, Size)  ! find min from this to last
         CALL  Swap(x(i), x(Location))  ! swap this and the minimum
      END DO
   END SUBROUTINE  Sort

END MODULE  Sorting
Click here to download this module.

Program Input and Output

If the input data consist of the following:
10
1   5   6   3
9   8   4   2
0   7
7
1   5   7   3
9   4   6
The output of the program is:
 InputData:
 1,  5,  6,  3,  9,  8,  4,  2,  0,  7

 Median = 4.5

 InputData:
 1,  5,  7,  3,  9,  4,  6

 Median = 5.

 End of data reached.

Discussion