An Extended Histogram Program

Problem Statement

Suppose there are n score values x1, x2, ..., xn. We want to know extend the previous by (1) making the range as an input, and (2) printing a vertical bar type histogram.

Since the range may be different from examination to examination, treating it as an input would make our program more flexible. The following is a typical input format:

15
78  95  68  85  55
88  82  75  63  90
85  76  82  40  68
 4
60  70  80  90
The first set of input values consists of 15 (the number of scores) followed by fifteen scores. Then, the next value 4 gives the number of range division points followed the actual values. In the above, there are five ranges [0,59], [60,69], [70,79], [80,89], [90,100].

The bar of the generated histogram should be printed vertically. In the above score values, there are 2 scores in [0,59], 3 in [60,69], 3 in [70,79], 5 in [80,89] and 2 in [90,100]. Therefore, the histogram should look like the following:

 +---+---+---+---+---+
 |            ***    |
 |            ***    |
 |    *** *** ***    |
 |*** *** *** *** ***|
 |*** *** *** *** ***|
 +---+---+---+---+---+

Solution

Here is the module for counting and histogram printing:
! --------------------------------------------------------------------
! MODULE  Histogram_and_Count:
!    This module implements the counting and histogram printing.  Note
! that for the counting part, handled by subroutine Distribute(), two
! more arguments for the range array and its number of entries.  The
! Plot() subroutine now prints a vertical bar histogram.
! --------------------------------------------------------------------

MODULE  Histogram_and_Count
   IMPLICIT  NONE

CONTAINS

! --------------------------------------------------------------------
! SUBROUTINE  Distribute() :
!    This subroutine receives a score array and a range array, counts
! the number of each scores in each range, and calls Plot() to print
! a histogram.
! --------------------------------------------------------------------

   SUBROUTINE  Distribute(X, N, Range, M)
      IMPLICIT NONE
      INTEGER, DIMENSION(1:), INTENT(IN) :: X     ! input score
      INTEGER, INTENT(IN)                :: N     ! # of scores
      INTEGER, DIMENSION(1:), INTENT(IN) :: Range ! range array
      INTEGER, INTENT(IN)                :: M     ! # of ranges
      INTEGER                            :: i, j  
      INTEGER, DIMENSION(1:M+1)          :: Bucket! counting bucket

      DO i = 1, M+1                     ! clear buckets
         Bucket(i) = 0
      END DO

      DO i = 1, N                       ! for each input score
         DO j = 1, M                    ! determine the bucket
            IF (X(i) < Range(j)) THEN
               Bucket(j) = Bucket(j) + 1
               EXIT
            END IF               
         END DO                         ! don't forget the last bucket
         IF (X(i) >= Range(M))  Bucket(M+1) = Bucket(M+1)+1
      END DO
      CALL  Plot(Bucket, M+1)           ! print a histogram
   END SUBROUTINE  Distribute

! --------------------------------------------------------------------
! SUBROUTINE  Plot() :
!    This subroutine receives a counting array and prints a vertical
! bar histogram.
! --------------------------------------------------------------------

   SUBROUTINE  Plot(Count, K)
      IMPLICIT NONE
      INTEGER, DIMENSION(1:), INTENT(IN) :: Count
      INTEGER, INTENT(IN)                :: K
      CHARACTER(LEN=4), DIMENSION(1:K)   :: Line
      CHARACTER(LEN=4), PARAMETER        :: Division  = "---+"
      CHARACTER(LEN=4), PARAMETER        :: Empty     = "    "
      CHARACTER(LEN=4), PARAMETER        :: EmptyLast = "   |"
      CHARACTER(LEN=4), PARAMETER        :: Data      = "*** "
      CHARACTER(LEN=4), PARAMETER        :: DataLast  = "***|"
      INTEGER                            :: i, j, Maximum

      Maximum = Count(1)                ! find the maximum of the count
      Line(1) = Division                ! clear the print line
      DO i = 2, K
         Line(i) = Division
         IF (Maximum < Count(i))  Maximum = Count(i)
      END DO

      WRITE(*,*) "Histogram:"
      WRITE(*,*)
      WRITE(*,*) "+", (Line(j), j=1,K)  ! print the top border
      DO i = Maximum, 1, -1             ! print from the top
         DO j = 1, K                    ! for each count value
            IF (Count(j) >= i) THEN     !   if >= current value, show ***
               IF (j == K) THEN         !     if this is the last bar
                  Line(j) = DataLast    !       use "***|"
               ELSE                     !     otherwise
                  Line(j) = Data        !       use "*** "
               END IF
            ELSE                        !   if < current value , don't show
               IF (j == K) THEN         !     if this is the last bar
                  Line(j) = EmptyLast   !       use "   |"
               ELSE                     !     otherwise
                  Line(j) = Empty       !       use "    "
               END IF
            END IF
         END DO
         WRITE(*,*) "|", (Line(j), j=1,K)    ! all done.  display this line
      END DO

      DO j = 1, K                       ! prepare and display the lower border
         Line(j) = Division
      END DO
      WRITE(*,*) "+", (Line(j), j=1,K)
   END SUBROUTINE  Plot

END MODULE  Histogram_and_Count
Click here to download this module.

Here is a simple main program:

! --------------------------------------------------------------------
! PROGRAM  Score_Distribution:
!    Give a set of scores, this program plots a histogram showing the
! number of score in the range of [0,59], [60,69], [70,79], [80,89]
! and [90,100].  The range values (i.e., 60, 70, 80 and 90) are read
! in as input data.  The counting and printing subroutines are moved
! to module Histogram_and_Count in file histo-2m.f90.
! --------------------------------------------------------------------

PROGRAM  Score_Distribution
   USE  Histogram_and_Count
   IMPLICIT   NONE
   INTEGER, PARAMETER         :: SIZE = 20   ! array size
   INTEGER, DIMENSION(1:SIZE) :: Score       ! array containing scores
   INTEGER                    :: ActualSize  ! the # of scores read in
   INTEGER, PARAMETER         :: RANGE_SIZE = 10  ! score range size
   INTEGER, DIMENSION(1:RANGE_SIZE) :: Range ! range of scores
   INTEGER                    :: ActualRange
   INTEGER                    :: i

   READ(*,*)  ActualSize, (Score(i), i = 1, ActualSize)
   WRITE(*,*) "Input Scores:"
   WRITE(*,*) (Score(i), i = 1, ActualSize)
   WRITE(*,*)

   READ(*,*)  ActualRange, (Range(i), i = 1, ActualRange)
   WRITE(*,*) "Input Range:"
   WRITE(*,*) (Range(i), i = 1, ActualRange)
   WRITE(*,*)

   CALL  Distribute(Score, ActualSize, Range, ActualRange)

END PROGRAM  Score_Distribution
Click here to download this program.

Program Input and Output

If the input data consist of the following:
15
78  95  68  85  55
88  82  75  63  90
85  76  82  40  68
 4
60  70  80  90
The output of the program is:
 Input Scores:
 78,  95,  68,  85,  55,  88,  82,  75,  63,  90,  85,  76,  82,  40,  68

 Input Range:
 60,  70,  80,  90

 Histogram:

 +---+---+---+---+---+
 |            ***    |
 |            ***    |
 |    *** *** ***    |
 |*** *** *** *** ***|
 |*** *** *** *** ***|
 +---+---+---+---+---+

Discussion