Sorting algorithms/Shell sort: Difference between revisions

From Rosetta Code
Content added Content deleted
m (Fixed lang tags.)
Line 5: Line 5:
=={{header|Ada}}==
=={{header|Ada}}==
This is a generic implementation of the shell sort. Ada allows arrays to be indexed by integer or enumeration types starting at any value. This version deals with any kind or value of valid index type.
This is a generic implementation of the shell sort. Ada allows arrays to be indexed by integer or enumeration types starting at any value. This version deals with any kind or value of valid index type.
<lang ada>
<lang ada>generic
generic
type Element_Type is digits <>;
type Element_Type is digits <>;
type Index_Type is (<>);
type Index_Type is (<>);
Line 12: Line 11:
package Shell_Sort is
package Shell_Sort is
procedure Sort(Item : in out Array_Type);
procedure Sort(Item : in out Array_Type);
end Shell_Sort;
end Shell_Sort;</lang>
</lang>
<lang ada>package body Shell_Sort is
<lang ada>package body Shell_Sort is
Line 43: Line 41:
end Sort;
end Sort;


end Shell_Sort;
end Shell_Sort;</lang>
</lang>


=={{header|ALGOL 68}}==
=={{header|ALGOL 68}}==
Line 52: Line 49:
{{works with|ALGOL 68G|Any - tested with release mk15-0.8b.fc9.i386}}
{{works with|ALGOL 68G|Any - tested with release mk15-0.8b.fc9.i386}}
{{works with|ELLA ALGOL 68|Any (with appropriate job cards) - tested with release 1.8.8d.fc9.i386}}
{{works with|ELLA ALGOL 68|Any (with appropriate job cards) - tested with release 1.8.8d.fc9.i386}}
<lang algol>MODE TYPE = CHAR;
<lang algol68>MODE TYPE = CHAR;


PROC in place shell sort = (REF[]TYPE seq)REF[]TYPE:(
PROC in place shell sort = (REF[]TYPE seq)REF[]TYPE:(
Line 196: Line 193:
=={{header|D}}==
=={{header|D}}==
From the Python version, uses Phobos of D 1.
From the Python version, uses Phobos of D 1.
<lang d>
<lang d>import std.stdio: writefln;
import std.stdio: writefln;


void shell(T)(T[] seq) {
void shell(T)(T[] seq) {
Line 217: Line 213:
shell(data);
shell(data);
writefln(data); // [-5, 2, 4, 7, 8, 22]
writefln(data); // [-5, 2, 4, 7, 8, 22]
}</lang>
}
</lang>


=={{header|E}}==
=={{header|E}}==
Line 241: Line 236:
=={{header|Forth}}==
=={{header|Forth}}==
{{works with|GNU Forth}}
{{works with|GNU Forth}}
defer less? ' < is less?
<lang forth>defer less? ' < is less?
: shell { array len -- }
1 begin dup len u<= while 2* 1+ repeat { gap }
begin gap 2/ dup to gap while
len gap do
array i cells +
dup @ swap ( temp last )
begin gap cells -
array over u<=
while 2dup @ less?
while dup gap cells + over @ swap !
repeat then
gap cells + !
loop
repeat ;


: shell { array len -- }
create array 8 , 1 , 4 , 2 , 10 , 3 , 7 , 9 , 6 , 5 ,
1 begin dup len u<= while 2* 1+ repeat { gap }
begin gap 2/ dup to gap while
array 10 shell
len gap do
array 10 cells dump
array i cells +
dup @ swap ( temp last )
begin gap cells -
array over u<=
while 2dup @ less?
while dup gap cells + over @ swap !
repeat then
gap cells + !
loop
repeat ;

create array 8 , 1 , 4 , 2 , 10 , 3 , 7 , 9 , 6 , 5 ,

array 10 shell
array 10 cells dump</lang>


=={{header|Fortran}}==
=={{header|Fortran}}==
{{works with|Fortran|90 and later}}
{{works with|Fortran|90 and later}}
<lang fortran> MODULE sort
<lang fortran>MODULE sort

CONTAINS

SUBROUTINE Shell_Sort(a)

IMPLICIT NONE
INTEGER :: i, j, increment
REAL :: temp
REAL, INTENT(in out) :: a(:)
increment = SIZE(a) / 2
DO WHILE (increment > 0)
DO i = increment+1, SIZE(a)
j = i
temp = a(i)
DO WHILE (j >= increment+1 .AND. a(j-increment) > temp)
a(j) = a(j-increment)
j = j - increment
END DO
a(j) = temp
END DO
IF (increment == 2) THEN
increment = 1
ELSE
increment = increment * 5 / 11
END IF
END DO
END SUBROUTINE Shell_Sort
CONTAINS

END MODULE sort

PROGRAM Shellsort

USE sort

IMPLICIT NONE
REAL :: array(1000)
CALL RANDOM_SEED
CALL RANDOM_NUMBER(array)
WRITE (*,*) "Unsorted array"
SUBROUTINE Shell_Sort(a)
WRITE (*,*) array
WRITE (*,*)
IMPLICIT NONE
CALL Shell_Sort(array)
INTEGER :: i, j, increment
WRITE (*,*) "Sorted array"
REAL :: temp
WRITE (*,*) array
REAL, INTENT(in out) :: a(:)
increment = SIZE(a) / 2
DO WHILE (increment > 0)
DO i = increment+1, SIZE(a)
j = i
temp = a(i)
DO WHILE (j >= increment+1 .AND. a(j-increment) > temp)
a(j) = a(j-increment)
j = j - increment
END DO
a(j) = temp
END DO
IF (increment == 2) THEN
increment = 1
ELSE
increment = increment * 5 / 11
END IF
END DO
END PROGRAM Shellsort</lang>
END SUBROUTINE Shell_Sort
END MODULE sort
PROGRAM Shellsort
USE sort
IMPLICIT NONE
REAL :: array(1000)
CALL RANDOM_SEED
CALL RANDOM_NUMBER(array)
WRITE (*,*) "Unsorted array"
WRITE (*,*) array
WRITE (*,*)
CALL Shell_Sort(array)
WRITE (*,*) "Sorted array"
WRITE (*,*) array
END PROGRAM Shellsort</lang>


=={{header|Haskell}}==
=={{header|Haskell}}==
Line 352: Line 347:


=={{header|Lisaac}}==
=={{header|Lisaac}}==
<lang Lisaac>
<lang Lisaac>Section Header
Section Header


+ name := SHELL_SORT;
+ name := SHELL_SORT;
Line 398: Line 392:
};
};
};
};
);
);</lang>
</lang>


=={{header|OCaml}}==
=={{header|OCaml}}==
Line 471: Line 464:


This method sorts in place. If you want to preserve your unsorted list, copy it first.
This method sorts in place. If you want to preserve your unsorted list, copy it first.
<lang python>
<lang python>def shell(seq):
def shell(seq):
inc = len(seq) // 2
inc = len(seq) // 2
while inc:
while inc:
Line 484: Line 476:
data = [22, 7, 2, -5, 8, 4]
data = [22, 7, 2, -5, 8, 4]
shell(data)
shell(data)
print data # [-5, 2, 4, 7, 8, 22]
print data # [-5, 2, 4, 7, 8, 22]</lang>
</lang>


=={{header|Ruby}}==
=={{header|Ruby}}==

Revision as of 00:16, 22 November 2009

Task
Sorting algorithms/Shell sort
You are encouraged to solve this task according to the task description, using any language you may know.

In this task, the goal is to sort an array of elements using the Shell sort algorithm, a diminishing increment sort. The Shell sort is named after its inventor, Donald Shell, who published the algorithm in 1959. Shellsort is a sequence of interleaved insertion sorts based on an increment sequence. The increment size is reduced after each pass until the increment size is 1. With an increment size of 1, the sort is a basic insertion sort, but by this time the data is guaranteed to be almost sorted, which is insertion sort's "best case". Any sequence will sort the data as long as it ends in 1, but some work better than others. Empirical studies have shown a geometric increment sequence with a ratio of about 2.2 work well in practice. [1] Other good sequences are found at the Online Encyclopedia of Integer Sequences.

Ada

This is a generic implementation of the shell sort. Ada allows arrays to be indexed by integer or enumeration types starting at any value. This version deals with any kind or value of valid index type. <lang ada>generic

  type Element_Type is digits <>;
  type Index_Type is (<>);
  type Array_Type is array(Index_Type range <>) of Element_Type;

package Shell_Sort is

  procedure Sort(Item : in out Array_Type);

end Shell_Sort;</lang> <lang ada>package body Shell_Sort is

  ----------
  -- Sort --
  ----------
  procedure Sort (Item : in out Array_Type) is
     Increment : Natural := Index_Type'Pos(Item'Last) / 2;
     J : Index_Type;
     Temp : Element_Type;
  begin
     while Increment > 0 loop
        for I in Index_Type'Val(Increment) .. Item'Last loop
           J := I;
           Temp := Item(I);
           while J > Index_Type'val(Increment) and then Item (Index_Type'Val(Index_Type'Pos(J) - Increment)) > Temp loop
              Item(J) := Item (Index_Type'Val(Index_Type'Pos(J) - Increment));
              J := Index_Type'Val(Index_Type'Pos(J) - Increment);
           end loop;
           Item(J) := Temp;
        end loop;
        if Increment = 2 then
           Increment := 1;
        else
           Increment := Increment * 5 / 11;
        end if;
     end loop;
  end Sort;

end Shell_Sort;</lang>

ALGOL 68

Translation of: python
Works with: ALGOL 68 version Standard - no extensions to language used
Works with: ALGOL 68G version Any - tested with release mk15-0.8b.fc9.i386
Works with: ELLA ALGOL 68 version Any (with appropriate job cards) - tested with release 1.8.8d.fc9.i386

<lang algol68>MODE TYPE = CHAR;

PROC in place shell sort = (REF[]TYPE seq)REF[]TYPE:(

   INT inc := ( UPB seq + LWB seq + 1 ) OVER 2;
   WHILE inc NE 0 DO
       FOR index FROM LWB seq TO UPB seq DO
           INT i := index;
           TYPE el = seq[i];
           WHILE ( i  - LWB seq >= inc | seq[i - inc] > el | FALSE ) DO
               seq[i] := seq[i - inc];
               i -:= inc
           OD;
           seq[i] := el
       OD;
       inc := IF inc = 2 THEN 1 ELSE ENTIER(inc * 5 / 11) FI
   OD;
   seq

);

PROC shell sort = ([]TYPE seq)[]TYPE:

 in place shell sort(LOC[LWB seq: UPB seq]TYPE:=seq);

[]TYPE char array data = "big fjords vex quick waltz nymph"; print((shell sort(char array data), new line))</lang> Output:

     abcdefghiijklmnopqrstuvwxyz

AutoHotkey

ahk forum: discussion <lang AutoHotkey>MsgBox % ShellSort("") MsgBox % ShellSort("xxx") MsgBox % ShellSort("3,2,1") MsgBox % ShellSort("dog,000000,xx,cat,pile,abcde,1,cat,zz,xx,z") MsgBox % ShellSort("12,11,10,9,8,4,5,6,7,3,2,1,10,13,14,15,19,17,18,16,20,10")

ShellSort(var) {  ; SORT COMMA SEPARATED LIST

  StringSplit a, var, `,                ; make array (length = a0)
  inc := a0
  While inc:=round(inc/2.2)             ; geometric gap sequence
     Loop % a0-inc {                    ; insertion sort:
        i := A_Index+inc, t := a%i%, j := i, k := j-inc
        While j > inc && a%k% > t
           a%j% := a%k%, j := k, k -= inc
        a%j% := t
     }
  Loop % a0                             ; construct string from sorted array
     s .= "," . a%A_Index%
  Return SubStr(s,2)                    ; drop leading comma

}</lang>

AWK

Translation of: Fortran

<lang awk>{

 line[NR] = $0

} END { # sort it with shell sort

 increment = int(NR / 2)
 while ( increment > 0 ) {
   for(i=increment+1; i <= NR; i++) {
     j = i
     temp = line[i]
     while ( (j >= increment+1) && (line[j-increment] > temp) ) {

line[j] = line[j-increment] j -= increment

     }
     line[j] = temp
   }
   if ( increment == 2 )
     increment = 1
   else 
     increment = int(increment*5/11)
 }
 #print it
 for(i=1; i <= NR; i++) {
   print line[i]
 }

}</lang>

C

This implementation uses an array of pre-defined increments <lang c>#include <ansi_c.h>

  1. define ARRAYSIZE 100000 /* or whatever */

void shellsort (int a[], int length);

int main (int argc, char *argv[]) {

 int intArray[ARRAYSIZE], i;
 for(i=0; i<ARRAYSIZE; i++)
   intArray[i] = rand();
 shellsort(intArray, ARRAYSIZE);

}

void shellsort (int a[], int length) {

 int i, j, k, temp, increment;
 static int incSequence[] = {412771, 165103, 66041, 26417, 10567,
                             4231, 1693, 673, 269, 107, 43, 17, 7, 3, 1};
 for (k = 0; k < sizeof(incSequence)/sizeof(int); k++)
 {
   if (incSequence[k]*2 > length) continue;
   increment = incSequence[k];
   for (i=increment; i < length; i++)
   {
     temp = a[i];
     for (j = i - increment; j >= 0; j -= increment)
     {
       if (a[j] <= temp) break;
       a[j + increment] = a[j];
     }
     a[j + increment] = temp;
   }
 }

}</lang>

Common Lisp

<lang lisp>(defun gap-insertion-sort (array predicate gap)

 (let ((length (length array)))
   (if (< length 2) array
     (do ((i 1 (1+ i))) ((eql i length) array)
       (do ((x (aref array i))
            (j i (- j gap)))
           ((or (< (- j gap) 0)
                (not (funcall predicate x (aref array (1- j)))))
            (setf (aref array j) x))
         (setf (aref array j) (aref array (- j gap))))))))

(defconstant +gaps+

 '(1750 701 301 132 57 23 10 4 1)
 "The best sequence of gaps, according to Marcin Ciura.")

(defun shell-sort (array predicate &optional (gaps +gaps+))

 (assert (eql 1 (car (last gaps))) (gaps)
   "Last gap of ~w is not 1." gaps)
 (dolist (gap gaps array)
   (gap-insertion-sort array predicate gap)))</lang>

D

From the Python version, uses Phobos of D 1. <lang d>import std.stdio: writefln;

void shell(T)(T[] seq) {

   int inc = seq.length / 2;
   while (inc) {
       foreach (i, el; seq) {
           while (i >= inc && seq[i - inc] > el) {
               seq[i] = seq[i - inc];
               i -= inc;
           }
           seq[i] = el;
       }
       inc = inc == 2 ? 1 : cast(int)(inc * 5.0 / 11);
   }

}

void main() {

   int[] data = [22, 7, 2, -5, 8, 4].dup;
   shell(data);
   writefln(data); // [-5, 2, 4, 7, 8, 22]

}</lang>

E

Translation of: Python

<lang e>/** Shell sort (in-place) */ def shellSort(array) {

   var inc := array.size() // 2
   while (inc.aboveZero()) {
       for var i => a in array {
           while (i >= inc && (def b := array[i - inc]) > a) {
               array[i] := b
               i -= inc
           }
           array[i] := a
       }
       inc := if (inc <=> 2) { 1 } else { (inc * 5.0 / 11).floor() }
   }

}</lang>

Forth

Works with: GNU Forth

<lang forth>defer less? ' < is less?

shell { array len -- }
 1 begin dup len u<= while 2* 1+ repeat { gap }
 begin gap 2/ dup to gap while
   len gap do
     array i cells +
     dup @ swap         ( temp last )
     begin gap cells -
           array over u<=
     while 2dup @ less?
     while dup gap cells + over @ swap !
     repeat then
     gap cells + !
   loop
 repeat ;

create array 8 , 1 , 4 , 2 , 10 , 3 , 7 , 9 , 6 , 5 ,

array 10 shell array 10 cells dump</lang>

Fortran

Works with: Fortran version 90 and later

<lang fortran>MODULE sort

CONTAINS

SUBROUTINE Shell_Sort(a)

 IMPLICIT NONE
 INTEGER :: i, j, increment
 REAL :: temp
 REAL, INTENT(in out) :: a(:)
 increment = SIZE(a) / 2
 DO WHILE (increment > 0)
     DO i = increment+1, SIZE(a)
        j = i
        temp = a(i)
        DO WHILE (j >= increment+1 .AND. a(j-increment) > temp)
           a(j) = a(j-increment)
           j = j - increment
        END DO
        a(j) = temp
     END DO
     IF (increment == 2) THEN
  	  increment = 1
     ELSE
        increment = increment * 5 / 11
     END IF      
 END DO

END SUBROUTINE Shell_Sort

END MODULE sort

PROGRAM Shellsort

USE sort

 IMPLICIT NONE
 REAL :: array(1000)
    
 CALL RANDOM_SEED
 CALL RANDOM_NUMBER(array)

 WRITE (*,*) "Unsorted array"
 WRITE (*,*) array
 WRITE (*,*) 
 CALL Shell_Sort(array)
 WRITE (*,*) "Sorted array"
 WRITE (*,*) array
 

END PROGRAM Shellsort</lang>

Haskell

Adapted version from [2]

<lang haskell>import Data.List

shellSort xs = foldr (invColumnize (map (foldr insert []))) xs gaps

 where gaps = takeWhile (< length xs) $ iterate (succ.(3*)) 1
       invColumnize f k = concat. transpose. f. transpose
                          . takeWhile (not.null). unfoldr (Just. splitAt k)</lang>

Java

Translation of: Fortran

This method will sort in place. If you want to preserve your unsorted array, use a copy of the array as an argument to this method. <lang java>public static void shell(int[] a) { int increment = a.length / 2; while (increment > 0) { for (int i = increment; i < a.length; i++) { int j = i; int temp = a[i]; while (j >= increment && a[j - increment] > temp) { a[j] = a[j - increment]; j -= increment; } a[j] = temp; } if (increment == 2) { increment = 1; } else { increment *= (5.0 / 11); } } }</lang>

Lisaac

<lang Lisaac>Section Header

+ name := SHELL_SORT;

- external := `#include <time.h>`;

Section Public

- main <- (

 + a : ARRAY[INTEGER];
 a := ARRAY[INTEGER].create 0 to 100;
 `srand(time(NULL))`;
 0.to 100 do { i : INTEGER;
   a.put `rand()`:INTEGER to i;
 };
 shell a;
 a.foreach { item : INTEGER;
   item.print;
   '\n'.print;
 };

);

- shell a : ARRAY[INTEGER] <- (

 + lower, length, increment, temp : INTEGER;
 lower := a.lower;
 length := a.upper - lower + 1;
 increment := length;
 {
   increment := increment / 2;
   increment > 0
 }.while_do {
   increment.to (length - 1) do { i : INTEGER; + j : INTEGER;
     temp := a.item(lower + i);
     j := i - increment;
     { (j >= 0) && { a.item(lower + j) > temp } }.while_do {
       a.put (a.item(lower + j)) to (lower + j + increment);
       j := j - increment;
     };
     a.put temp to (lower + j + increment);
   };
 };

);</lang>

OCaml

Translation of: C

<lang ocaml>let shellsort a =

 let len = Array.length a in
 let incSequence = [| 412771; 165103; 66041; 26417; 10567;
                      4231; 1693; 673; 269; 107; 43; 17; 7; 3; 1 |] in

 Array.iter (fun increment ->
   if (increment * 2) <= len then
     for i = increment to pred len do
       let temp = a.(i) in
       let rec loop j =
         if j < 0 || a.(j) <= temp then (j)
         else begin
           a.(j + increment) <- a.(j);
           loop (j - increment)
         end
       in
       let j = loop (i - increment) in
       a.(j + increment) <- temp;
     done;
 ) incSequence;
</lang>

and the main: <lang ocaml>let () =

 let arraysize = 1000 in  (* or whatever *)
 Random.self_init();
 let intArray =
   Array.init arraysize (fun _ -> Random.int 4000)
 in
 shellsort intArray;
 Array.iter (Printf.printf " %d") intArray;
 print_newline();
</lang>

Perl

Translation of: Java

<lang perl>use strict; use warnings; sub shell { # (int[a])

   my @iary = @_;
   my $inc = int(($#iary+1) / 2);
   while ($inc > 0) {
       foreach my $i (0 .. $#iary) {
           my $temp = $iary[$i];
           while ($i >= $inc && $iary[$i-$inc] > $temp) {
               $iary[$i] = $iary[$i-$inc];
               $i -= $inc;
           }
           $iary[$i] = $temp;
       }    
       if ($inc == 2) {
           $inc = 1;
       } else { 
          $inc *= (5.0 / 11);
          $inc = int($inc);
       }
   }
   return @iary;

} my @data = (22, 7, 2, -5, 8, 4); print "input =@data\n"; @data=shell(@data); print "output=@data\n"; # [-5, 2, 4, 7, 8, 22]</lang>

Python

Translation of: Java

This method sorts in place. If you want to preserve your unsorted list, copy it first. <lang python>def shell(seq):

   inc = len(seq) // 2
   while inc:
       for i, el in enumerate(seq):
           while i >= inc and seq[i - inc] > el:
               seq[i] = seq[i - inc]
               i -= inc
           seq[i] = el
       inc = 1 if inc == 2 else int(inc * 5.0 / 11)

data = [22, 7, 2, -5, 8, 4] shell(data) print data # [-5, 2, 4, 7, 8, 22]</lang>

Ruby

Translation of: Java

This method sorts in place. If you want to preserve your unsorted list, copy it first. <lang ruby>class Array

 def shellsort!
   inc = length / 2
   while inc != 0
     each_with_index do |el, i|
       while i >= inc and self[i - inc] > el
         self[i] = self[i - inc]
         i -= inc
       end
       self[i] = el
     end
     inc = (inc == 2 ? 1 : (inc * 5.0 / 11).to_i)
   end
 end

end

data = [22, 7, 2, -5, 8, 4] data.shellsort! p data # [-5, 2, 4, 7, 8, 22]</lang>

Tcl

<lang tcl>package require Tcl 8.5

proc shellsort {m} {

   set len [llength $m]
   set inc [expr {$len / 2}]
   while {$inc > 0} {
       for {set i $inc} {$i < $len} {incr i} {
           set j $i
           set temp [lindex $m $i]
           while {$j >= $inc && [set val [lindex $m [expr {$j - $inc}]]] > $temp} {
               lset m $j $val
               incr j -$inc
           }
           lset m $j $temp
       }
       set inc [expr {$inc == 2 ? 1 : $inc * 5 / 11}]
   }
   return $m

}

puts [shellsort {8 6 4 2 1 3 5 7 9}] ;# => 1 2 3 4 5 6 7 8 9</lang>