Finding All Prime Numbers in the Range of 2 and N - Revisited

Problem Statement

We have discussed a method for finding all prime numbers in the range of 2 and N previously. In fact, one can design a function with an INTEGER formal argument and returns .TRUE. if the argument is a prime number. Then, it is used to test if the integers in the range of 2 and N are integers.

Solution

! --------------------------------------------------------------------
! This program finds all prime numbers in the range of 2 and an
! input integer.
! --------------------------------------------------------------------

PROGRAM  Primes
   IMPLICIT  NONE

   INTEGER  :: Range, Number, Count

   Range = GetNumber()
   Count = 1                            ! input is correct. start counting
   WRITE(*,*)                           ! since 2 is a prime
   WRITE(*,*)  'Prime number #', Count, ': ', 2
   DO Number = 3, Range, 2              ! try all odd numbers 3, 5, 7, ...
      IF (Prime(Number)) THEN
         Count = Count + 1              ! yes, this Number is a prime
         WRITE(*,*)  'Prime number #', Count, ': ', Number
      END IF
   END DO

   WRITE(*,*)
   WRITE(*,*)  'There are ', Count, ' primes in the range of 2 and ', Range

CONTAINS

! --------------------------------------------------------------------
! INTEGER FUNCTION  GetNumber()
!    This function does not require any formal argument.  It keeps
! asking the reader for an integer until the input value is greater
! than or equal to 2.
! --------------------------------------------------------------------

   INTEGER FUNCTION  GetNumber()
      IMPLICIT  NONE

      INTEGER :: Input

      WRITE(*,*)  'What is the range ? '
      DO                                ! keep trying to read a good input
         READ(*,*)  Input               ! ask for an input integer
         IF (Input >= 2)  EXIT          ! if it is GOOD, exit
         WRITE(*,*)  'The range value must be >= 2.  Your input = ', Input
         WRITE(*,*)  'Please try again:'     ! otherwise, bug the user
      END DO
      GetNumber = Input
   END FUNCTION  GetNumber

! --------------------------------------------------------------------
! LOGICAL FUNCTION  Prime()
!    This function receives an INTEGER formal argument Number.  If it
! is a prime number, .TRUE. is returned; otherwise, this function
! returns .FALSE.
! --------------------------------------------------------------------

   LOGICAL FUNCTION  Prime(Number)
      IMPLICIT  NONE

      INTEGER, INTENT(IN) :: Number
      INTEGER             :: Divisor

      IF (Number < 2) THEN
         Prime = .FALSE.
      ELSE IF (Number == 2) THEN
         Prime = .TRUE.
      ELSE IF (MOD(Number,2) == 0) THEN
         Prime = .FALSE.
      ELSE
         Divisor = 3
         DO
            IF (Divisor*Divisor>Number .OR. MOD(Number,Divisor)==0)  EXIT
            Divisor = Divisor + 2
         END DO
         Prime = Divisor*Divisor > Number
      END IF
   END FUNCTION  Prime

END PROGRAM  Primes
Click here to download this program.

Program Input and Output

The following is the output from the above program.
What is the range ?
-10
The range value must be >= 2.  Your input = -10
Please try again:
0
The range value must be >= 2.  Your input = 0
Please try again:
60

Prime number #1: 2
Prime number #2: 3
Prime number #3: 5
Prime number #4: 7
Prime number #5: 11
Prime number #6: 13
Prime number #7: 17
Prime number #8: 19
Prime number #9: 23
Prime number #10: 29
Prime number #11: 31
Prime number #12: 37
Prime number #13: 41
Prime number #14: 43
Prime number #15: 47
Prime number #16: 53
Prime number #17: 59

There are 17 primes in the range of 2 and 60

Discussion