Shell sort (Fortran95)

From LiteratePrograms

Jump to: navigation, search
Other implementations: C | Fortran95


Shell sort is an enhancement of insertion sort, originally published by D. L. Shell in 1959, that gains its speed by comparing elements separated by an increment rather than adjacent elements. By performing a series of interleaved insertion sorts based on an increment sequence the array is gradually sorted until the final increment of one (straight insertion sort) fully sorts the array.

This implementation sorts single precision floating point numbers.

Increment Sequence

A shell sort implementation is said to be uniform if the increments used to sort N items are all less than N, taken in decreasing order, from a fixed infinite increasing sequence. A non-uniform Shellsort uses a different increment sequence for different N. An example of a non-uniform sequence is Shell's original sequence of continually halving until the increment reaches 1. A better non-uniform sequence is to start with 1/3 of N and continually divide by 2.2 using integer division, again ensuring that the last increment is 1.

This implementation uses a uniform sequence based on the formula 3*3^n + 3*2^n – 2 . Other sequences can be found at the On-Line Encyclopedia of Integers Sequences.[1]

<<Increment sequence>>=
INTEGER, PARAMETER :: sequence(15) = (/ 4807543, 1606609, 537583, 180217, 60583, &
                                        20449,  6943, 2377, 823, 289, 103, 37, 13, 4, 1 /)

Main Sort

The main sort is written as a Subroutine.

<<Shell sort subroutine>>=
SUBROUTINE Shellsort(a)
    REAL, INTENT(IN OUT) :: a(:)
    REAL :: temp
    INTEGER :: increment, i, j, k, n
    n = SIZE(a)
    DO k = 1, SIZE(sequence)
       increment = sequence(k)
       IF (increment * 3 > n) cycle
       DO i = increment + 1, n
          j = i - 1
          temp = a(i)
          DO WHILE (j >= increment .AND. a(j-increment+1) > temp)
             a(j+1) = a(j-increment+1)
             j = j - increment
          END DO
          a(j+1) = temp
       END DO
    END DO
  END SUBROUTINE Shellsort


We will encapsulate the increment sequence and subroutine into a Module

<<Sort Module>>=
MODULE Sort_Mod
  IMPLICIT NONE
<<Increment sequence>>=
CONTAINS
<<Shell sort subroutine>>=
END MODULE Sort_Mod

Test Program

We test the code by creating an array of random numbers then passing it to the subroutine for sorting then checking that the returned array is in order.

<<Test Program>>=
PROGRAM Shellsort_Test
  USE Sort_Mod
  IMPLICIT NONE
    INTEGER, PARAMETER :: num = 100000
    INTEGER :: i
    REAL :: array(num)
    CALL RANDOM_NUMBER(array)
    CALL Shellsort(array)
! Verify that the array is sorted
    DO i = 1, num-1
       IF(array(i) > array(i+1)) THEN 
          WRITE(*,*) "Error at index", i
          EXIT
       END IF
    END DO
END PROGRAM Shellsort_Test


<<shellsort.f95>>=
Sort Module
Test Program


This completes the implementation.

Download code
Views