Knuth shuffle

From Rosetta Code
Revision as of 16:02, 10 January 2010 by 83.77.106.249 (talk) (added factor example)
Task
Knuth shuffle
You are encouraged to solve this task according to the task description, using any language you may know.

Implement the Knuth shuffle (aka the Fisher-Yates shuffle) for an integer array (or, if possible, an array of any type). The Knuth shuffle is used to create a random permutation of an array.

Ada

This implementation is a generic shuffle routine, able to shuffle an array of any type. <lang Ada> generic

  type Element_Type is private;
  type Array_Type is array (Positive range <>) of Element_Type;
  

procedure Generic_Shuffle (List : in out Array_Type); </lang> <lang Ada> with Ada.Numerics.Discrete_Random;

procedure Generic_Shuffle (List : in out Array_Type) is

  package Discrete_Random is new Ada.Numerics.Discrete_Random(Result_Subtype => Integer);
  use Discrete_Random;
  K : Integer;
  G : Generator;
  T : Element_Type;

begin

  Reset (G);
  for I in reverse List'Range loop
     K := (Random(G) mod I) + 1;
     T := List(I);
     List(I) := List(K);
     List(K) := T;
  end loop;

end Generic_Shuffle; </lang> An example using Generic_Shuffle. <lang Ada> with Ada.Text_IO; with Generic_Shuffle;

procedure Test_Shuffle is

  type Integer_Array is array (Positive range <>) of Integer;
  Integer_List : Integer_Array
    := (1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18);
  procedure Integer_Shuffle is new Generic_Shuffle(Element_Type => Integer,
                                                   Array_Type => Integer_Array);

begin

  for I in Integer_List'Range loop
     Ada.Text_IO.Put(Integer'Image(Integer_List(I)));
  end loop;
  Integer_Shuffle(List => Integer_List);
  Ada.Text_IO.New_Line;
  for I in Integer_List'Range loop
     Ada.Text_IO.Put(Integer'Image(Integer_List(I)));
  end loop;

end Test_Shuffle; </lang>

AutoHotkey

ahk forum: discussion <lang AutoHotkey>MsgBox % shuffle("1,2,3,4,5,6,7,8,9") MsgBox % shuffle("1,2,3,4,5,6,7,8,9")

shuffle(list) {  ; shuffle comma separated list, converted to array

  StringSplit a, list, `,               ; make array (length = a0)
  Loop % a0-1 {
     Random i, A_Index, a0              ; swap item 1,2... with a random item to the right of it
     t := a%i%, a%i% := a%A_Index%, a%A_Index% := t
  }
  Loop % a0                             ; construct string from sorted array
     s .= "," . a%A_Index%
  Return SubStr(s,2)                    ; drop leading comma

}</lang>

BASIC

<lang qbasic> RANDOMIZE TIMER

DIM unShuffled(51) AS INTEGER DIM Shuffled(51) AS INTEGER DIM L0 AS LONG, card AS LONG

PRINT "before:" FOR L0 = 0 TO 51

   unShuffled(L0) = L0
   PRINT LTRIM$(STR$(unShuffled(L0))); " ";

NEXT

FOR L0 = 51 TO 0 STEP -1

   card = INT(RND * (L0 + 1))
   Shuffled(L0) = unShuffled(card)
   IF card <> L0 THEN unShuffled(card) = unShuffled(L0)

NEXT

PRINT : PRINT : PRINT "after:" FOR L0 = 0 TO 51

   PRINT LTRIM$(STR$(Shuffled(L0))); " ";

NEXT </lang>

Sample output:

before:
0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29
30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51

after:
37 5 4 12 29 25 34 20 40 23 31 1 14 6 18 15 50 38 45 0 30 28 24 26 21 11 16 41 2
 42 48 35 36 49 7 22 32 44 33 43 9 13 8 51 17 39 27 47 3 10 46 19

C

Works with: gcc

This shuffles any "object"; it imitates qsort in the syntax.

<lang c>#include <stdlib.h>

  1. include <string.h>

inline int rrand(int m) {

 return (int)((double)m * ( rand() / (RAND_MAX+1.0) ));

}

void shuffle(void *obj, size_t nmemb, size_t size) {

 void *temp = malloc(size);
 size_t n = nmemb;
 while ( n > 1 ) {
   size_t k = rrand(n--);
   memcpy(temp, obj + n*size, size);
   memcpy(obj + n*size, obj + k*size, size);
   memcpy(obj + k*size, temp, size);
 }
 free(temp);

}</lang>

C++

Compiler: g++ (version 4.3.2 20081105 (Red Hat 4.3.2-7))

<lang cpp>#include <cstdlib>

  1. include <algorithm>
  2. include <iterator>

template<typename RandomAccessIterator> void knuthShuffle(RandomAccessIterator begin, RandomAccessIterator end) {

 for(unsigned int n = end - begin - 1; n >= 1; --n) {
   unsigned int k = rand() % (n + 1);
   if(k != n) {
     std::iter_swap(begin + k, begin + n);
   }
 }

}</lang>

C#

<lang csharp>public static void KnuthShuffle<T>(T[] array) {

   System.Random random = new System.Random();
   for (int i = 0; i < array.Length; i++)
   {
       int j = random.Next(array.Length);
       T temp = array[i]; array[i] = array[j]; array[j] = temp;
   }

}</lang>

Clojure

<lang lisp>(defn shuffle [vect]

 (reduce (fn [v i] (let [r (rand-int i)]
                     (assoc v i (v r) r (v i)))
         vect (range (dec (count vect)) 1 -1)))</lang>

This works by generating a sequence of end-indices from n-1 to 1, then reducing that sequence (starting with the original vector) through a function that, given a vector and end-index, performs a swap between the end-index and some random index less than the end-index.

Common Lisp

<lang lisp>(defun nshuffle (sequence)

 (loop for i from (length sequence) downto 2
       do (rotatef (elt sequence (random i))
                   (elt sequence (1- i))))
 sequence)</lang>

This operates on arbitrary sequences, but will be inefficient applied to a list as opposed to a vector. Dispatching on type, and using an intermediate vector to hold the contents of list can make both cases more efficient (since the array specific case can use aref rather than elt):

<lang lisp>(defun nshuffle (sequence)

 (etypecase sequence
   (list  (nshuffle-list sequence))
   (array (nshuffle-array sequence))))

(defun nshuffle-list (list)

 "Shuffle the list using an intermediate vector."
 (let ((array (nshuffle-array (coerce list 'vector))))
   (declare (dynamic-extent array))
   (map-into list 'identity array)))

(defun nshuffle-array (array)

 (loop for i from (length array) downto 2
       do (rotatef (aref array (random i))
                   (aref array (1- i)))
       finally (return array)))</lang>

E

<lang e>def shuffle(array, random) {

   for bound in (2..(array.size())).descending() {
       def i := random.nextInt(bound)
       def swapTo := bound - 1
       def t := array[swapTo]
       array[swapTo] := array[i]
       array[i] := t
   }

}</lang>

<lang e>? def arr := [1,2,3,4,5,6,7,8,9,10].diverge()

  1. value: [1, 2, 3, 4, 5, 6, 7, 8, 9, 10].diverge()

? shuffle(arr, entropy) ? arr

  1. value: [4, 5, 2, 9, 7, 8, 1, 3, 6, 10].diverge()</lang>

Factor

There is a randomize word already in the standard library. Implementation: <lang factor>: randomize ( seq -- seq )

   dup length [ dup 1 > ]
   [ [ iota random ] [ 1 - ] bi [ pick exchange ] keep ]
   while drop ;</lang>

Forth

<lang forth>include random.fs

shuffle ( deck size -- )
 2 swap do
   dup i random cells +
   over @ over @  swap
   rot  ! over !
   cell+
 -1 +loop drop ;
.array 0 do dup @ . cell+ loop drop ;

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

deck 10 2dup shuffle .array</lang>

Fortran

Works with: Fortran version 90 and later

<lang fortran>program Knuth_Shuffle

 implicit none
 integer, parameter :: reps = 1000000
 integer :: i, n
 integer, dimension(10) :: a, bins = 0, initial = (/ (n, n=1,10) /) 
 do i = 1, reps
   a = initial
	call Shuffle(a)
   where (a == initial) bins = bins + 1  ! skew tester
 end do
 write(*, "(10(i8))") bins

! prints 100382 100007 99783 100231 100507 99921 99941 100270 100290 100442

contains

subroutine Shuffle(a)

 integer, intent(inout) :: a(:)
 integer :: i, randpos, temp
 real :: r
 do i = size(a), 2, -1
   call random_number(r)
   randpos = int(r * i) + 1
   temp = a(randpos)
   a(randpos) = a(i)
   a(i) = temp
 end do
    

end subroutine Shuffle

end program Knuth_Shuffle</lang>

F#

Allows a shuffle of arrays of arbitrary items. Requires 2010 beta of F#. Lazily returns a sequence.

This is the original Fisher-Yates shuffle as described by the link: <lang fsharp>open System open System let FisherYatesShuffle (initialList : array<'a>) =

   let availableFlags = Array.init initialList.Length (fun i -> (i, true))
                                                                   // Which items are available and their indices
   let rnd = new Random()  
   let nextItem nLeft =
       let nItem = rnd.Next(0, nLeft)                              // Index out of available items
       let index =                                                 // Index in original deck
           availableFlags                                          // Go through available array
           |> Seq.filter (fun (ndx,f) -> f)                        // and pick out only the available tuples
           |> Seq.nth nItem                                        // Get the one at our chosen index
           |> fst                                                  // and retrieve it's index into the original array
       availableFlags.[index] <- (index, false)                    // Mark that index as unavailable
       initialList.[index]                                         // and return the original item
   seq {(initialList.Length) .. -1 .. 1}                           // Going from the length of the list down to 1
   |> Seq.map (fun i -> nextItem i)                                // yield the next item

</lang> Here's the modified Knuth shuffle which shuffles the original array in place <lang fsharp>let KnuthShuffle (lst : array<'a>) =

   let Swap i j =                                                  // Standard swap
       let item = lst.[i]
       lst.[i] <- lst.[j]
       lst.[j] <- item
   let rnd = new Random()
   let ln = lst.Length
   [0..(ln - 2)]                                                   // For all indices except the last
   |> Seq.iter (fun i -> Swap i (rnd.Next(i, ln)))                 // swap th item at the index with a random one following it (or itself)
   lst                                                             // Return the list shuffled in place</lang>

Example: <lang fsharp>> KnuthShuffle [| "Darrell"; "Marvin"; "Doug"; "Greg"; "Sam"; "Ken" |];; val it : string array = [|"Marvin"; "Doug"; "Sam"; "Darrell"; "Ken"; "Greg"|] </lang>

Haskell

<lang Haskell>import System.Random import Data.List import Control.Monad import Control.Arrow

mkRands = mapM (randomRIO.(,)0 ). enumFromTo 1. pred

replaceAt :: Int -> a -> [a] -> [a] replaceAt i c = uncurry((.((c:).drop 1)).(++)). splitAt i

swapElems :: (Int, Int) -> [a] -> [a] swapElems (i,j) xs | i==j = xs

                  | otherwise = replaceAt j (xs!!i) $ replaceAt i (xs!!j) xs

knuthShuffle :: [a] -> IO [a] knuthShuffle xs =

 liftM (foldr swapElems xs. zip [1..]) (mkRands (length xs))</lang>

Examples of use:

*Main> knuthShuffle  ['a'..'k']
"bhjdgfciake"

*Main> knuthShuffle $ map(ap (,)(+10)) [0..9]
[(0,10),(8,18),(2,12),(3,13),(9,19),(4,14),(7,17),(1,11),(6,16),(5,15)]

Function for showing intermediate results: <lang Haskell>knuthShuffleProcess :: (Show a) => [a] -> IO () knuthShuffleProcess =

  (mapM_ print. reverse =<<). ap (fmap. (. zip [1..]). scanr swapElems) (mkRands. length)</lang>

Detailed output example:

*Main> knuthShuffleProcess  ['a'..'k']
"abcdefghijk"
"abckefghijd"
"jbckefghiad"
"jbckeighfad"
"jbckeihgfad"
"jbhkeicgfad"
"jbhiekcgfad"
"jbeihkcgfad"
"ibejhkcgfad"
"iebjhkcgfad"
"iebjhkcgfad"

An imperative implementation using arrays and the ST monad:

<lang haskell>import Data.Array.ST import Data.STRef import Control.Monad import Control.Monad.ST import Control.Arrow import System.Random

shuffle :: RandomGen g => [a] -> g -> ([a], g) shuffle list g = runST $ do

   r <- newSTRef g
   let rand range = liftM (randomR range) (readSTRef r) >>=
           runKleisli (second (Kleisli $ writeSTRef r) >>> arr fst)
   a <- newAry (1, len) list
   forM_ [len, len - 1 .. 2] $ \n -> do
       k <- rand (1, n)
       liftM2 (,) (readArray a k) (readArray a n) >>=
          runKleisli (Kleisli (writeArray a n) *** Kleisli (writeArray a k))
   liftM2 (,) (getElems a) (readSTRef r)
 where len = length list
       newAry :: (Int, Int) -> [a] -> ST s (STArray s Int a)
       newAry = newListArray</lang>

J

<lang j>KS=:{~ (2&{.@[ {`(|.@[)`]} >@])/@(,~(,.?@>:))@i.@#</lang> The input array is transformed to a rectangular array of indexes. By doing this all kinds of arrays can serve as input (see examples below). The process is imitated by using using a fold, swapping elements in a restricted part of this index-array in each fold step. <lang j>proces J

fold swap transform array   <==>  f / g y</lang>   

Example of a transformed input: <lang j>(,~(,.?@>:))@i.@# 1+i.6 0 0 0 0 0 0 1 1 0 0 0 0 2 0 0 0 0 0 3 2 0 0 0 0 4 3 0 0 0 0 5 0 0 0 0 0 0 1 2 3 4 5</lang> The last row is the index-array that has to be shuffled. The other rows have valid indexes in the first two columns. The second column has a randomized value <= value first column.

The index-swapping is done by the part: <lang j>2&{.@[ {`(|.@[)`]} >@]</lang> Finally, the shuffled indexes select elements from the original array. <lang j>input { ~ shuffled indexes</lang> Examples:<lang j>]A=: 5+i.9 5 6 7 8 9 10 11 12 13</lang> Shuffle: <lang j>KS A 13 10 7 5 11 9 8 6 12</lang>Input <lang j>]M=: /:~(1 2 3,:2 3 4),(11 2 3,: 0 11 2),(1 1 1,:1 0),:1 1 1,:1 0 1

1  1 1
1  0 0
1  1 1
1  0 1
1  2 3
2  3 4

11 2 3

0 11 2</lang>Shuffle

<lang j>KS M 11 2 3

0 11 2
1  1 1
1  0 1
1  1 1
1  0 0
1  2 3
2  3 4</lang>Input

<lang j>]L=:'aA';'bbB';'cC%$';'dD@' +--+---+----+---+ |aA|bbB|cC%$|dD@| +--+---+----+---+</lang>Shuffle <lang j>KS L +--+----+---+---+ |aA|cC%$|dD@|bbB| +--+----+---+---+</lang> In J the shuffling of an arbitrary array can easily be implemented by the phrase ( ref http://www.jsoftware.com/jwiki/JPhrases/RandomNumbers ): <lang j>({~?~@#)</lang> Applied on the former examples: <lang j>({~?~@#) A 8 7 13 6 10 11 5 9 12

  ({~?~@#) M
1  1 1
1  0 1
1  2 3
2  3 4

11 2 3

0 11 2
1  1 1
1  0 0
  ({~?~@#) L

+----+---+--+---+ |cC%$|bbB|aA|dD@| +----+---+--+---+</lang>

Java

<lang java>import java.util.Random;

public static final Random gen = new Random();

// version for array of ints public static void shuffle (int[] array) {

   int n = array.length;
   while (n > 1) {
       int k = gen.nextInt(n--); //decrements after using the value
       int temp = array[n];
       array[n] = array[k];
       array[k] = temp;
   }

} // version for array of references public static void shuffle (Object[] array) {

   int n = array.length;
   while (n > 1) {
       int k = gen.nextInt(n--); //decrements after using the value
       Object temp = array[n];
       array[n] = array[k];
       array[k] = temp;
   }

}</lang>

JavaScript

Translation of: Java

<lang javascript>function knuth_shuffle(a) {

   var n = a.length;
   var r, temp;
   while (n > 1) {
       r = Math.floor(n * Math.random());
       n--;
       temp = a[n];
       a[n] = a[r];
       a[r] = temp;
   }
   return a;

}

var res = {'1,2,3': 0, '1,3,2': 0, '2,1,3': 0, '2,3,1': 0, '3,1,2': 0, '3,2,1': 0};

for (var i = 0; i < 100000; i++)

   res[ knuth_shuffle([1,2,3]).join(',') ] ++;

for (var key in res)

   print(key + "\t" + res[key]);</lang>

results in:

1,2,3   16619
1,3,2   16614
2,1,3   16752
2,3,1   16959
3,1,2   16460
3,2,1   16596

<lang logo>to swap :i :j :a

 localmake "t item :i :a
 setitem :i :a item :j :a
 setitem :j :a :t

end to shuffle :a

 for [i [count :a] 2] [swap 1 + random :i :i :a]

end

make "a {1 2 3 4 5 6 7 8 9 10} shuffle :a show :a</lang>

Lua

<lang lua>function table.shuffle(t)

 local n = #t
 while n > 1 do
   local k = math.random(n)
   t[n], t[k] = t[k], t[n]
   n = n - 1
 end

 return t

end math.randomseed( os.time() ) a = {1, 2, 3, 4, 5, 6, 7, 8, 9, 10} table.shuffle(a) for i,v in ipairs(a) do print(i,v) end</lang>

M4

<lang M4>divert(-1) define(`randSeed',141592653) define(`rand_t',`eval(randSeed^(randSeed>>13))') define(`random',

  `define(`randSeed',eval((rand_t^(rand_t<<18))&0x7fffffff))randSeed')

define(`for',

  `ifelse($#,0,``$0,
  `ifelse(eval($2<=$3),1,
  `pushdef(`$1',$2)$4`'popdef(`$1')$0(`$1',incr($2),$3,`$4')')')')

define(`set',`define(`$1[$2]',`$3')') define(`get',`defn($1[$2])') define(`new',`set($1,size,0)') define(`deck',

  `new($1)for(`x',1,$2,
        `set(`$1',x,x)')`'set(`$1',size,$2)')

define(`show',

  `for(`x',1,get($1,size),`get($1,x)`'ifelse(x,get($1,size),`',`, ')')')

define(`swap',`set($1,$2,get($1,$4))`'set($1,$4,$3)') define(`shuffle',

  `define(`s',get($1,size))`'for(`x',1,decr(s),
     `swap($1,x,get($1,x),eval(x+random%(s-x+1)))')')

divert

deck(`b',52) show(`b') shuffle(`b') show(`b')</lang>

Output:

1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23,
24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43,
44, 45, 46, 47, 48, 49, 50, 51, 52

6, 22, 33, 51, 35, 45, 16, 32, 7, 34, 10, 44, 5, 38, 43, 25, 29, 9, 37, 20, 21,
48, 24, 46, 8, 26, 41, 47, 49, 36, 14, 31, 15, 39, 12, 17, 13, 1, 3, 4, 27, 11,
28, 2, 19, 30, 42, 50, 18, 52, 40, 23

Mathematica

Usage of built-in function: <lang Mathematica>RandomSample[{1, 2, 3, 4, 5, 6}]</lang> Custom function: <lang Mathematica>Shuffle[input_List /; Length[input] >= 1] :=

Module[{indices = {}, allindices = Range[Length[input]]},
 Do[
  AppendTo[indices, 
    Complement[allindices, indices][[RandomInteger[{1, i}]]]];
  ,
  {i, Length[input], 1, -1}
  ];
 inputindices
 ]</lang>

Example: <lang Mathematica>Shuffle[{1, 2, 3, 4, 5, 6}]</lang>

Modula-3

<lang modula3>MODULE Shuffle EXPORTS Main;

IMPORT IO, Fmt, Random;

VAR a := ARRAY [0..9] OF INTEGER {1, 2, 3, 4, 5, 6, 7, 8, 9, 10};

PROCEDURE Shuffle(VAR a: ARRAY OF INTEGER) =

 VAR temp: INTEGER;
     n: INTEGER := NUMBER(a);

BEGIN

 WITH rand = NEW(Random.Default).init() DO
   WHILE n > 1 DO
     WITH k = rand.integer(0, n - 1) DO
       DEC(n);
       temp := a[n];
       a[n] := a[k];
       a[k] := temp;
     END;
   END;
 END;

END Shuffle;

BEGIN

 Shuffle(a);
 FOR i := FIRST(a) TO LAST(a) DO
   IO.Put(Fmt.Int(a[i]) & " ");
 END;
 IO.Put("\n");

END Shuffle.</lang> Output:

martin@thinkpad:~$ ./shuffle
9 2 7 3 6 8 4 5 1 10 
martin@thinkpad:~$ ./shuffle
1 7 8 10 5 4 6 3 9 2 

OCaml

<lang ocaml>let shuffle arr =

 for n = Array.length arr - 1 downto 1 do
   let k = Random.int (n + 1) in
   let temp = arr.(n) in
   arr.(n) <- arr.(k);
   arr.(k) <- temp
 done</lang>

Perl

<lang perl>sub shuffle

{my @a = @_;
 foreach my $n (1 .. $#a)
    {my $k = int rand $n + 1;
     $k == $n or @a[$k, $n] = @a[$n, $k];}
 return @a;}</lang>

Perl 6

Works with: Rakudo version #21 "Seattle"

<lang perl6>sub shuffle (@a is copy) {

   for 1 ..^ @a -> $n {
       my $k = (0 .. $n).pick;
       $k == $n or @a[$k, $n] = @a[$n, $k];
   }
   return @a;

}</lang>

PowerShell

Works with: PowerShell version 2

<lang powershell>function shuffle ($a) {

   $c = $a.Clone()  # make copy to avoid clobbering $a
   1..($c.Length - 1) | ForEach-Object {
       $i = Get-Random -Minimum $_ -Maximum $c.Length
       $c[$_-1],$c[$i] = $c[$i],$c[$_-1]
       $c[$_-1]  # return newly-shuffled value
   }
   $c[-1]  # last value

}</lang> This yields the values one by one instead of returning the array as a whole, so the rest of the pipeline can work on the values while shuffling is still in progress.

Python

Python's standard library function random.shuffle uses this algorithm. The function below is very similar: <lang python>from random import randrange

def knuth_shuffle(x):

   for i in reversed(range(1, len(x))):
       j = randrange(i + 1)
       x[i], x[j] = x[j], x[i]

x = list(range(10)) knuth_shuffle(x) print("shuffled:", x)</lang> Sample output

shuffled: [5, 1, 6, 0, 8, 4, 2, 3, 9, 7]

R

See also, the built-in function 'sample'.

Original Fisher-Yates version <lang r>fisheryatesshuffle <- function(n) {

 pool <- seq_len(n)
 a <- c()
 while(length(pool) > 0)
 {
    k <- sample.int(length(pool), 1)
    a <- c(a, pool[k])
    pool <- pool[-k]
 }
 a

}</lang> Knuth variation: <lang r>fisheryatesknuthshuffle <- function(n) {

  a <- seq_len(n)
  while(n >=2)
  {     
     k <- sample.int(n, 1)
     if(k != n)
     {
        temp <- a[k]
        a[k] <- a[n]
        a[n] <- temp
     }
     n <- n - 1
  }
  a

}

  1. Example usage:

fisheryatesshuffle(6) # e.g. 1 3 6 2 4 5 x <- c("foo", "bar", "baz", "quux") x[fisheryatesknuthshuffle(4)] # e.g. "bar" "baz" "quux" "foo"</lang>

Ruby

Translation of: Tcl

<lang ruby>class Array

 def knuth_shuffle!
   j = length
   i = 0
   while j > 1
     r = i + rand(j)
     self[i], self[r] = self[r], self[i]
     i += 1
     j -= 1
   end
   self
 end

end

r = Hash.new(0) 100_000.times do |i|

 a = [1,2,3].knuth_shuffle!
 r[a] += 1

end

r.keys.sort.each {|a| puts "#{a.inspect} => #{r[a]}"}</lang> results in

[1, 2, 3] => 16572
[1, 3, 2] => 16610
[2, 1, 3] => 16633
[2, 3, 1] => 16714
[3, 1, 2] => 16838
[3, 2, 1] => 16633

Scheme

Works with: PLT Scheme

<lang scheme> (define (swap vec i j)

 (let ([tmp (vector-ref vec i)])
   (vector-set! vec i (vector-ref vec j))
   (vector-set! vec j tmp)))

(define (shuffle vec)

 (for ((i (in-range (- (vector-length vec) 1) 0 -1)))
   (let ((r (random i)))
     (swap vec i r)))
 vec)

</lang>

> (shuffle (list->vector (for/list ((i (in-range 0 12))) i)))
#(11 9 7 5 10 6 2 0 1 3 8 4)

Smalltalk

Works with: GNU Smalltalk

<lang smalltalk>"The selector swap:with: is documented, but it seems not

implemented (GNU Smalltalk version 3.0.4); so here it is an implementation"

SequenceableCollection extend [

 swap: i with: j [
   |t|
   t := self at: i.
   self at: i put: (self at: j).
   self at: j put: t.
 ]

].

Object subclass: Shuffler [

 Shuffler class >> Knuth: aSequenceableCollection [
   |n k|
   n := aSequenceableCollection size.
   [ n > 1 ] whileTrue: [
     k := Random between: 1 and: n.
     aSequenceableCollection swap: n with: k.
     n := n - 1
   ]      
 ]

].</lang>

Testing

<lang smalltalk>"Test" |c| c := OrderedCollection new. c addAll: #( 1 2 3 4 5 6 7 8 9 ). Shuffler Knuth: c. c display.</lang>

Tcl

<lang tcl>proc knuth_shuffle lst {

  set j [llength $lst]
  for {set i 0} {$j > 1} {incr i;incr j -1} {
      set r [expr {$i+int(rand()*$j)}]
      set t [lindex $lst $i]
      lset lst $i [lindex $lst $r]
      lset lst $r $t
  }
  return $lst

}

% knuth_shuffle {1 2 3 4 5} 2 1 3 5 4 % knuth_shuffle {1 2 3 4 5} 5 2 1 4 3 % knuth_shuffle {tom dick harry peter paul mary} tom paul mary harry peter dick</lang> As a test of skewing (an indicator of a poor implementation) this code was used: <lang tcl>% for {set i 0} {$i<100000} {incr i} {

   foreach val [knuth_shuffle {1 2 3 4 5}] pos {pos0 pos1 pos2 pos3 pos4} {
       incr tots($pos) $val
   }

} % parray tots tots(pos0) = 300006 tots(pos1) = 300223 tots(pos2) = 299701 tots(pos3) = 299830 tots(pos4) = 300240</lang>

Ursala

This function works on lists of any type and length, including character strings.

<lang Ursala>shuffle = @iNX ~&l->r ^jrX/~&l ~&lK8PrC</lang>

test program: <lang Ursala>#cast %s

example = shuffle 'abcdefghijkl'</lang> output:

'keacfjlbdigh'

Vedit macro language

The shuffle routine in Playing Cards shuffles text lines in edit buffer. This example shuffles numeric registers #0 to #19.

The output will be inserted in current edit buffer.

<lang vedit>// Test main

  1. 90 = Time_Tick // seed for random number generator
  2. 99 = 20 // number of items in the array

IT("Before:") IN for (#100 = 0; #100 < #99; #100++) {

   #@100 = #100
   Num_Ins(#@100, LEFT+NOCR) IT(" ")

} IN

Call("SHUFFLE_NUMBERS")

IT("After:") IN for (#100 = 0; #100 < #99; #100++) {

   Num_Ins(#@100, LEFT+NOCR) IT(" ")

} IN Return

//-------------------------------------------------------------- // Shuffle numeric registers #0 to #nn // #99 = number of registers to shuffle (nn-1) //

SHUFFLE_NUMBERS:

for (#91 = #99-1; #91 > 0; #91--) {

   Call("RANDOM")
   #101 = Return_Value
   #102 = #@101; #@101 = #@91; #@91 = #102

} Return

//-------------------------------------------------------------- // Generate random numbers in range 0 <= Return_Value < #91 // #90 = Seed (0 to 0x7fffffff) // #91 = Scaling (0 to 0x10000) //

RANDOM:
  1. 92 = 0x7fffffff / 48271
  2. 93 = 0x7fffffff % 48271
  3. 90 = (48271 * (#90 % #92) - #93 * (#90 / #92)) & 0x7fffffff

Return ((#90 & 0xffff) * #91 / 0x10000)</lang>

Output:

Before:
0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 
After:
9 13 8 18 10 1 17 15 0 16 14 19 3 2 7 11 6 4 5 12