Tuesday 30 June 2015

Sorting algorithms/Bubble sort

360 Assembly

For maximum compatibility, this program uses only the basic instruction set.
*        Bubble Sort
BUBBLE   CSECT  
         USING  BUBBLE,R13,R12
SAVEAREA B      STM-SAVEAREA(R15) skip savearea
         DC     17F'0'
         DC     CL8'BUBBLE'
STM      STM    R14,R12,12(R13) save calling context
         ST     R13,4(R15)
         ST     R15,8(R13)
         LR     R13,R15         set addessability
         LA     R12,4095(R13)
         LA     R12,1(R12)
MORE     EQU    *
         LA     R8,0            R8=no more
         LA     R1,A            R1=Addr(A(I))
         LA     R2,2(R1)        R2=Addr(A(I+1))
         LA     R4,0            to start at 1
         LA     R6,1            increment
         L      R7,N            R7=N 
         BCTR   R7,0            R7=N-1
LOOP     BXH    R4,R6,ENDLOOP   for R4=1 to N-1
         LH     R3,0(R1)        R3=A(I)         
         CH     R3,0(R2)        A(I)::A(I+1)
         BNH    NOSWAP          if A(I)<=A(I+1) then goto NOSWAP
         LH     R9,0(R1)        R9=A(I)
         LH     R3,0(R2)        R3=A(I+1)
         STH    R3,0(R1)        A(I)=R3
         STH    R9,0(R2)        A(I+1)=R9
         LA     R8,1            R8=more
NOSWAP   EQU    *
         LA     R1,2(R1)        next A(I)
         LA     R2,2(R2)        next A(I+1)
         B      LOOP
ENDLOOP  EQU    *
         LTR    R8,R8
         BNZ    MORE
         LA     R3,A            R3=Addr(A(I))
         LA     R4,0            to start at 1
         LA     R6,1            increment
         L      R7,N          
PRNT     BXH    R4,R6,ENDPRNT   for R4=1 to N
         LH     R5,0(R3)        R5=A(I)
         CVD    R4,P            Store I to packed P
         UNPK   Z,P             Z=P
         MVC    C,Z             C=Z
         OI     C+L'C-1,X'F0'   ZAP SIGN
         MVC    BUFFER(4),C+12
         CVD    R5,P            Store A(I) to packed P
         UNPK   Z,P             Z=P
         MVC    C,Z             C=Z
         OI     C+L'C-1,X'F0'   ZAP SIGN
         MVC    BUFFER+10(6),C+10
         WTO    MF=(E,WTOMSG)
         LA     R3,2(R3)        next A(I)
         B      PRNT
ENDPRNT  EQU    *
         CNOP   0,4
         L      R13,4(0,R13)
         LM     R14,R12,12(R13) restore context
         XR     R15,R15         set return code to 0
         BR     R14             return to caller
N        DC     A((AEND-A)/2)   number of items in A, so N=F'80'
A        DC H'223',H'356',H'018',H'820',H'664',H'845',H'927',H'198' 8  
         DC H'261',H'802',H'523',H'982',H'242',H'192',H'913',H'230' 16 
         DC H'353',H'565',H'195',H'174',H'665',H'807',H'050',H'539' 24 
         DC H'436',H'249',H'848',H'010',H'006',H'794',H'100',H'433' 32 
         DC H'782',H'728',H'259',H'358',H'206',H'081',H'701',H'997' 40 
         DC H'880',H'520',H'780',H'293',H'861',H'942',H'735',H'091' 48 
         DC H'503',H'582',H'716',H'836',H'135',H'653',H'856',H'142' 56 
         DC H'919',H'498',H'303',H'894',H'536',H'211',H'539',H'986' 64 
         DC H'356',H'796',H'644',H'552',H'771',H'443',H'035',H'780' 72 
         DC H'474',H'278',H'332',H'949',H'351',H'282',H'558',H'904' 80 
AEND     EQU    *
P        DS     PL8             packed
Z        DS     ZL16            zoned
C        DS     CL16            character 
WTOMSG   CNOP   0,4
         DC     H'80'           length of WTO buffer
         DC     H'0'            must be binary zeroes
BUFFER   DC     80C' '
         LTORG  
         YREGS  
         END    BUBBLE
Output:
0001      000006
0002      000010
0003      000018
0004      000035
0005      000050
0006      000081
0007      000091
0008      000100
0009      000135
0010      000142
0011      000174
0012      000192
0013      000195
0014      000198
0015      000206
0016      000211
0017      000223
0018      000230
0019      000242
0020      000249
0021      000259
0022      000261
0023      000278
0024      000282
0025      000293
0026      000303
0027      000332
0028      000351
0029      000353
0030      000356
0031      000356
0032      000358
0033      000433
0034      000436
0035      000443
0036      000474
0037      000498
0038      000503
0039      000520
0040      000523
0041      000536
0042      000539
0043      000539
0044      000552
0045      000558
0046      000565
0047      000582
0048      000644
0049      000653
0050      000664
0051      000665
0052      000701
0053      000716
0054      000728
0055      000735
0056      000771
0057      000780
0058      000780
0059      000782
0060      000794
0061      000796
0062      000802
0063      000807
0064      000820
0065      000836
0066      000845
0067      000848
0068      000856
0069      000861
0070      000880
0071      000894
0072      000904
0073      000913
0074      000919
0075      000927
0076      000942
0077      000949
0078      000982
0079      000986
0080      000997

[edit]ACL2

(defun bubble (xs)
   (if (endp (rest xs))
       (mv nil xs)
       (let ((x1 (first xs))
             (x2 (second xs)))
         (if (> x1 x2)
             (mv-let (_ ys)
                     (bubble (cons x1 (rest (rest xs))))
                (declare (ignore _))
                (mv t (cons x2 ys)))
             (mv-let (has-changed ys)
                     (bubble (rest xs))
                (mv has-changed (cons x1 ys)))))))
 
(defun bsort-r (xs limit)
   (declare (xargs :measure (nfix limit)))
   (if (zp limit)
       xs
       (mv-let (has-changed ys)
               (bubble xs)
          (if has-changed
              (bsort-r ys (1- limit))
              ys))))
 
(defun bsort (xs)
   (bsort-r xs (len xs)))

[edit]ActionScript

public function bubbleSort(toSort:Array):Array
{
 var changed:Boolean = false;
 
 while (!changed)
 {
  changed = true;
 
  for (var i:int = 0; i < toSort.length - 1; i++)
  {
   if (toSort[i] > toSort[i + 1])
   {
    var tmp:int = toSort[i];
    toSort[i] = toSort[i + 1];
    toSort[i + 1] = tmp;
 
    changed = false;
   }
  }
 }
 
 return toSort;
}

[edit]Ada

Works withGCC version 4.1.2
generic
 type Element is private;
 with function "=" (E1, E2 : Element) return Boolean is <>;
 with function "<" (E1, E2 : Element) return Boolean is <>;
 type Index is (<>);
 type Arr is array (Index range <>) of Element;
procedure Bubble_Sort (A : in out Arr);
 
procedure Bubble_Sort (A : in out Arr) is
 Finished : Boolean;
 Temp     : Element;
begin
 loop
  Finished := True;
  for J in A'First .. Index'Pred (A'Last) loop
   if A (Index'Succ (J)) < A (J) then
    Finished := False;
    Temp := A (Index'Succ (J));
    A (Index'Succ (J)) := A (J);
    A (J) := Temp;
   end if;
  end loop;
  exit when Finished;
 end loop;
end Bubble_Sort;
 
--  Example of usage:
with Ada.Text_IO; use Ada.Text_IO;
with Bubble_Sort;
procedure Main is
 type Arr is array (Positive range <>) of Integer;
 procedure Sort is new
  Bubble_Sort
   (Element => Integer,
    Index   => Positive,
    Arr     => Arr);
 A : Arr := (1, 3, 256, 0, 3, 4, -1);
begin
 Sort (A);
 for J in A'Range loop
  Put (Integer'Image (A (J)));
 end loop;
 New_Line;
end Main;

[edit]ALGOL 68

MODE DATA = INT; 
PROC swap = (REF[]DATA slice)VOID:
(
  DATA tmp = slice[1];
  slice[1] := slice[2];
  slice[2] := tmp
);
 
PROC sort = (REF[]DATA array)VOID:
(
  BOOL sorted;
  INT shrinkage := 0;
  FOR size FROM UPB array - 1 BY -1 WHILE
    sorted := TRUE;
    shrinkage +:= 1;
    FOR i FROM LWB array TO size DO
      IF array[i+1] < array[i] THEN
        swap(array[i:i+1]);
        sorted := FALSE
      FI
    OD;
    NOT sorted
  DO SKIP OD
);
 
main:(
  [10]INT random := (1,6,3,5,2,9,8,4,7,0); 
 
  printf(($"Before: "10(g(3))l$,random));
  sort(random);
  printf(($"After: "10(g(3))l$,random))
)
Output:
 Before:  +1 +6 +3 +5 +2 +9 +8 +4 +7 +0
 After:  +0 +1 +2 +3 +4 +5 +6 +7 +8 +9

[edit]Arendelle

A function that returns a sorted version of it's x input
< x > ( i , 0 )

( sjt , 1; 0; 0 ) // swapped:0 / j:1 / temp:2

[ @sjt = 1 ,

 ( sjt , 0 )
 ( sjt[ 1 ] , +1 )

 ( i , 0 )

 [ @i < @x? - @sjt[ 1 ],

  { @x[ @i ] < @x[ @i + 1 ],

   ( sjt[ 2 ] , @x[ @i ] )
   ( x[ @i ] , @x[ @i + 1 ] )
   ( x[ @i + 1 ] , @sjt[ 2 ] )
   ( sjt , 1 )
  }

  ( i , +1 )
 ]
]

( return , @x )

[edit]AutoHotkey

var = 
(
dog
cat
pile
abc
)
MsgBox % bubblesort(var)
 
bubblesort(var) ; each line of var is an element of the array
{ 
  StringSplit, array, var, `n
  hasChanged = 1
  size := array0
  While hasChanged
  {
    hasChanged = 0
    Loop, % (size - 1)
    {
      i := array%A_Index%
      aj := A_Index + 1
      j := array%aj%
      If (j < i)
      {
        temp := array%A_Index%
        array%A_Index% := array%aj%
        array%aj% := temp
        hasChanged = 1
      } 
    }
  }
  Loop, % size
    sorted .= array%A_Index% . "`n"
  Return sorted
}

[edit]AWK

Sort the standard input and print it to standard output.
{ # read every line into an array
  line[NR] = $0
}
END { # sort it with bubble sort
  do {
    haschanged = 0
    for(i=1; i < NR; i++) {
      if ( line[i] > line[i+1] ) {
 t = line[i]
 line[i] = line[i+1]
 line[i+1] = t
 haschanged = 1
      }
    }
  } while ( haschanged == 1 )
  # print it
  for(i=1; i <= NR; i++) {
    print line[i]
  }
}
GNU awk contains built in functions for sorting, but POSIX Awk doesn't. Here is a generic bubble sort() implementation that you can copy/paste to your Awk programs. Adapted from the above example. Note that it is not possible to return arrays from Awk functions so the array is "edited in place". The extra parameters passed in function's argument list is a well known trick to define local variables.
 
# Test this example file from command line with:
#
#    awk -f file.awk /dev/null
#
# Code by Jari Aalto <jari.aalto A T cante net>
# Licensed and released under GPL-2+, see http://spdx.org/licenses
 
function alen(array,   dummy, len) {
    for (dummy in array)
        len++;
 
    return len;
}
 
function sort(array,   haschanged, len, tmp, i)
{
    len = alen(array)
    haschanged = 1
 
    while ( haschanged == 1 )
    {
        haschanged = 0
 
        for (i = 1; i <= len - 1; i++)
        {
            if (array[i] > array[i+1])
            {
                tmp = array[i]
                array[i] = array[i + 1]
                array[i + 1] = tmp
                haschanged = 1
            }
        }
    }
}
 
# An Example. Sorts array to order: b, c, z
{
    array[1] = "c"
    array[2] = "z"
    array[3] = "b"
    sort(array)
    print array[1] " " array[2] " " array[3]
    exit
}
 

[edit]BASIC

Works withQuickBasic version 4.5
Translation ofJava
Assume numbers are in a DIM of size "size" called "nums".
 
DO
  changed = 0
  FOR I = 1 TO size -1
    IF nums(I) > nums(I + 1) THEN
      tmp = nums(I)
      nums(I) = nums(I + 1)
      nums(I + 1) = tmp
      changed = 1
    END IF
  NEXT
LOOP WHILE(NOT changed)

[edit]BASIC256

Works withBASIC256
 
Dim a(11): ordered=false
print "Original set"
For n = 0 to 9
a[n]=int(rand*20+1)
print a[n]+", ";
next n
#algorithm
while ordered=false
   ordered=true
   For n = 0 to 9
      if a[n]> a[n+1] then
          x=a[n]
          a[n]=a[n+1]
          a[n+1]=x
          ordered=false
       end if
    next n
end while
 
print
print "Ordered set"
For n = 1 to 10
print a[n]+", ";
next n
 
Output:
(example)
Original set
2, 10, 17, 13, 20, 14, 3, 17, 16, 16, 
Ordered set
2, 3, 10, 13, 14, 16, 16, 17, 17, 20, 

[edit]BBC BASIC

The Bubble sort is very inefficient for 99% of cases. This routine uses a couple of 'tricks' to try and mitigate the inefficiency to a limited extent. Note that the array index is assumed to start at zero.
      DIM test(9)
      test() = 4, 65, 2, -31, 0, 99, 2, 83, 782, 1
      PROCbubblesort(test(), 10)
      FOR i% = 0 TO 9
        PRINT test(i%) ;
      NEXT
      PRINT
      END
 
      DEF PROCbubblesort(a(), n%)
      LOCAL i%, l%
      REPEAT
        l% = 0
        FOR i% = 1 TO n%-1
          IF a(i%-1) > a(i%) THEN
            SWAP a(i%-1),a(i%)
            l% = i%
          ENDIF
        NEXT
        n% = l%
      UNTIL l% = 0
      ENDPROC
Output:
       -31         0         1         2         2         4        65        83        99       782

[edit]C

#include <stdio.h>
 
void bubble_sort (int *a, int n) {
    int i, t, s = 1;
    while (s) {
        s = 0;
        for (i = 1; i < n; i++) {
            if (a[i] < a[i - 1]) {
                t = a[i];
                a[i] = a[i - 1];
                a[i - 1] = t;
                s = 1;
            }
        }
    }
}
 
int main () {
    int a[] = {4, 65, 2, -31, 0, 99, 2, 83, 782, 1};
    int n = sizeof a / sizeof a[0];
    int i;
    for (i = 0; i < n; i++)
        printf("%d%s", a[i], i == n - 1 ? "\n" : " ");
    bubble_sort(a, n);
    for (i = 0; i < n; i++)
        printf("%d%s", a[i], i == n - 1 ? "\n" : " ");
    return 0;
}
 
Output:
4 65 2 -31 0 99 2 83 782 1
-31 0 1 2 2 4 65 83 99 782

[edit]C++

Uses C++11. Compile with
g++ -std=c++11 bubble.cpp
#include <algorithm>
#include <iostream>
#include <iterator>
 
template <typename RandomAccessIterator>
void bubble_sort(RandomAccessIterator begin, RandomAccessIterator end) {
  bool swapped = true;
  while (begin != end-- && swapped) {
    swapped = false;
    for (auto i = begin; i != end; ++i) {
      if (*(i + 1) < *i) {
        std::iter_swap(i, i + 1);
        swapped = true;
      }
    }
  }
}
 
int main() {
  int a[] = {100, 2, 56, 200, -52, 3, 99, 33, 177, -199};
  bubble_sort(std::begin(a), std::end(a));
  copy(std::begin(a), std::end(a), std::ostream_iterator<int>(std::cout, " "));
  std::cout << "\n";
}
Output:
-199 -52 2 3 33 56 99 100 177 200

[edit]C#

Works withC# version 3.0+
using System;
using System.Collections.Generic;
 
namespace RosettaCode.BubbleSort
{
    public static class BubbleSortMethods
    {
        //The "this" keyword before the method parameter identifies this as a C# extension
        //method, which can be called using instance method syntax on any generic list,
        //without having to modify the generic List<T> code provided by the .NET framework.
        public static void BubbleSort<T>(this List<T> list) where T : IComparable
        {
            bool madeChanges;
            int itemCount = list.Count;
            do
            {
                madeChanges = false;
                itemCount--;
                for (int i = 0; i < itemCount; i++)
                {
                    if (list[i].CompareTo(list[i + 1]) > 0)
                    {
                        T temp = list[i + 1];
                        list[i + 1] = list[i];
                        list[i] = temp;
                        madeChanges = true;
                    }
                }
            } while (madeChanges);
        }
    }
 
    //A short test program to demonstrate the BubbleSort. The compiler will change the
    //call to testList.BubbleSort() into one to BubbleSortMethods.BubbleSort<T>(testList).
    class Program
    {
        static void Main()
        {
            List<int> testList = new List<int> { 3, 7, 3, 2, 1, -4, 10, 12, 4 };
            testList.BubbleSort();
            foreach (var t in testList) Console.Write(t + " ");
        }
    }
}

[edit]Clojure

Bubble sorts a Java ArrayList in place. Uses 'doseq' iteration construct with a short-circuit when a pass didn't produce any change, and within the pass, an atomic 'changed' variable that gets reset whenever a change occurs.
(ns bubblesort
  (:import java.util.ArrayList))
 
(defn bubble-sort
  "Sort in-place.
  arr must implement the Java List interface and should support
  random access, e.g. an ArrayList."
  ([arr] (bubble-sort compare arr))
  ([cmp arr]
     (letfn [(swap! [i j]
                    (let [t (.get arr i)]
                      (doto arr
                        (.set i (.get arr j))
                        (.set j t))))
             (sorter [stop-i]
                     (let [changed (atom false)]
                       (doseq [i (range stop-i)]
                         (if (pos? (cmp (.get arr i) (.get arr (inc i))))
                           (do
                             (swap! i (inc i))
                             (reset! changed true))))
                       @changed))]
       (doseq [stop-i (range (dec (.size arr)) -1 -1)
               :while (sorter stop-i)])
       arr)))
 
(println (bubble-sort (ArrayList. [10 9 8 7 6 5 4 3 2 1])))
Purely functional version working on Clojure sequences:
(defn- bubble-step
  "was-changed: whether any elements prior to the current first element
  were swapped;
  returns a two-element vector [partially-sorted-sequence is-sorted]"
 [less? xs was-changed]
  (if (< (count xs) 2)
    [xs (not was-changed)]
    (let [[x1 x2 & xr] xs
   first-is-smaller   (less? x1 x2)
   is-changed         (or was-changed (not first-is-smaller))
   [smaller larger]   (if first-is-smaller [x1 x2] [x2 x1])
   [result is-sorted] (bubble-step
         less? (cons larger xr) is-changed)]
      [(cons smaller result) is-sorted])))
 
(defn bubble-sort
  "Takes an optional less-than predicate and a sequence.
  Returns the sorted sequence.
  Very inefficient (O(n²))"
  ([xs] (bubble-sort <= xs))
  ([less? xs] 
     (let [[result is-sorted] (bubble-step less? xs false)]
       (if is-sorted
  result
  (recur less? result)))))
 
(println (bubble-sort [10 9 8 7 6 5 4 3 2 1]))

[edit]CMake

Only for lists of integers.
# bubble_sort(var [value1 value2...]) sorts a list of integers.
function(bubble_sort var)
  math(EXPR last "${ARGC} - 1")  # Prepare to sort ARGV[1]..ARGV[last].
  set(again YES)
  while(again)
    set(again NO)
    math(EXPR last "${last} - 1")               # Decrement last index.
    foreach(index RANGE 1 ${last})              # Loop for each index.
      math(EXPR index_plus_1 "${index} + 1")
      set(a "${ARGV${index}}")                  # a = ARGV[index]
      set(b "${ARGV${index_plus_1}}")           # b = ARGV[index + 1]
      if(a GREATER "${b}")                      # If a > b...
        set(ARGV${index} "${b}")                # ...then swap a, b
        set(ARGV${index_plus_1} "${a}")         #    inside ARGV.
        set(again YES)
      endif()
    endforeach(index)
  endwhile()
 
  set(answer)
  math(EXPR last "${ARGC} - 1")
  foreach(index RANGE 1 "${last}")
    list(APPEND answer "${ARGV${index}}")
  endforeach(index)
  set("${var}" "${answer}" PARENT_SCOPE)
endfunction(bubble_sort)
bubble_sort(result 33 11 44 22 66 55)
message(STATUS "${result}")
-- 11;22;33;44;55;66

[edit]COBOL

This is a complete program that demonstrates the bubble sort algorithm in COBOL.
 
       identification division.
       program-id. BUBBLSRT.
       data division.
       working-storage section.
       01 changed-flag      pic x.
          88 hasChanged         value 'Y'.
          88 hasNOTChanged      value 'N'.
       01 itemCount         pic 99.
       01 tempItem          pic 99.
       01 itemArray.   
          03 itemArrayCount pic 99.
          03 item           pic 99 occurs 99 times
                                   indexed by itemIndex.
      *          
       procedure division.
       main.
      * place the values to sort into itemArray
           move 10 to itemArrayCount 
           move 28 to item (1)
           move 44 to item (2)
           move 46 to item (3)           
           move 24 to item (4)
           move 19 to item (5)
           move  2 to item (6)
           move 17 to item (7)
           move 11 to item (8)
           move 24 to item (9)           
           move  4 to item (10)
      * store the starting count in itemCount and perform the sort    
           move itemArrayCount to itemCount
           perform bubble-sort
      * output the results     
           perform varying itemIndex from 1 by 1 
              until itemIndex > itemArrayCount
              display item (itemIndex) ';' with no advancing
           end-perform   
      * thats it!       
           stop run.
      *     
       bubble-sort.
           perform with test after until hasNOTchanged
              set hasNOTChanged to true
              subtract 1 from itemCount
              perform varying itemIndex from 1 by 1 
                 until itemIndex > itemCount
                 if item (itemIndex) > item (itemIndex + 1)
                    move item (itemIndex) to tempItem
                    move item (itemIndex + 1) to item (itemIndex)
                    move tempItem to item (itemIndex + 1)
                    set hasChanged to true
                 end-if   
              end-perform   
           end-perform   
           .
 
Output:
 Output: 02;04;11;17;19;24;24;28;44;46; 

[edit]Common Lisp

Bubble sort an sequence in-place, using the < operator for comparison if no comaprison function is provided
(defun bubble-sort (sequence &optional (compare #'<))
  "sort a sequence (array or list) with an optional comparison function (cl:< is the default)"
  (loop with sorted = nil until sorted do
        (setf sorted t)
        (loop for a below (1- (length sequence)) do
              (unless (funcall compare (elt sequence a)
                                       (elt sequence (1+ a)))
                (rotatef (elt sequence a)
                         (elt sequence (1+ a)))
                (setf sorted nil)))))
(bubble-sort (list 5 4 3 2 1))
elt has linear access time for lists, making the prior implementation of bubble-sort very expensive (although very clear, and straightforward to code. Here is an implementation that works efficiently for both vectors and lists. For lists it also has the nice property that the input list and the sorted list begin with the same cons cell.
(defun bubble-sort-vector (vector predicate &aux (len (1- (length vector))))
  (do ((swapped t)) ((not swapped) vector)
    (setf swapped nil)
    (do ((i (min 0 len) (1+ i))) ((eql i len))
      (when (funcall predicate (aref vector (1+ i)) (aref vector i))
        (rotatef (aref vector i) (aref vector (1+ i)))
        (setf swapped t)))))
 
(defun bubble-sort-list (list predicate)
  (do ((swapped t)) ((not swapped) list)
    (setf swapped nil)
    (do ((list list (rest list))) ((endp (rest list)))
      (when (funcall predicate (second list) (first list))
        (rotatef (first list) (second list))
        (setf swapped t)))))
 
(defun bubble-sort (sequence predicate)
  (etypecase sequence
    (list (bubble-sort-list sequence predicate))
    (vector (bubble-sort-vector sequence predicate))))

[edit]D

import std.stdio, std.algorithm;
 
void bubbleSort(T)(T[] data) pure nothrow {
    auto itemCount = data.length;
    bool hasChanged = false;
 
    do {
        hasChanged = false;
        itemCount--;
        foreach (immutable i; 0 .. itemCount)
            if (data[i] > data[i + 1]) {
                swap(data[i], data[i + 1]);
                hasChanged = true;
            }
    } while (hasChanged);
}
 
void main() {
    auto array = [28, 44, 46, 24, 19, 2, 17, 11, 25, 4];
    array.bubbleSort();
    writeln(array);
}
Output:
[2, 4, 11, 17, 19, 24, 25, 28, 44, 46]

[edit]Delphi

Dynamic array is a 0-based array of variable length
Static array is an arbitrary-based array of fixed length
program TestBubbleSort;
 
{$APPTYPE CONSOLE}
 
{.$DEFINE DYNARRAY}  // remove '.' to compile with dynamic array
 
type
  TItem = Integer;   // declare ordinal type for array item
{$IFDEF DYNARRAY}
  TArray = array of TItem;          // dynamic array
{$ELSE}
  TArray = array[0..15] of TItem;   // static array
{$ENDIF}
 
procedure BubbleSort(var A: TArray);
var
  Item: TItem;
  K, L, J: Integer;
 
begin
  L:= Low(A) + 1;
  repeat
    K:= High(A);
    for J:= High(A) downto L do begin
      if A[J - 1] > A[J] then begin
        Item:= A[J - 1];
        A[J - 1]:= A[J];
        A[J]:= Item;
        K:= J;
      end;
    end;
    L:= K + 1;
  until L > High(A);
end;
 
var
  A: TArray;
  I: Integer;
 
begin
{$IFDEF DYNARRAY}
  SetLength(A, 16);
{$ENDIF}
  for I:= Low(A) to High(A) do
    A[I]:= Random(100);
  for I:= Low(A) to High(A) do
    Write(A[I]:3);
  Writeln;
  BubbleSort(A);
  for I:= Low(A) to High(A) do
    Write(A[I]:3);
  Writeln;
  Readln;
end.
Output:
  0  3 86 20 27 67 31 16 37 42  8 47  7 84  5 29
  0  3  5  7  8 16 20 27 29 31 37 42 47 67 84 86

[edit]E

def bubbleSort(target) {
  __loop(fn {
    var changed := false
    for i in 0..(target.size() - 2) {
      def [a, b] := target(i, i + 2)
      if (a > b) {
        target(i, i + 2) := [b, a]
        changed := true
      }
    }
    changed
  })
}
(Uses the primitive __loop directly because it happens to map to the termination test for this algorithm well.)

[edit]Eiffel

Works withEiffelStudio version 6.6 (with provisional loop syntax)
This solution is presented in two classes. The first is a simple application that creates a set, an instance of MY_SORTED_SET, and adds elements to the set in unsorted order. It iterates across the set printing the elements, then it sorts the set, and reprints the elements.
class
    APPLICATION
create
    make
 
feature
    make
            -- Create and print sorted set
        do
            create my_set.make
            my_set.put_front (2)
            my_set.put_front (6)
            my_set.put_front (1)
            my_set.put_front (5)
            my_set.put_front (3)
            my_set.put_front (9)
            my_set.put_front (8)
            my_set.put_front (4)
            my_set.put_front (10)
            my_set.put_front (7)
            print ("Before: ")
            across my_set as ic loop print (ic.item.out + " ")  end
            print ("%NAfter : ")
            my_set.sort
            across my_set as ic loop print (ic.item.out + " ")  end
        end
 
    my_set: MY_SORTED_SET [INTEGER]
            -- Set to be sorted
end
The second class is MY_SORTED_SET.
class
    MY_SORTED_SET [G -> COMPARABLE]
inherit
    TWO_WAY_SORTED_SET [G]
        redefine
            sort
        end
create
    make
 
feature
    sort
            -- Sort with bubble sort
        local
            l_unchanged: BOOLEAN
            l_item_count: INTEGER
            l_temp: G
        do
            from
                l_item_count := count
            until
                l_unchanged
            loop
                l_unchanged := True
                l_item_count := l_item_count - 1
                across 1 |..| l_item_count as ic loop
                    if Current [ic.item] > Current [ic.item + 1] then
                        l_temp := Current [ic.item]
                        Current [ic.item] := Current [ic.item + 1]
                        Current [ic.item + 1] := l_temp
                        l_unchanged := False
                    end
                end
            end
        end
end
This class inherits from the Eiffel library class TWO_WAY_SORTED_SET, which implements sets whose elements are comparable. Therefore, the set can be ordered and in fact is kept so under normal circumstances.
MY_SORTED_SET redefines only the routine sort which contains the implementation of the sort algorithm. The implementation in the redefined version of sort in MY_SORTED_SET uses a bubble sort.
Output:
Before: 7 10 4 8 9 3 5 1 6 2
After : 1 2 3 4 5 6 7 8 9 10
TWO_WAY_SORTED_SET is implemented internally as a list. For this example, we use the feature put_front which explicitly adds each new element to the beginning of the list, allowing us to show that the elements are unordered until we sort them. It also causes, in the "Before" output, the elements to be printed in the reverse of the order in which they were added. Under normal circumstances, we would use the feature extend (rather than put_front) to add elements to the list. This would assure that the order was maintained even as elements were added.

[edit]Elixir

defmodule Sort do
  def bubble_sort(list) when length(list)<=1, do: list
  def bubble_sort(list) when is_list(list), do: bubble_sort(list, [])
 
  def bubble_sort([x], sorted), do: [x | sorted]
  def bubble_sort(list, sorted) do
    {rest, [max]} = Enum.split(bubble_move(list), -1)
    bubble_sort(rest, [max | sorted])
  end
 
  def bubble_move([x]), do: [x]
  def bubble_move([x, y | t]) when x > y, do: [y | bubble_move([x | t])]
  def bubble_move([x, y | t])           , do: [x | bubble_move([y | t])]
 
end
 
IO.inspect Sort.bubble_sort([3,2,1,4,5,2])
Output:
[1, 2, 2, 3, 4, 5]

[edit]Erlang

sort/3 copied from Stackoverflow.
 
-module( bubble_sort ).
 
-export( [list/1, task/0] ).
 
list( To_be_sorted ) -> sort( To_be_sorted, [], true ).
 
task() ->
 List = "asdqwe123",
 Sorted = list( List ),
 io:fwrite( "List ~p is sorted ~p~n", [List, Sorted] ).
 
 
sort( [], Acc, true ) -> lists:reverse( Acc );
sort( [], Acc, false ) -> sort( lists:reverse(Acc), [], true );
sort( [X, Y | T], Acc, _Done ) when X > Y -> sort( [X | T], [Y | Acc], false );
sort( [X | T], Acc, Done ) -> sort( T, [X | Acc], Done ).
 
Output:
7> bubble_sort:task().
List "asdqwe123" is sorted "123adeqsw"

[edit]Euphoria

function bubble_sort(sequence s)
    object tmp
    integer changed
    for j = length(s) to 1 by -1 do
        changed = 0
        for i = 1 to j-1 do
            if compare(s[i], s[i+1]) > 0 then
                tmp = s[i]
                s[i] = s[i+1]
                s[i+1] = tmp
                changed = 1
            end if
        end for
        if not changed then
            exit
        end if
    end for
    return s
end function
 
include misc.e
constant s = {4, 15, "delta", 2, -31, 0, "alfa", 19, "gamma", 2, 13, "beta", 782, 1}
 
puts(1,"Before: ")
pretty_print(1,s,{2})
puts(1,"\nAfter: ")
pretty_print(1,bubble_sort(s),{2})
Output:
Before: {
  4,
  15,
  "delta",
  2,
  -31,
  0,
  "alfa",
  19,
  "gamma",
  2,
  13,
  "beta",
  782,
  1
}
After: {
  -31,
  0,
  1,
  2,
  2,
  4,
  13,
  15,
  19,
  782,
  "alfa",
  "beta",
  "delta",
  "gamma"
}

[edit]Ezhil

 
 
## இந்த நிரல் ஒரு பட்டியலில் உள்ள எண்களை Bubble Sort என்ற முறைப்படி ஏறுவரிசையிலும் பின்னர் அதையே இறங்குவரிசையிலும் அடுக்கித் தரும்
 
## மாதிரிக்கு நாம் ஏழு எண்களை எடுத்துக்கொள்வோம்
 
எண்கள் = [5, 1, 10, 8, 1, 21, 4, 2]
எண்கள்பிரதி = எண்கள்
 
பதிப்பி "ஆரம்பப் பட்டியல்:"
பதிப்பி எண்கள்
 
நீளம் = len(எண்கள்)
குறைநீளம் = நீளம் - 1
 
@(குறைநீளம் != -1) வரை
  மாற்றம் = -1
  @(எண் = 0, எண் < குறைநீளம், எண் = எண் + 1) ஆக
    முதலெண் = எடு(எண்கள், எண்)
    இரண்டாமெண் = எடு(எண்கள், எண் + 1)
    @(முதலெண் > இரண்டாமெண்) ஆனால்
 
      ## பெரிய எண்களை ஒவ்வொன்றாகப் பின்னே நகர்த்துகிறோம்
 
      வெளியேஎடு(எண்கள், எண்)
      நுழைக்க(எண்கள், எண், இரண்டாமெண்)
      வெளியேஎடு(எண்கள், எண் + 1)
      நுழைக்க(எண்கள், எண் + 1, முதலெண்)
      மாற்றம் = எண்
    முடி
  முடி
  குறைநீளம் = மாற்றம்
முடி
 
பதிப்பி "ஏறு வரிசையில் அமைக்கப்பட்ட பட்டியல்:"
பதிப்பி எண்கள்
 
## இதனை இறங்குவரிசைக்கு மாற்றுவதற்கு எளிய வழி
 
தலைகீழ்(எண்கள்)
 
## இப்போது, நாம் ஏற்கெனவே எடுத்துவைத்த எண்களின் பிரதியை Bubble Sort முறைப்படி இறங்குவரிசைக்கு மாற்றுவோம்
 
நீளம் = len(எண்கள்பிரதி)
குறைநீளம் = நீளம் - 1
 
@(குறைநீளம் != -1) வரை
  மாற்றம் = -1
  @(எண் = 0, எண் < குறைநீளம், எண் = எண் + 1) ஆக
    முதலெண் = எடு(எண்கள்பிரதி, எண்)
    இரண்டாமெண் = எடு(எண்கள்பிரதி, எண் + 1)
    @(முதலெண் < இரண்டாமெண்) ஆனால்
 
      ## சிறிய எண்களை ஒவ்வொன்றாகப் பின்னே நகர்த்துகிறோம்
 
      வெளியேஎடு(எண்கள்பிரதி, எண்)
      நுழைக்க(எண்கள்பிரதி, எண், இரண்டாமெண்)
      வெளியேஎடு(எண்கள்பிரதி, எண் + 1)
      நுழைக்க(எண்கள்பிரதி, எண் + 1, முதலெண்)
      மாற்றம் = எண்
    முடி
  முடி
  குறைநீளம் = மாற்றம்
முடி
 
பதிப்பி "இறங்கு வரிசையில் அமைக்கப்பட்ட பட்டியல்:"
பதிப்பி எண்கள்பிரதி
 
 

[edit]F#

let BubbleSort (lst : list<int>) = 
    let rec sort accum rev lst =
        match lst, rev with
        | [], true -> accum |> List.rev
        | [], false -> accum |> List.rev |> sort [] true
        | x::y::tail, _ when x > y -> sort (y::accum) false (x::tail)
        | head::tail, _ -> sort (head::accum) rev tail
    sort [] true lst
 

[edit]Factor

USING: fry kernel locals math math.order sequences
sequences.private ;
IN: rosetta.bubble
 
<PRIVATE
 
:: ?exchange ( i seq quot -- ? )
    i i 1 + [ seq nth-unsafe ] bi@ quot call +gt+ = :> doit?
    doit? [ i i 1 + seq exchange ] when
    doit? ; inline
 
: 1pass ( seq quot -- ? )
    [ [ length 1 - iota ] keep ] dip
    '[ _ _ ?exchange ] [ or ] map-reduce ; inline
 
PRIVATE>
 
: sort! ( seq quot -- )
    over empty?
    [ 2drop ] [ '[ _ _ 1pass ] loop ] if ; inline
 
: natural-sort! ( seq -- )
    [ <=> ] sort! ;
It is possible to pass your own comparison operator to sort!, so you can f.e. sort your sequence backwards with passing [ >=< ] into it.
10 [ 10000 random ] replicate
[ "Before:  " write . ]
[ "Natural: " write [ natural-sort! ] keep . ]
[ "Reverse: " write [ [ >=< ] sort! ] keep . ] tri
Before:  { 3707 5045 4661 1489 3140 7195 8844 6506 6322 3199 }
Natural: { 1489 3140 3199 3707 4661 5045 6322 6506 7195 8844 }
Reverse: { 8844 7195 6506 6322 5045 4661 3707 3199 3140 1489 }

[edit]Fish

This is not a complete implementation of bubblesort: it doesn't keep a boolean flag whether to stop, so it goes on printing each stage of the sorting process ad infinitum.
v Sorts the (pre-loaded) stack
  with bubblesort.
v                     <
\l0=?;l&
>&:1=?v1-&2[$:{:{](?${
          >~{ao       ^
      >~}l &{   v
o","{n:&-1^?=0:&<

[edit]Forth

Sorts the 'cnt' cells stored at 'addr' using the test stored in the deferred word 'bubble-test'. Uses forth local variables for clarity.
defer bubble-test
' > is bubble-test
 
: bubble { addr cnt -- }
  cnt 1 do
    addr cnt i - cells bounds do
      i 2@ bubble-test if i 2@ swap i 2! then
    cell +loop
  loop ;
This is the same algorithm done without the local variables:
: bubble ( addr cnt -- )
  dup 1 do
    2dup i - cells bounds do
      i 2@ bubble-test if i 2@ swap i 2! then
    cell +loop
  loop ;
Version with O(n) best case:
: bubble ( addr len -- )
  begin
    1- 2dup  true -rot  ( sorted addr len-1 )
    cells bounds ?do
      i 2@ bubble-test if
        i 2@ swap i 2!
        drop false   ( mark unsorted )
      then
    cell +loop  ( sorted )
  until 2drop ;
Test any version with this:
create test
8 , 1 , 4 , 2 , 10 , 3 , 7 , 9 , 6 , 5 ,
here test - cell / constant tcnt

test tcnt cells dump
' > is bubble-test
test tcnt bubble
test tcnt cells dump
' < is bubble-test
test tcnt bubble
test tcnt cells dump

[edit]Fortran

SUBROUTINE Bubble_Sort(a)
  REAL, INTENT(in out), DIMENSION(:) :: a
  REAL :: temp
  INTEGER :: i, j
  LOGICAL :: swapped
 
  DO j = SIZE(a)-1, 1, -1
    swapped = .FALSE.
    DO i = 1, j
      IF (a(i) > a(i+1)) THEN
        temp = a(i)
        a(i) = a(i+1)
        a(i+1) = temp
        swapped = .TRUE.
      END IF
    END DO
    IF (.NOT. swapped) EXIT
  END DO
END SUBROUTINE Bubble_Sort

[edit]FreeBASIC

Per task pseudo code:
' version 21-06-2015
' compile with: fbc -s console
' for boundry checks on array's compile with: fbc -s console -exx
 
Sub bubblesort(bs() As Integer)
    ' sort from lower bound to the highter bound
    ' array's can have subscript range from -2147483648 to +2147483647
    Dim As Integer lb = LBound(bs)
    Dim As Integer ub = UBound(bs) -1
    Dim As Integer done, i
 
    Do
        done = 0
        For i = lb To ub 
            ' replace "<" with ">" for downwards sort
            If bs(i) > bs(i + 1) Then
                Swap bs(i), bs(i + 1)
                done = 1
            End If
        Next
        ub = ub -1
    Loop Until done = 0
 
End Sub
 
' ------=< MAIN >=------
 
Dim As Integer i, array(-7 To 7)
 
Dim As Integer a = LBound(array), b = UBound(array)
 
Randomize Timer
For i = a To b : array(i) = i  : Next
For i = a To b ' little shuffle
    Swap array(i), array(Rnd * b)
Next
 
Print "unsort ";
For i = a To b : Print Using "####"; array(i); : Next : Print
bubblesort(array())  ' sort the array
Print "  sort ";
For i = a To b : Print Using "####"; array(i); : Next : Print
 
' empty keyboard buffer
While InKey <> "" : Var _key_ = InKey : Wend
Print : Print "hit any key to end program"
Sleep
End
Output:
unsort    6   2   4   7   1   5  -6  -2   3  -4  -7  -3  -1  -5   0
  sort   -7  -6  -5  -4  -3  -2  -1   0   1   2   3   4   5   6   7

[edit]Go

Per task pseudocode:
package main
 
import "fmt"
 
func main() {
    list := []int{31, 41, 59, 26, 53, 58, 97, 93, 23, 84}
    fmt.Println("unsorted:", list)
 
    bubblesort(list)
    fmt.Println("sorted!  ", list)
}
 
func bubblesort(a []int) {
    for itemCount := len(a) - 1; ; itemCount-- {
        hasChanged := false
        for index := 0; index < itemCount; index++ {
            if a[index] > a[index+1] {
                a[index], a[index+1] = a[index+1], a[index]
                hasChanged = true
            }
        }
        if hasChanged == false {
            break
        }
    }
}
More generic version that can sort anything that implements sort.Interface:
package main
 
import (
  "sort"
  "fmt"
)
 
func main() {
    list := []int{31, 41, 59, 26, 53, 58, 97, 93, 23, 84}
    fmt.Println("unsorted:", list)
 
    bubblesort(sort.IntSlice(list))
    fmt.Println("sorted!  ", list)
}
 
func bubblesort(a sort.Interface) {
    for itemCount := a.Len() - 1; ; itemCount-- {
        hasChanged := false
        for index := 0; index < itemCount; index++ {
            if a.Less(index+1, index) {
                a.Swap(index, index+1)
                hasChanged = true
            }
        }
        if !hasChanged {
            break
        }
    }
}

[edit]Groovy

Solution:
def makeSwap = { a, i, j = i+1 -> print "."; a[[i,j]] = a[[j,i]] }
 
def checkSwap = { a, i, j = i+1 -> [(a[i] > a[j])].find { it }.each { makeSwap(a, i, j) } }
 
def bubbleSort = { list ->
    boolean swapped = true
    while (swapped) { swapped = (1..<list.size()).any { checkSwap(list, it-1) } }
    list
}
Test Program:
println bubbleSort([23,76,99,58,97,57,35,89,51,38,95,92,24,46,31,24,14,12,57,78,4])
println bubbleSort([88,18,31,44,4,0,8,81,14,78,20,76,84,33,73,75,82,5,62,70,12,7,1])
Output:
..............................................................................................................................................[4, 12, 14, 23, 24, 24, 31, 35, 38, 46, 51, 57, 57, 58, 76, 78, 89, 92, 95, 97, 99]
.........................................................................................................................................[0, 1, 4, 5, 7, 8, 12, 14, 18, 20, 31, 33, 44, 62, 70, 73, 75, 76, 78, 81, 82, 84, 88]

[edit]Haskell

This version checks for changes in a separate step for simplicity, because Haskell has no variables to track them with.
bsort :: Ord a => [a] -> [a]
bsort s = case _bsort s of
               t | t == s    -> t
                 | otherwise -> bsort t
  where _bsort (x:x2:xs) | x > x2    = x2:(_bsort (x:xs))
                         | otherwise = x:(_bsort (x2:xs))
        _bsort s = s
This version uses the polymorphic Maybe type to designate unchanged lists. (The type signature of _bsort is now Ord a => [a] -> Maybe [a].) It is slightly faster than the previous one.
import Data.Maybe (fromMaybe)
import Control.Monad
 
bsort :: Ord a => [a] -> [a]
bsort s = maybe s bsort $ _bsort s
  where _bsort (x:x2:xs) = if x > x2
            then Just $ x2 : fromMaybe (x:xs) (_bsort $ x:xs)
            else liftM (x:) $ _bsort (x2:xs)
        _bsort _         = Nothing
This version is based on the above, but avoids sorting whole list each time. To implement this without a counter and retain using pattern matching, inner sorting is reversed, and then result is reversed back. Sorting is based on a predicate, e. g. (<) or (>).
import Data.Maybe (fromMaybe)
import Control.Monad
 
bubbleSortBy ::  (a -> a -> Bool) -> [a] -> [a]
bubbleSortBy f as = case innerSort $ reverse as of
                         Nothing -> as
                         Just v  -> let (x:xs) = reverse v
                                   in x : bubbleSortBy f xs
    where innerSort (a:b:cs) = if b `f` a
                                  then liftM (a:) $ innerSort (b:cs)
                                  else Just $ b : fromMaybe (a:cs)
                                                (innerSort $ a:cs)
          innerSort _        = Nothing
 
bsort :: Ord a => [a] -> [a]
bsort =  bubbleSortBy (<)

[edit]HicEst

SUBROUTINE Bubble_Sort(a)
  REAL :: a(1)
 
  DO j = LEN(a)-1, 1, -1
    swapped = 0
    DO i = 1, j
      IF (a(i) > a(i+1)) THEN
        temp = a(i)
        a(i) = a(i+1)
        a(i+1) = temp
        swapped = 1
      ENDIF
    ENDDO
    IF (swapped == 0) RETURN
  ENDDO
END

[edit]Icon and Unicon

Icon/Unicon implementation of a bubble sort
procedure main()                     #: demonstrate various ways to sort a list and string
   demosort(bubblesort,[3, 14, 1, 5, 9, 2, 6, 3],"qwerty")
end
 
procedure bubblesort(X,op)           #: return sorted list 
local i,swapped
 
   op := sortop(op,X)                # select how and what we sort
 
   swapped := 1 
   while \swapped := &null do         # the sort
      every  i := 2 to *X do  
         if op(X[i],X[i-1]) then  
            X[i-1] :=: X[swapped := i] 
   return X
end
Output:
Sorting Demo using procedure bubblesort
  on list : [ 3 14 1 5 9 2 6 3 ]
    with op = &null:         [ 1 2 3 3 5 6 9 14 ]   (0 ms)
    with op = "numeric":     [ 1 2 3 3 5 6 9 14 ]   (0 ms)
    with op = "string":      [ 1 14 2 3 3 5 6 9 ]   (0 ms)
    with op = ">>":          [ 9 6 5 3 3 2 14 1 ]   (0 ms)
    with op = ">":           [ 14 9 6 5 3 3 2 1 ]   (0 ms)
    with op = procedure cmp: [ 1 2 3 3 5 6 9 14 ]   (1 ms)
    with op = "cmp":         [ 1 2 3 3 5 6 9 14 ]   (0 ms)
  on string : "qwerty"
    with op = &null:         "eqrtwy"   (0 ms)
The following code supports this and other sorting demonstrations.
  • Sorting illustrates a difference in the way Icon and Unicon handles data types. Built-in operators for comparing data types make a syntactic distinction between numeric and string types, and sorting structured and user-defined types require custom code. An added complication arises because mixed types are allowed. Two approaches are possible here: (1) that taken by the built-in sort which sorts first by type and then value The sort order of types is: &null, integer, real, string, cset, procedure, list, set, table, and record; and (2) Coercion of types which is used here (and implemented in 'sortop') to decide on using string or numeric sorting. These sorts will not handle more exotic type mixes.
  • The 'sortop' procedure allows various methods of comparison be selected including customized ones. The example could be made more general to deal with coercion of types like cset to string (admittedly an uninteresting example as csets are already sorted). Custom comparators are shown by and example procedure 'cmp'.
  • 'demosort' can apply different sorting procedures and operators to lists and strings to show how this works. The routines 'displaysort' and 'writex' are helpers.
invocable all                # for op
 
procedure sortop(op,X)                  #: select how to sort
 
    op := case op of {               
             "string":  "<<"
             "numeric": "<"
             &null:     if type(!X) == "string" then "<<" else "<"
             default:   op
          }
return proc(op, 2) | runerr(123, image(op))
end
 
procedure cmp(a,b)                    #: example custom comparison procedure
    return a < b                      #  Imagine a complex comparison test here!
end
 
procedure demosort(sortproc,L,s)      # demonstrate sort on L and s
 
    write("Sorting Demo using ",image(sortproc))
    writes("  on list : ")
    writex(L)
    displaysort(sortproc,L)           # default string sort
    displaysort(sortproc,L,"numeric") # explicit numeric sort
    displaysort(sortproc,L,"string")  # explicit string sort
    displaysort(sortproc,L,">>")      # descending string sort
    displaysort(sortproc,L,">")       # descending numeric sort
    displaysort(sortproc,L,cmp)       # ascending custom comparison
    displaysort(sortproc,L,"cmp")     # ascending custom comparison
 
    writes("  on string : ")
    writex(s)
    displaysort(sortproc,s)           # sort characters in a string
    write()
    return
end
 
procedure displaysort(sortproc,X,op)  #: helper to show sort behavior
local t,SX
    writes("    with op = ",left(image(op)||":",15))
    X := copy(X)
    t := &time
    SX := sortproc(X,op)
    writex(SX,"   (",&time - t," ms)")
    return 
end
 
procedure writex(X,suf[])             #: helper for displaysort
    if type(X) == "string" then 
        writes(image(X))
    else {
        writes("[")
        every writes(" ",image(!X))
        writes(" ]")
        }
    every writes(!suf)
    write()
return 
end

[edit]J

Generally, this task should be accomplished in J using /:~ list. Here we take an approach that's more comparable with the other examples on this page.
bubbleSort=:  (([ (<. , >.) {.@]) , }.@])/^:_
Test program:
   ?. 10 $ 10
4 6 8 6 5 8 6 6 6 9
   bubbleSort ?. 10 $ 10
4 5 6 6 6 6 6 8 8 9
For the most part, bubble sort works against J's strengths. However, once a single pass has been implemented as a list operation, ^:_ tells J to repeat this until the result stops changing.

[edit]Java

Bubble sorting (ascending) an array of any Comparable type:
public static <E extends Comparable<? super E>> void bubbleSort(E[] comparable) {
    boolean changed = false;
    do {
        changed = false;
        for (int a = 0; a < comparable.length - 1; a++) {
            if (comparable[a].compareTo(comparable[a + 1]) > 0) {
                E tmp = comparable[a];
                comparable[a] = comparable[a + 1];
                comparable[a + 1] = tmp;
                changed = true;
            }
        }
    } while (changed);
}
For descending, simply switch the direction of comparison:
if (comparable[a].compareTo(comparable[b]) < 0){
   //same swap code as before
}

[edit]JavaScript

Array.prototype.bubblesort = function() {
    var done = false;
    while (!done) {
        done = true;
        for (var i = 1; i<this.length; i++) {
            if (this[i-1] > this[i]) {
                done = false;
                [this[i-1], this[i]] = [this[i], this[i-1]]
            }
        }
    }
    return this;
}
Works withSEE version 3.0
Works withOSSP js version 1.6.20070208
Array.prototype.bubblesort = function() {
  var done = false;
  while (! done) {
    done = true;
    for (var i = 1; i < this.length; i++) {
      if (this[i - 1] > this[i]) {
        done = false;
        var tmp = this[i - 1];
        this[i - 1] = this[i];
        this[i] = tmp;
      }
    }
  }
  return this;
}
Example:
var my_arr = ["G", "F", "C", "A", "B", "E", "D"];
my_arr.bubblesort();
print(my_arr);
Output:
 A,B,C,D,E,F,G

[edit]jq

def bubble_sort:
  def swap(i;j): .[i] as $x | .[i]=.[j] | .[j]=$x;
 
  # input/output: [changed, list]
  reduce range(0; length) as $i
    ( [false, .];
      if $i > 0 and (.[0]|not) then .
      else reduce range(0; (.[1]|length) - $i - 1) as $j
        (.[0] = false;
        .[1] as $list
        | if $list[$j] > $list[$j + 1] then [true, ($list|swap($j; $j+1))]
          else .
          end )
      end  ) | .[1] ;
Example:
(
 [3,2,1],
 [1,2,3],
 ["G", "F", "C", "A", "B", "E", "D"]
)  | bubble_sort
Output:
$ jq -c -n -f Bubble_sort.jq
[1,2,3]
[1,2,3]
["A","B","C","D","E","F","G"]

[edit]Julia

 
function bubblesort{T}(a::AbstractArray{T,1})
    b = copy(a)
    isordered = false
    span = length(b)
    while !isordered && span > 1
        isordered = true
        for i in 2:span
            if b[i] < b[i-1]
                t = b[i]
                b[i] = b[i-1]
                b[i-1] = t
                isordered = false
            end
        end
        span -= 1
    end
    return b
end
 
a = [rand(-100:100) for i in 1:20]
println("Before bubblesort:")
println(a)
a = bubblesort(a)
println("\nAfter bubblesort:")
println(a)
 
Output:
Before bubblesort:
[95,-40,-93,38,95,-20,-13,-61,81,51,-54,77,-4,-49,-99,-55,28,-52,2,-28]

After bubblesort:
[-99,-93,-61,-55,-54,-52,-49,-40,-28,-20,-13,-4,2,28,38,51,77,81,95,95]
Here bubblesort was used on a list of integers. As written the function will work on lists of any objects for which isless is defined.

[edit]Kotlin

Translation ofJava
fun <T> bubbleSort(a : Array<T>, c: Comparator<T>) {
    var changed : Boolean
    do {
        changed = false
        for (i in 0 .. a.size - 2) {
            if (c.compare(a[i], a[i + 1]) > 0) {
                val tmp = a[i]
                a[i] = a[i + 1]
                a[i + 1] = tmp
                changed = true
            }
        }
    } while (changed)
}

[edit]Io

 
List do(
  bubblesort := method(
    t := true
    while( t,
      t := false
      for( j, 0, self size - 2,
        if( self at( j ) start > self at( j+1 ) start,
          self swapIndices( j,j+1 )
          t := true
        )
      )
    )
    return( self )
  )
)
 

[edit]Liberty BASIC

 
    itemCount = 20
    dim item(itemCount)
    for i = 1 to itemCount
        item(i) = int(rnd(1) * 100)
    next i
    print "Before Sort"
    for i = 1 to itemCount
        print item(i)
    next i
    print: print
    counter = itemCount
    do
        hasChanged = 0
        for i = 1 to counter - 1
            if item(i) > item(i + 1) then
                temp = item(i)
                item(i) = item(i + 1)
                item(i + 1) = temp
                hasChanged = 1
            end if
        next i
        counter =counter -1
    loop while hasChanged = 1
    print "After Sort"
    for i = 1 to itemCount
        print item(i)
    next i
end
 

[edit]Lisaac

Section Header
 
+ name := BUBBLE_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;
  };
 
  bubble a;
 
  a.foreach { item : INTEGER;
    item.print;
    '\n'.print;
  };
);
 
- bubble a : ARRAY(INTEGER) <- (
  + lower, size, t : INTEGER;
  + sorted : BOOLEAN;
  lower := a.lower;
  size := a.upper - lower + 1;
  {
    sorted := TRUE;
    size := size - 1;
    0.to (size - 1) do { i : INTEGER;
      (a.item(lower + i + 1) < a.item(lower + i)).if {
        t := a.item(lower + i + 1);
        a.put (a.item(lower + i)) to (lower + i + 1);
        a.put t to (lower + i);
        sorted := FALSE;
      };
    };
  }.do_while {!sorted};
);

[edit]Lua

 
function bubbleSort(A)
  local itemCount=#A
  local hasChanged
  repeat
    hasChanged = false
    itemCount=itemCount - 1
    for i = 1, itemCount do
      if A[i] > A[i + 1] then
        A[i], A[i + 1] = A[i + 1], A[i]
        hasChanged = true
      end
    end
  until hasChanged == false
end
 
Example:
 
list = { 5, 6, 1, 2, 9, 14, 2, 15, 6, 7, 8, 97 }
bubbleSort(list)
for i, j in pairs(list) do
    print(j)
end
 

[edit]Lucid

bsort(a) = if iseod(first a) then a else
              follow(bsort(allbutlast(b)),last(b)) fi
  where
   b = bubble(a);
   bubble(a) = smaller(max, next a)
       where
        max = first a fby larger(max, next a);
        larger(x,y) = if iseod(y) then y elseif x
       end;
   follow(x,y) = if xdone then y upon xdone else x fi
                   where
                      xdone = iseod x fby xdone or iseod x;
                   end;
   last(x) = (x asa iseod next x) fby eod;
   allbutlast(x) = if not iseod(next x) then x else eod fi;
  end

[edit]M4

divert(-1)
 
define(`randSeed',141592653)
define(`setRand',
   `define(`randSeed',ifelse(eval($1<10000),1,`eval(20000-$1)',`$1'))')
define(`rand_t',`eval(randSeed^(randSeed>>13))')
define(`random',
   `define(`randSeed',eval((rand_t^(rand_t<<18))&0x7fffffff))randSeed')
 
define(`set',`define(`$1[$2]',`$3')')
define(`get',`defn(`$1[$2]')')
define(`new',`set($1,size,0)')
dnl  for the heap calculations, it's easier if origin is 0, so set value first
define(`append',
   `set($1,size,incr(get($1,size)))`'set($1,get($1,size),$2)')
 
dnl  swap(<name>,<j>,<name>[<j>],<k>)  using arg stack for the temporary
define(`swap',`set($1,$2,get($1,$4))`'set($1,$4,$3)')
 
define(`deck',
   `new($1)for(`x',1,$2,
         `append(`$1',eval(random%100))')')
define(`show',
   `for(`x',1,get($1,size),`get($1,x) ')')
define(`for',
   `ifelse($#,0,``$0'',
   `ifelse(eval($2<=$3),1,
   `pushdef(`$1',$2)$4`'popdef(`$1')$0(`$1',incr($2),$3,`$4')')')')
 
define(`bubbleonce',
   `for(`x',1,$2,
      `ifelse(eval(get($1,x)>get($1,incr(x))),1,
         `swap($1,x,get($1,x),incr(x))`'1')')0')
define(`bubbleupto',
   `ifelse(bubbleonce($1,$2),0,
      `',
      `bubbleupto($1,decr($2))')')
define(`bubblesort',
   `bubbleupto($1,decr(get($1,size)))')
 
divert
deck(`a',10)
show(`a')
bubblesort(`a')
show(`a')
Output:
17 63 80 55 90 88 25 9 71 38

9 17 25 38 55 63 71 80 88 90

[edit]Mathematica / Wolfram Language

bubbleSort[{w___, x_, y_, z___}] /; x > y := bubbleSort[{w, y, x, z}]
bubbleSort[sortedList_] := sortedList
Example:
bubbleSort[{10, 3, 7, 1, 4, 3, 8, 13, 9}]
{1, 3, 3, 4, 7, 8, 9, 10, 13}

[edit]MATLAB

function list = bubbleSort(list)
 
    hasChanged = true;
    itemCount = numel(list);
 
    while(hasChanged)
 
        hasChanged = false;
        itemCount = itemCount - 1;
 
        for index = (1:itemCount)
 
            if(list(index) > list(index+1))
                list([index index+1]) = list([index+1 index]); %swap
                hasChanged = true;
            end %if
 
        end %for
    end %while
end %bubbleSort
Output:
bubbleSort([5 3 8 4 9 7 6 2 1])

ans =

     1     2     3     4     5     6     7     8     9

[edit]MAXScript

fn bubbleSort arr =
(
    while true do
    (
        changed = false
        for i in 1 to (arr.count - 1) do
        (
            if arr[i] > arr[i+1] then
            (
                swap arr[i] arr[i+1]
                changed = true
            )
        )
        if not changed then exit
    )
    arr
)
-- Usage
myArr = #(9, 8, 7, 6, 5, 4, 3, 2, 1)
myArr = bubbleSort myArr

[edit]MMIX

Ja        IS $127
 
          LOC Data_Segment
DataSeg   GREG @
Array     IS @-Data_Segment
          OCTA   999,200,125,1,1020,40,4,5,60,100
ArrayLen  IS (@-Array-Data_Segment)/8
 
NL        IS  @-Data_Segment
   BYTE #a,0
   LOC  @+(8-@)&7
 
Buffer    IS @-Data_Segment
 
 
            LOC #1000
            GREG @
sorted      IS  $5
i           IS  $6
size        IS  $1
a           IS  $0
t           IS  $20
t1          IS  $21
t2          IS  $22
% Input: $0 ptr to array, $1 its length (in octabyte)
% Trashed: $5, $6, $1, $20, $21, $22
BubbleSort  SETL  sorted,1          % sorted = true
            SUB   size,size,1       % size--
            SETL  i,0               % i = 0
3H          CMP   t,i,size          % i < size ?
            BNN   t,1F              % if false, end for loop
            8ADDU $12,i,a           % compute addresses of the
            ADDU  t,i,1             % octas a[i] and a[i+1]
            8ADDU $11,t,a
            LDO   t1,$12,0          % get their values
            LDO   t2,$11,0
            CMP   t,t1,t2           % compare
            BN    t,2F              % if t1<t2, next
            STO   t1,$11,0          % else swap them
            STO   t2,$12,0
            SETL  sorted,0          % sorted = false
2H          INCL  i,1               % i++
            JMP   3B                % next (for loop)
1H          PBZ   sorted,BubbleSort % while sorted is false, loop
            GO    Ja,Ja,0
            
% Help function (Print an octabyte)
% Input:    $0 (the octabyte)
BufSize     IS    64
            GREG  @
PrintInt8   ADDU  t,DataSeg,Buffer  % get buffer address 
            ADDU  t,t,BufSize       % end of buffer
            SETL  t1,0              % final 0 for Fputs            
            STB   t1,t,0
1H          SUB   t,t,1             % t--
            DIV   $0,$0,10          % ($0,rR) = divmod($0,10)
            GET   t1,rR             % get reminder
            INCL  t1,'0'            % turn it into ascii digit
            STB   t1,t,0            % store it
            PBNZ  $0,1B             % if $0 /= 0, loop
            OR    $255,t,0          % $255 = t
            TRAP  0,Fputs,StdOut 
            GO    Ja,Ja,0           % print and return
 
 
Main        ADDU  $0,DataSeg,Array  % $0 = Array address
            SETL  $1,ArrayLen       % $1 = Array Len
            GO    Ja,BubbleSort     % BubbleSort it
            SETL  $4,ArrayLen       % $4 = ArrayLen
     ADDU  $3,DataSeg,Array  % $3 = Array address
2H          BZ    $4,1F             % if $4 == 0, break
            LDO   $0,$3,0           % $0 = * ($3 + 0)
            GO    Ja,PrintInt8      % print the octa
            ADDU  $255,DataSeg,NL   % add a trailing newline
     TRAP  0,Fputs,StdOut
            ADDU  $3,$3,8           % next octa
            SUB   $4,$4,1           % $4--
     JMP   2B                % loop
1H          XOR   $255,$255,$255
            TRAP  0,Halt,0          % exit(0)

[edit]Modula-2

PROCEDURE BubbleSort(VAR a: ARRAY OF INTEGER);
  VAR
    changed:        BOOLEAN;
    temp, count, i: INTEGER;
BEGIN
  count := HIGH(a);
  REPEAT
    changed := FALSE;
    DEC(count);
    FOR i := 0 TO count DO
      IF a[i] > a[i+1] THEN
        temp := a[i];
        a[i] := a[i+1];
        a[i+1] := temp;
        changed := TRUE
      END
    END
  UNTIL NOT changed
END BubbleSort;

[edit]Modula-3

MODULE Bubble;
 
PROCEDURE Sort(VAR a: ARRAY OF INTEGER) =
  VAR sorted: BOOLEAN;
      temp, len: INTEGER := LAST(a);
  BEGIN
    WHILE NOT sorted DO
      sorted := TRUE;
      DEC(len);
      FOR i := FIRST(a) TO len DO
        IF a[i+1] < a[i] THEN
          temp := a[i];
          a[i] := a[i + 1];
          a[i + 1] := temp;
          sorted := FALSE;
        END;
      END;
    END;
  END Sort;
END Bubble.

[edit]Nemerle

[edit]Functional

using System;
using System.Console;
 
module Bubblesort
{
    Bubblesort[T] (x : list[T]) : list[T]
      where T : IComparable
    {
        def isSorted(y)
        {
            |[_] => true
            |y1::y2::ys => (y1.CompareTo(y2) < 0) && isSorted(y2::ys)
        }
 
        def sort(y)
        {
            |[y]        => [y]
            |y1::y2::ys => if (y1.CompareTo(y2) < 0) y1::sort(y2::ys)
                           else y2::sort(y1::ys)
        }
 
        def loop(y)
        {
            if (isSorted(y)) y else {def z = sort(y); loop(z)}            
        }
 
        match(x)
        {
            |[]  => []
            |_   => loop(x)
        }
    }
 
    Main() : void
    {
        def empty = [];
        def single = [2];
        def several = [2, 6, 1, 7, 3, 9, 4];
        WriteLine(Bubblesort(empty));
        WriteLine(Bubblesort(single));
        WriteLine(Bubblesort(several));
    }
}

[edit]Imperative

Translation ofC#
We use an array for this version so that we can update in place. We could use a C# style list (as in the C# example), but that seemed too easy to confuse with a Nemerle style list.
using System;
using System.Console;
 
module Bubblesort
{
    public static Bubblesort[T](this x : array[T]) : void
      where T : IComparable
    {
        mutable changed = false;
        def ln = x.Length;
 
        do
        {
            changed = false;
            foreach (i in [0 .. (ln - 2)])
            {
                when (x[i].CompareTo(x[i + 1]) > 0)
                {
                    x[i] <-> x[i + 1];
                    changed = true;
                }
            }
        } while (changed);
    }
 
    Main() : void
    {
        def several = array[2, 6, 1, 7, 3, 9, 4];
        several.Bubblesort();
        foreach (i in several)
            Write($"$i  ");
    }
}

[edit]NetRexx

/* NetRexx */
options replace format comments java crossref savelog symbols binary
 
placesList = [String -
    "UK  London",     "US  New York"   -
  , "US  Boston",     "US  Washington" -
  , "UK  Washington", "US  Birmingham" -
  , "UK  Birmingham", "UK  Boston"     -
]
sortedList = bubbleSort(String[] Arrays.copyOf(placesList, placesList.length))
 
lists = [placesList, sortedList]
loop ln = 0 to lists.length - 1
  cl = lists[ln]
  loop ct = 0 to cl.length - 1
    say cl[ct]
    end ct
    say
  end ln
 
return
 
method bubbleSort(list = String[]) public constant binary returns String[]
 
listLen = list.length
loop i_ = 0 to listLen - 1
  loop j_ = i_ + 1 to listLen - 1
    if list[i_].compareTo(list[j_]) > 0 then do
      tmpstor  = list[j_]
      list[j_] = list[i_]
      list[i_] = tmpstor
      end
    end j_
  end i_
 
return list
 
Output:
UK  London
US  New York
US  Boston
US  Washington
UK  Washington
US  Birmingham
UK  Birmingham
UK  Boston

UK  Birmingham
UK  Boston
UK  London
UK  Washington
US  Birmingham
US  Boston
US  New York
US  Washington

[edit]Translation of Pseudocode

This version is a direct implementation of this task's pseudocode.
/* NetRexx */
options replace format comments java crossref savelog symbols binary
 
placesList = [String -
    "UK  London",     "US  New York"   -
  , "US  Boston",     "US  Washington" -
  , "UK  Washington", "US  Birmingham" -
  , "UK  Birmingham", "UK  Boston"     -
]
sortedList = bubbleSort(String[] Arrays.copyOf(placesList, placesList.length))
 
lists = [placesList, sortedList]
loop ln = 0 to lists.length - 1
  cl = lists[ln]
  loop ct = 0 to cl.length - 1
    say cl[ct]
    end ct
    say
  end ln
 
return
 
method bubbleSort(item = String[]) public constant binary returns String[]
 
hasChanged = boolean
itemCount = item.length
loop label h_ until \hasChanged
  hasChanged  = isFalse
  itemCount = itemCount - 1
  loop index = 0 to itemCount - 1
    if item[index].compareTo(item[index + 1]) > 0 then do
      swap            = item[index]
      item[index]     = item[index + 1]
      item[index + 1] = swap
      hasChanged      = isTrue
      end
    end index
  end h_
 
return item
 
method isTrue public constant binary returns boolean
  return 1 == 1
 
method isFalse public constant binary returns boolean
  return \isTrue
 

[edit]Nim

proc bubbleSort[T](a: var openarray[T]) =
  var t = true
  for n in countdown(a.len-2, 0):
    if not t: break
    t = false
    for j in 0..n:
      if a[j] <= a[j+1]: continue
      swap a[j], a[j+1]
      t = true
 
var a = @[4, 65, 2, -31, 0, 99, 2, 83, 782]
bubbleSort a
echo a
Output:
@[-31, 0, 2, 2, 4, 65, 83, 99, 782]

[edit]Objeck

Translation ofC
 
function : Swap(p : Int[]) ~ Nil {
  t := p[0];
  p[0] := p[1];
  p[1] := t;
}
 
function : Sort(a : Int[]) ~ Nil {
  do {
    sorted := true;
    size -= 1;
    for (i:=0; i<a->Size(); i+=1;) {
      if (a[i+1] < a[i]) {
        swap(a+i);
        sorted := 0;
      };
    };
  } 
  while (sorted = false);
}
 

[edit]Objective-C

- (NSArray *) bubbleSort:(NSMutableArray *)unsorted {
    BOOL done = false;
 
    while (!done) {
        done = true;
        for (int i = 1; i < unsorted.count; i++) {
            if ( [[unsorted objectAtIndex:i-1] integerValue] > [[unsorted objectAtIndex:i] integerValue] ) {
                [unsorted exchangeObjectAtIndex:i withObjectAtIndex:i-1];
                done = false;
            }
        }
    }
 
    return unsorted;
}
 

[edit]OCaml

Like the Haskell versions above:
This version checks for changes in a separate step for simplicity.
let rec bsort s =
  let rec _bsort = function
    | x :: x2 :: xs when x > x2 ->
        x2 :: _bsort (x :: xs)
    | x :: x2 :: xs ->
        x :: _bsort (x2 :: xs)
    | s -> s
  in
  let t = _bsort s in
    if t = s then t
    else bsort t
This version uses the polymorphic option type to designate unchanged lists. (The type signature of _bsort is now 'a list -> 'a list option.) It is slightly faster than the previous one.
let rec bsort s =
  let rec _bsort = function
    | x :: x2 :: xs when x > x2 -> begin
        match _bsort (x :: xs) with
          | None -> Some (x2 :: x :: xs)
          | Some xs2 -> Some (x2 :: xs2)
      end
    | x :: x2 :: xs -> begin
        match _bsort (x2 :: xs) with
          | None -> None
          | Some xs2 -> Some (x :: xs2)
      end
    | _ -> None
  in
    match _bsort s with
      | None -> s
      | Some s2 -> bsort s2

[edit]Octave

function s = bubblesort(v)
  itemCount = length(v);
  do
    hasChanged = false;
    itemCount--;
    for i = 1:itemCount
      if ( v(i) > v(i+1) )
 v([i,i+1]) = v([i+1,i]);  % swap
 hasChanged = true;
      endif
    endfor
  until(hasChanged == false)
  s = v;
endfunction
v = [9,8,7,3,1,100];
disp(bubblesort(v));

[edit]ooRexx

[edit]Reimplementation of NetRexx

Translation ofNetRexx
This version exploits the "Collection Classes" and some other features of the language that are only available in Open Object Rexx.
/* Rexx */
Do
  placesList = sampleData()
  call show placesList
  say
  sortedList = bubbleSort(placesList)
  call show sortedList
  say
 
  return
End
Exit
 
-- -----------------------------------------------------------------------------
bubbleSort:
procedure
Do
  il = arg(1)
  sl = il~copy
 
  listLen = sl~size
  loop i_ = 1 to listLen
    loop j_ = i_ + 1 to listLen
      cmpi = sl[i_]
      cmpj = sl[j_]
      if cmpi > cmpj then do
        sl[i_] = cmpj
        sl[j_] = cmpi
        end
      end j_
    end i_
  return sl
End
Exit
 
-- -----------------------------------------------------------------------------
show:
procedure
Do
  al = arg(1)
 
  loop e_ over al
    say e_
    end e_
 
  return
End
Exit
 
-- -----------------------------------------------------------------------------
sampleData:
procedure
Do
  placesList = .array~of( ,
    "UK  London",     "US  New York",   "US  Boston",     "US  Washington", ,
    "UK  Washington", "US  Birmingham", "UK  Birmingham", "UK  Boston"      ,
    )
 
  return placesList
End
Exit
 
 
Output:
UK  London
US  New York
US  Boston
US  Washington
UK  Washington
US  Birmingham
UK  Birmingham
UK  Boston

UK  Birmingham
UK  Boston
UK  London
UK  Washington
US  Birmingham
US  Boston
US  New York
US  Washington

[edit]Translation of Pseudocode

This version is a direct implementation of this task's pseudocode.
/* Rexx */
Do
  placesList = sampleData()
  call show placesList
  say
  sortedList = bubbleSort(placesList)
  call show sortedList
  say
 
  return
End
Exit
 
-- -----------------------------------------------------------------------------
bubbleSort:
procedure
Do
  il = arg(1)
  sl = il~copy
  itemCount = sl~size
 
  loop label c_ until \hasChanged
    hasChanged = isFalse()
    itemCount = itemCount - 1
    loop i_ = 1 to itemCount
      if sl[i_] > sl[i_ + 1] then do
        t_         = sl[i_]
        sl[i_]     = sl[i_ + 1]
        sl[i_ + 1] = t_
        hasChanged = isTrue()
        end
      end i_
    end c_
 
  return sl
End
Exit
 
-- -----------------------------------------------------------------------------
show:
procedure
Do
  al = arg(1)
 
  loop e_ over al
    say e_
    end e_
 
  return
End
Exit
 
-- -----------------------------------------------------------------------------
sampleData:
procedure
Do
  placesList = .array~of( ,
    "UK  London",     "US  New York",   "US  Boston",     "US  Washington", ,
    "UK  Washington", "US  Birmingham", "UK  Birmingham", "UK  Boston"      ,
    )
 
  return placesList
End
Exit
 
-- -----------------------------------------------------------------------------
isTrue: procedure
  return (1 == 1)
 
-- -----------------------------------------------------------------------------
isFalse: procedure
  return \isTrue()
 

[edit]Classic Rexx Implementation

A more "traditional" implementation of version 1 using only Rexx primitive constructs. This version has been tested with the Open Object Rexx and Regina Rexx interpreters and could equally have been exhibited as a Rexx solution.
/* Rexx */
Do
  placesList. = ''
  sortedList. = ''
  call sampleData
  call bubbleSort
 
  do i_ = 1 to placesList.0
    say placesList.i_
    end i_
  say
 
  do i_ = 1 to sortedList.0
    say sortedList.i_
    end i_
  say
 
  return
End
Exit
 
/* -------------------------------------------------------------------------- */
bubbleSort:
procedure expose sortedList. placesList.
Do
  /* Copy list */
  do !_ = 0 to placesList.0
    sortedList.!_ = placesList.!_
    end !_
 
  listLen = sortedList.0
  do i_ = 1 to listLen
    do j_ = i_ + 1 to listLen
      if sortedList.i_ > sortedList.j_ then do
        !_            = sortedList.j_
        sortedList.j_ = sortedList.i_
        sortedList.i_ = !_
        end
      end j_
    end i_
  return
End
Exit
 
/* -------------------------------------------------------------------------- */
sampleData:
procedure expose placesList.
Do
  ! = 0
  ! = ! + 1; placesList.0 = !; placesList.! = "UK  London"
  ! = ! + 1; placesList.0 = !; placesList.! = "US  New York"
  ! = ! + 1; placesList.0 = !; placesList.! = "US  Boston"
  ! = ! + 1; placesList.0 = !; placesList.! = "US  Washington"
  ! = ! + 1; placesList.0 = !; placesList.! = "UK  Washington"
  ! = ! + 1; placesList.0 = !; placesList.! = "US  Birmingham"
  ! = ! + 1; placesList.0 = !; placesList.! = "UK  Birmingham"
  ! = ! + 1; placesList.0 = !; placesList.! = "UK  Boston"
 
  return
End
Exit
 

[edit]Oz

In-place sorting of mutable arrays:
declare
  proc {BubbleSort Arr}
     proc {Swap I J}
        Arr.J := (Arr.I := Arr.J) %% assignment returns the old value
     end
     IsSorted = {NewCell false}
     MaxItem = {NewCell {Array.high Arr}-1}
  in
     for until:@IsSorted do
        IsSorted := true
        for I in {Array.low Arr}..@MaxItem do
           if Arr.I > Arr.(I+1) then
              IsSorted := false
              {Swap I I+1}
           end
        end
        MaxItem := @MaxItem - 1
     end
  end
  Arr = {Tuple.toArray unit(10 9 8 7 6 5 4 3 2 1)}
in
  {BubbleSort Arr}
  {Inspect Arr}
Purely-functional sorting of immutable lists:
declare
  local
     fun {Loop Xs Changed ?IsSorted}
        case Xs
        of X1|X2|Xr andthen X1 > X2 then
           X2|{Loop X1|Xr true IsSorted}
        [] X|Xr then
           X|{Loop Xr Changed IsSorted}
        [] nil then
           IsSorted = {Not Changed}
           nil
        end
     end
  in
     fun {BubbleSort Xs}
        IsSorted
        Result = {Loop Xs false ?IsSorted}
     in
        if IsSorted then Result
        else {BubbleSort Result}
        end
     end
  end
in
  {Show {BubbleSort [3 1 4 1 5 9 2 6 5]}}

[edit]PARI/GP

bubbleSort(v)={
  for(i=1,#v-1,
    for(j=i+1,#v,
      if(v[j]<v[i],
        my(t=v[j]);
        v[j]=v[i];
        v[i]=t
      )
    )
  );
  v
};

[edit]Pascal

procedure bubble_sort(var list: array of real);
var
  i, j, n: integer;
  t: real;
begin
  n := length(list);
  for i := n downto 2 do
    for j := 0 to i - 1 do
      if list[j] > list[j + 1] then
      begin
        t := list[j];
        list[j] := list[j + 1];
        list[j + 1] := t;
      end;
end;
Usage:
var
  list: array[0 .. 9] of real;
// ...
bubble_sort(list);

[edit]Perl

# Sorts an array in place
sub bubble_sort {
    for my $i (0 .. $#_){
        for my $j ($i + 1 .. $#_){
            $_[$j] < $_[$i] and @_[$i, $j] = @_[$j, $i];
        }
    }
}
Usage:
my @a = (39, 25, 30, 28, 36, 72, 98, 25, 43, 38);
bubble_sort(@a);

[edit]Perl 6

Works withRakudo version #24 "Seoul"
sub bubble_sort (@a is rw) {
    for ^@a -> $i {
        for $i ^..^ @a -> $j {
            @a[$j] < @a[$i] and @a[$i, $j] = @a[$j, $i];
        }
    }
}

[edit]PHP

function bubbleSort( array &$array )
{
 do
 {
  $swapped = false;
  for( $i = 0, $c = count( $array ) - 1; $i < $c; $i++ )
  {
   if( $array[$i] > $array[$i + 1] )
   {
    list( $array[$i + 1], $array[$i] ) =
      array( $array[$i], $array[$i + 1] );
    $swapped = true;
   }
  }
 }
 while( $swapped );
}

[edit]PL/I

/* A primitive bubble sort */
bubble_sort: procedure (A);
   declare A(*) fixed binary;
   declare temp fixed binary;
   declare i fixed binary, no_more_swaps bit (1) aligned;
 
   do until (no_more_swaps);
      no_more_swaps = true;
      do i = lbound(A,1) to hbound(A,1)-1;
         if A(i) > A(i+1) then
            do; temp = A(i); A(i) = A(i+1); A(i+1) = temp;
                no_more_swaps = false;
            end;
      end;
   end;
end bubble_sort;

[edit]PicoLisp

(de bubbleSort (Lst)
   (use Chg
      (loop
         (off Chg)
         (for (L Lst (cdr L) (cdr L))
            (when (> (car L) (cadr L))
               (xchg L (cdr L))
               (on Chg) ) )
         (NIL Chg Lst) ) ) )

[edit]Pop11

define bubble_sort(v);
lvars n=length(v), done=false, i;
while not(done) do
   true -> done;
   n - 1 -> n;
   for i from 1 to n do
      if v(i) > v(i+1) then
         false -> done;
         ;;; Swap using multiple assignment
         (v(i+1), v(i)) -> (v(i), v(i+1));
      endif;
   endfor;
endwhile;
enddefine;
 
;;; Test it
vars ar = { 10 8 6 4 2 1 3 5 7 9};
bubble_sort(ar);
ar =>

[edit]PostScript

 
/bubblesort{
/x exch def
/temp x x length 1 sub get def
/i x length 1 sub def
/j i 1 sub def
 
x length 1 sub{
i 1 sub{
x j 1 sub get x j get lt
{
/temp x j 1 sub get def
x j 1 sub x j get put
x j temp put
}if
/j j 1 sub def
}repeat
/i i 1 sub def
/j i 1 sub def
}repeat
x pstack
}def
 

[edit]PowerShell

function bubblesort ($a) {
    $l = $a.Length
    $hasChanged = $true
    while ($hasChanged) {
        $hasChanged = $false
        $l--
        for ($i = 0; $i -lt $l; $i++) {
            if ($a[$i] -gt $a[$i+1]) {
                $a[$i], $a[$i+1] = $a[$i+1], $a[$i]
                $hasChanged = $true
            }
        }
    }
}

[edit]Prolog

It's surprisingly easy in Prolog while coding this sort, to accidentally create a sort that is similar, but not identical to the bubble sort algorithm. Some of these are easier and shorter to code and work as well if not better. Having said that, it's difficult to think of a reason to code the bubble sort these days except as an example of inefficiency.
%___________________________________________________________________________
% Bubble sort
 
bubble(0, Res, Res, sorted).
bubble(Len, [A,B|T], Res, unsorted) :- A > B, !, bubble(Len,[B,A|T], Res, _).
bubble(Len, [A|T], [A|Ts], Ch) :- L is Len-1, bubble(L, T, Ts, Ch).
 
bubblesort(In, Out) :- length(In, Len), bubblesort(Len, In, Out).
bubblesort(0, In, In).
bubblesort(Len, In, Out) :-
 bubble(Len, In, Bubbled, SortFlag),  % bubble the list
 (SortFlag=sorted -> Out=Bubbled;     % list is already sorted
  SegLen is Len - 1,       % one fewer to process
  writef('bubbled=%w\n', [Bubbled]),  % show progress
  bubblesort(SegLen, Bubbled, Out)).
 
test :-  In = [8,9,1,3,4,2,6,5,4],
  writef('  input=%w\n', [In]),
  bubblesort(In, R),
  writef('-> %w\n', [R]).
for example:
?- test.
  input=[8,9,1,3,4,2,6,5,4]
bubbled=[8,1,3,4,2,6,5,4,9]
bubbled=[1,3,4,2,6,5,4,8,9]
bubbled=[1,3,2,4,5,4,6,8,9]
bubbled=[1,2,3,4,4,5,6,8,9]
-> [1,2,3,4,4,5,6,8,9]
true.

[edit]Alternative version

Should be ISO (but tested only with GNU Prolog). Note: doesn't constuct list for each swap, only for each pass.
:- initialization(main).
 
 
bubble_sort(Xs,Res) :-
    write(Xs), nl
  , bubble_pass(Xs,Ys,Changed)
  , ( Changed == true -> bubble_sort(Ys,Res) ; Res = Xs )
  .
 
bubble_pass(Xs,Res,Changed) :-
    Xs = [X|Ys], Ys = [Y|Zs]
  , ( X > Y -> H = Y, T = [X|Zs], Changed = true
             ; H = X, T = Ys
    )
  , Res = [H|R], !, bubble_pass(T,R,Changed)
  ; Res = Xs
  .
 
 
test([8,9,1,3,4,2,6,5,4]).
 
main :- test(T), bubble_sort(T,_), halt.
Output:
[8,9,1,3,4,2,6,5,4]
[8,1,3,4,2,6,5,4,9]
[1,3,4,2,6,5,4,8,9]
[1,3,2,4,5,4,6,8,9]
[1,2,3,4,4,5,6,8,9]

[edit]PureBasic

Procedure bubbleSort(Array a(1))
  Protected i, itemCount, hasChanged
 
  itemCount = ArraySize(a())
  Repeat
    hasChanged = #False
    itemCount - 1
    For i = 0 To itemCount
      If a(i) > a(i + 1)
        Swap a(i), a(i + 1)
        hasChanged = #True
      EndIf 
    Next  
  Until hasChanged = #False
EndProcedure

[edit]Python

def bubble_sort(seq):
    """Inefficiently sort the mutable sequence (list) in place.
       seq MUST BE A MUTABLE SEQUENCE.
 
       As with list.sort() and random.shuffle this does NOT return 
    """
    changed = True
    while changed:
        changed = False
        for i in xrange(len(seq) - 1):
            if seq[i] > seq[i+1]:
                seq[i], seq[i+1] = seq[i+1], seq[i]
                changed = True
    return None
 
if __name__ == "__main__":
   """Sample usage and simple test suite"""
 
   from random import shuffle
 
   testset = range(100)
   testcase = testset[:] # make a copy
   shuffle(testcase)
   assert testcase != testset  # we've shuffled it
   bubble_sort(testcase)
   assert testcase == testset  # we've unshuffled it back into a copy

[edit]Qi

(define bubble-shot
  [A]     -> [A]
  [A B|R] -> [B|(bubble-shot [A|R])] where (> A B)
  [A  |R] -> [A|(bubble-shot R)])
 
(define bubble-sort
  X -> (fix bubble-shot X))
 
(bubble-sort [6 8 5 9 3 2 2 1 4 7])
 

[edit]R

bubblesort <- function(v) {
  itemCount <- length(v)
  repeat {
    hasChanged <- FALSE
    itemCount <- itemCount - 1
    for(i in 1:itemCount) {
      if ( v[i] > v[i+1] ) {
        t <- v[i]
        v[i] <- v[i+1]
        v[i+1] <- t
        hasChanged <- TRUE
      }
    }
    if ( !hasChanged ) break;
  }
  v
}
 
v <- c(9,8,7,3,1,100)
print(bubblesort(v))

[edit]Ra

 
class BubbleSort
 **Sort a list with the Bubble Sort algorithm**
 
 on start
 
  args := program arguments
  .sort(args)
  print args
 
 define sort(list) is shared
  **Sort the list**
 
  test
   list := [4, 2, 7, 3]
   .sort(list)
   assert list = [2, 3, 4, 7]
 
  body
   last := list.count - 1
 
   post while changed
 
    changed := false
 
    for i in last
 
     if list[i] > list[i + 1]
      temp := list[i]
      list[i] := list[i + 1]
      list[i + 1] := temp
      changed := true
 

[edit]Racket

This bubble sort sorts the elelement in the vector v with regard to <?.
 
#lang racket
 
(define (bubble-sort <? v)
  (define len (vector-length v))
  (define ref vector-ref)
  (let loop ([max len] 
             [again? #f])
    (for ([i (in-range 0 (- max 1))]
          [j (in-range 1 max)])
      (define vi (ref v i))
      (when (<? (ref v j) vi)
        (vector-set! v i (ref v j))
        (vector-set! v j vi)
        (set! again? #t)))
    (when again? (loop (- max 1) #f)))
  v)
 
Example: Sorting a vector of length 10 with random entries.
 
(bubble-sort < (for/vector ([_ 10]) (random 20)))
 

[edit]REALbasic

Sorts an array of Integers
 
  Dim sortable() As Integer ' assume the array is populated  sortable.Shuffle() ' sortable is now randomized  Dim swapped As Boolean
  Do
    Dim index, bound As Integer
    bound = sortable.Ubound
 
    While index < bound
      If Sortable(index) > Sortable(index + 1) Then
        Dim s As Integer = Sortable(index)
        Sortable.Remove(index)
        Sortable.Insert(index + 1, s)
        swapped = True
      End If
      index = index + 1
    Wend
 
  Loop Until Not swapped
'sortable is now sorted

[edit]REXX

/*REXX program sorts an array using the  bubble-sort  algorithm.        */
call gen@                              /*generate the array elements.   */
call show@  'before sort'              /*show the before array elements.*/
call bubbleSort   #                    /*invoke the bubble sort.        */
call show@  ' after sort'              /*show the  after array elements.*/
exit                                   /*stick a fork in it, we're done.*/
/*──────────────────────────────────BUBBLESORT subroutine───────────────*/
bubbleSort: procedure expose @.; parse arg n      /*N:  number of items.*/
                                       /*diminish # items each time.    */
  do  until done                       /*sort until it's done.          */
  done=1                               /*assume it's done   (1 ≡ true). */
         do j=1  for n-1               /*sort M items this time around. */
          k=j+1                        /*point to the next item.        */
          if @.j>@.k  then do          /*is it out of order?            */
                           _=@.j       /*assign to a temp variable.     */
                           @.j=@.k     /*swap current item with next ···*/
                           @.k=_       /*      ··· and the next with  _ */
                           done=0      /*indicate it's not done, whereas*/
                           end         /*  [↑]      1≡true      0≡false */
          end   /*j*/
  end           /*until done*/
return
/*──────────────────────────────────GEN@ subroutine─────────────────────*/
gen@: @.=                              /*assign default value to all @. */
@.1  = '---letters of the Hebrew alphabet---' ;   @.13 = 'kaph    [kaf]'
@.2  = '====================================' ;   @.14 = 'lamed'
@.3  = 'aleph   [alef]'                       ;   @.15 = 'mem'
@.4  = 'beth    [bet]'                        ;   @.16 = 'nun'
@.5  = 'gimel'                                ;   @.17 = 'samekh'
@.6  = 'daleth  [dalet]'                      ;   @.18 = 'ayin'
@.7  = 'he'                                   ;   @.19 = 'pe'
@.8  = 'waw     [vav]'                        ;   @.20 = 'sadhe   [tsadi]'
@.9  = 'zayin'                                ;   @.21 = 'qoph    [qof]'
@.10 = 'heth    [het]'                        ;   @.22 = 'resh'
@.11 = 'teth    [tet]'                        ;   @.23 = 'shin'
@.12 = 'yod'                                  ;   @.24 = 'taw     [tav]'
 
        do #=1  while  @.# \==''       /*find how many entries in list. */
        end   /*#*/
#=#-1                                  /*adjust because of DO increment.*/
return
/*──────────────────────────────────SHOW@ subroutine────────────────────*/
show@: widthH=length(#)                /*maximum width of any line.     */
                         do j=1  for #
                         say 'element'   right(j,widthH)   arg(1)':'   @.j
                         end   /*j*/
say copies('─',80)                     /*show a separator line.         */
return
Output:
element  1 before sort: ---letters of the Hebrew alphabet---
element  2 before sort: ====================================
element  3 before sort: aleph   [alef]
element  4 before sort: beth    [bet]
element  5 before sort: gimel
element  6 before sort: daleth  [dalet]
element  7 before sort: he
element  8 before sort: waw     [vav]
element  9 before sort: zayin
element 10 before sort: heth    [het]
element 11 before sort: teth    [tet]
element 12 before sort: yod
element 13 before sort: kaph    [kaf]
element 14 before sort: lamed
element 15 before sort: mem
element 16 before sort: nun
element 17 before sort: samekh
element 18 before sort: ayin
element 19 before sort: pe
element 20 before sort: sadhe   [tsadi]
element 21 before sort: qoph    [qof]
element 22 before sort: resh
element 23 before sort: shin
element 24 before sort: taw     [tav]
────────────────────────────────────────────────────────────────────────────────
element  1  after sort: ---letters of the Hebrew alphabet---
element  2  after sort: ====================================
element  3  after sort: aleph   [alef]
element  4  after sort: ayin
element  5  after sort: beth    [bet]
element  6  after sort: daleth  [dalet]
element  7  after sort: gimel
element  8  after sort: he
element  9  after sort: heth    [het]
element 10  after sort: kaph    [kaf]
element 11  after sort: lamed
element 12  after sort: mem
element 13  after sort: nun
element 14  after sort: pe
element 15  after sort: qoph    [qof]
element 16  after sort: resh
element 17  after sort: sadhe   [tsadi]
element 18  after sort: samekh
element 19  after sort: shin
element 20  after sort: taw     [tav]
element 21  after sort: teth    [tet]
element 22  after sort: waw     [vav]
element 23  after sort: yod
element 24  after sort: zayin
────────────────────────────────────────────────────────────────────────────────

[edit]Ruby

Generally, this task should be accomplished in Ruby using Array.sort!. Here we take an approach that's more comparable with the other examples on this page.
This example adds the bubblesort! method to the Array object. Below are two different methods that show four different iterating constructs in ruby.
class Array
  def bubblesort1!
    length.times do |j|
      for i in 1...(length - j)
        if self[i] < self[i - 1]
          self[i], self[i - 1] = self[i - 1], self[i]
        end
      end
    end
    self
  end
   def bubblesort2!
    each_index do |index|
      (length - 1).downto( index ) do |i|
        self[i-1], self[i] = self[i], self[i-1] if self[i-1] < self[i]
      end
    end
    self
  end
end
ary = [3, 78, 4, 23, 6, 8, 6]
ary.bubblesort1!
p ary
# => [3, 4, 6, 6, 8, 23, 78]

[edit]Run BASIC

siz = 100
dim data$(siz)
unSorted = 1
 
WHILE unSorted
  unSorted = 0
  FOR i = 1 TO siz -1
    IF data$(i) > data$(i + 1) THEN
      tmp       = data$(i)
      data$(i)  = data$(i + 1)
      data$(i + 1) = tmp
      unSorted  = 1
    END IF
  NEXT
WEND

[edit]Sather

class SORT{T < $IS_LT{T}} is
  private swap(inout a, inout b:T) is
    temp ::= a;
    a := b;
    b := temp;
  end;
  bubble_sort(inout a:ARRAY{T}) is
    i:INT;
    if a.size < 2 then return; end;
    loop
      sorted ::= true;
      loop i := 0.upto!(a.size - 2);
        if a[i+1] < a[i] then
          swap(inout a[i+1], inout a[i]);
          sorted := false;
        end;
      end;
      until!(sorted);
    end;
  end;
end;
class MAIN is
  main is
    a:ARRAY{INT} := |10, 9, 8, 7, 6, -10, 5, 4|;
    SORT{INT}::bubble_sort(inout a);
    #OUT + a + "\n";
  end;
end;
This should be able to sort (in ascending order) any object for which is_lt (less than) is defined.

[edit]Scala

Library: Scala
This slightly more complex version of Bubble Sort avoids errors with indices.
def bubbleSort[T](arr: Array[T])(implicit o: Ordering[T]) {
  import o._
  val consecutiveIndices = (arr.indices, arr.indices drop 1).zipped
  var hasChanged = true
  do {
    hasChanged = false
    consecutiveIndices foreach { (i1, i2) =>
      if (arr(i1) > arr(i2)) {
        hasChanged = true
        val tmp = arr(i1)
        arr(i1) = arr(i2)
        arr(i2) = tmp
      }
    }
  } while(hasChanged)
}
import scala.annotation.tailrec
 
def bubbleSort(xt: List[Int]) = {
  @tailrec
  def bubble(xs: List[Int], rest: List[Int], sorted: List[Int]): List[Int] = xs match {
    case x :: Nil =>
      if (rest.isEmpty) x :: sorted
      else bubble(rest, Nil, x :: sorted)
    case a :: b :: xs =>
      if (a > b) bubble(a :: xs, b :: rest, sorted)
      else       bubble(b :: xs, a :: rest, sorted)
  }
  bubble(xt, Nil, Nil)
}

[edit]Scheme

(define (bubble-sort x gt?)
  (letrec
    ((fix (lambda (f i)
       (if (equal? i (f i))
           i
           (fix f (f i)))))
 
     (sort-step (lambda (l)
        (if (or (null? l) (null? (cdr l)))
            l
            (if (gt? (car l) (cadr l))
                (cons (cadr l) (sort-step (cons (car l) (cddr l))))
                (cons (car  l) (sort-step (cdr l))))))))
 
  (fix sort-step x)))
This solution recursively finds the fixed point of sort-step. A comparison function must be passed to bubblesort. Example usages:
(bubble-sort (list 1 3 5 9 8 6 4 2) >)
(bubble-sort (string->list "Monkey") char<?)
Here is the same function, using a different syntax:
(define (bsort l gt?)
  (define (dosort l)
    (cond ((null? (cdr l))
           l)
          ((gt? (car l) (cadr l))
           (cons (cadr l) (dosort (cons (car l) (cddr l)))))
          (else 
           (cons (car l) (dosort (cdr l))))))
  (let ((try (dosort l)))
    (if (equal? l try)
        l
        (bsort try gt?))))
 
For example, you could do
(bsort > '(2 4 6 2))
(1 2 3)

[edit]Scilab

function b=BubbleSort(a)
  n=length(a)
  swapped=%T
  while swapped
    swapped=%F
    for i=1:1:n-1
      if a(i)>a(i+1) then
        temp=a(i)
        a(i)=a(i+1)
        a(i+1)=temp
        swapped=%T
      end
    end
  end
  b=a
endfunction BubbleSort
Output:
-->y=[5 4 3 2 1]
 y  =
     5.    4.    3.    2.    1.  
-->x=BubbleSort(a) 
 x  =
     1.    2.    3.    4.    5.  

[edit]Scratch

This solution is hosted at the Scratch site, because it is difficult to document visual programming solutions directly here at Rosetta Code. There you can see the solution results as well as examine the code. This solution is intended to illustrate the Bubble sort algorithm rather than to maximize performance. Scratch provides visual queues to indicate list access, and these are used to help show what is happening.

[edit]Seed7

const proc: bubbleSort (inout array elemType: arr) is func
  local
    var boolean: swapped is FALSE;
    var integer: i is 0;
    var elemType: help is elemType.value;
  begin
    repeat
      swapped := FALSE;
      for i range 1 to length(arr) - 1 do
        if arr[i] > arr[i + 1] then
          help := arr[i];
          arr[i] := arr[i + 1];
          arr[i + 1] := help;
          swapped := TRUE;
        end if;
      end for;
    until not swapped;
  end func;
Original source: [2]

[edit]Sidef

func bubble_sort(arr is Array) -> Array {
    loop {
        var swapped = false;
        { |i|
            arr[i-1] > arr[i] && (
                arr[i-1, i] = arr[i, i-1];
                swapped = true;
            );
        } * arr.offset;
        swapped || break;
    };
    return arr;
};

[edit]Smalltalk

A straight translation from the pseudocode above. Swap is done with a block closure.
|item swap itemCount hasChanged|
item := #(1 4 5 6 10 8 7 61 0 -3) copy.
swap := 
 [:indexOne :indexTwo| 
 |temp|
 temp := item at: indexOne.
 item at: indexOne put: (item at: indexTwo).
 item at: indexTwo put: temp].
 
itemCount := item size.
[hasChanged := false.
itemCount := itemCount - 1.
1 to: itemCount do:
 [:index | 
 (item at: index) > (item at: index + 1) ifTrue:
  [swap value: index value: index + 1.
  hasChanged := true]].
hasChanged] whileTrue.

[edit]SNOBOL4

*       # Sort array in place, return array
        define('bubble(a,alen)i,j,ub,tmp') :(bubble_end)
bubble  i = 1; ub = alen
outer   gt(ub,1) :f(bdone)
        j = 1
inner   le(a<j>, a<j + 1>) :s(incrj)
        tmp = a<j>
        a<j> = a<j + 1>
        a<j + 1> = tmp
incrj   j = lt(j + 1,ub) j + 1 :s(inner)
        ub = ub - 1 :(outer)
bdone   bubble = a :(return)
bubble_end
 
*       # Fill array with test data
        str = '33 99 15 54 1 20 88 47 68 72'
        output = str; arr = array(10)
floop   i = i + 1; str span('0123456789') . arr<i> = :s(floop)
 
*       # Test and display
        bubble(arr,10); str = ''
sloop   j = j + 1; str = str arr<j> ' ' :s(sloop)
        output = trim(str)
end
Output:
33 99 15 54 1 20 88 47 68 72
1 15 20 33 47 54 68 72 88 99

[edit]SPARK

Works withSPARK GPL version 2010
The first version is based on the Ada version, with Integer for both the array index and the array element.
Static analysis of this code shows that it is guaranteed free of any run-time error when called from any other SPARK code.
package Bubble
is
 
   type Arr is array(Integer range <>) of Integer;
 
   procedure Sort (A : in out Arr);
   --# derives A from *;
 
end Bubble;
 
 
package body Bubble
is
   procedure Sort (A : in out Arr)
   is
      Finished : Boolean;
      Temp     : Integer;
   begin
      if A'Last /= A'First then
         loop
            Finished := True;
            for J in Integer range A'First .. A'Last - 1 loop
               if A (J + 1) < A (J) then
                  Finished := False;
                  Temp := A (J + 1);
                  A (J + 1) := A (J);
                  A (J) := Temp;
               end if;
            end loop;
            --# assert A'Last /= A'First;
            exit when Finished;
         end loop;
      end if;
   end Sort;
 
end Bubble;
 
The next version has a postcondition to guarantee that the returned array is sorted correctly. This requires the two proof rules that follow the source. The Ada code is identical with the first version.
package Bubble
is
 
   type Arr is array(Integer range <>) of Integer;
 
   --  Sorted is a proof function with the definition:
   --    Sorted(A, From_I, To_I)
   --      <->
   --    (for all I in Integer range From_I .. To_I - 1 =>
   --               (A(I) <= A(I + 1))) .
   --
   --# function Sorted (A            : Arr;
   --#                  From_I, To_I : Integer) return Boolean;
 
   procedure Sort (A : in out Arr);
   --# derives A from *;
   --# post Sorted(A, A'First, A'Last);
 
end Bubble;
 
 
package body Bubble
is
   procedure Sort (A : in out Arr)
   is
      Finished : Boolean;
      Temp     : Integer;
   begin
      if A'Last > A'First then
         loop
            Finished := True;
            for J in Integer range A'First .. A'Last - 1
            --# assert Finished -> Sorted(A, A'First, J);
            loop
               if A (J + 1) < A (J) then
                  Finished := False;
                  Temp := A (J + 1);
                  A (J + 1) := A (J);
                  A (J) := Temp;
               end if;
            end loop;
            --# assert A'Last /= A'First
            --#   and  (Finished -> Sorted(A, A'First, A'Last));
            exit when Finished;
         end loop;
      end if;
   end Sort;
 
end Bubble;
 
The proof rules are stated here without justification (but they are fairly obvious). A formal proof of these rules from the definition of Sorted has been completed.
bubble_sort_rule(1): sorted(A, I, J)
                       may_be_deduced_from
                     [ J <= I ] .

bubble_sort_rule(2): Fin -> sorted(A, I, J + 1)
                       may_be_deduced_from
                     [ Fin -> sorted(A, I, J),
                       element(A, [J]) <= element(A, [J + 1]) ] .
Both of the two versions above use an inner loop that scans over all the array on every pass of the outer loop. This makes the proof in the second version very simple.
The final version scans over a reducing portion of the array in the inner loop, consequently the proof becomes more complex. The package specification for this version is the same as the second version above. The package body defines two more proof functions.
package body Bubble
is
   procedure Sort (A : in out Arr)
   is
      Finished : Boolean;
 
      --  In_Position is a proof function with the definition:
      --    In_Position(A, A_Start, A_I, A_End)
      --      <->
      --    ((for all K in Integer range A_Start .. A_I - 1 =>
      --                (A(K) <= A(A_I)))
      --     and
      --     Sorted(A, A_I, A_End) .
      --
      --# function In_Position (A                  : Arr;
      --#                       A_Start, A_I, A_End : Integer) return Boolean;
 
      --  Swapped is a proof function with the definition:
      --    Swapped(A_In, A_Out, I1, I2)
      --      <->
      --    (A_Out = A_In[I1 => A_In(I2); I2 => A_In(I1)]).
      --
      --# function Swapped (A_In, A_Out : Arr;
      --#                   I1, I2      : Integer) return Boolean;
 
      procedure Swap (A  : in out Arr;
                      I1 : in     Integer;
                      I2 : in     Integer)
      --# derives A from *, I1, I2;
      --# pre  I1 in A'First .. A'Last
      --#  and I2 in A'First .. A'Last;
      --# post Swapped(A~, A, I1, I2);
      is
         Temp : Integer;
      begin
         Temp  := A(I2);
         A(I2) := A(I1);
         A(I1) := Temp;
      end Swap;
      pragma Inline (Swap);
 
   begin
      if A'Last > A'First then
         for I in reverse Integer range A'First + 1 .. A'Last loop
            Finished := True;
            for J in Integer range A'First .. I - 1 loop
               if A (J + 1) < A (J) then
                  Finished := False;
                  Swap (A, J, J + 1);
               end if;
               --# assert I% = I  --  I is unchanged by execution of the loop
               --#   and  (for all K in Integer range A'First .. J =>
               --#                    (A(K) <= A(J + 1)))
               --#   and  (I < A'Last -> In_Position(A, A'First, I + 1, A'Last))
               --#   and  (Finished -> Sorted(A, A'First, J + 1));
            end loop;
            exit when Finished;
            --# assert In_Position(A, A'First, I, A'Last);
         end loop;
      end if;
   end Sort;
 
end Bubble;
 
Completion of the proof of this version requires more rules than the previous version and they are rather more complex. Creation of these rules is quite straightforward - I tend to write whatever rules the Simplifier needs first and then validate them afterwards. A formal proof of these rules from the definition of Sorted, In_Position and Swapped has been completed.
bubble_sort_rule(1):  sorted(A, I, J)
                        may_be_deduced_from
                      [ J <= I ] .

bubble_sort_rule(2):  sorted(A, I - 1, J)
                        may_be_deduced_from
                      [ sorted(A, I, J),
                        element(A, [I - 1]) <= element(A, [I]) ] .

bubble_sort_rule(3):  Fin -> sorted(A, I, J + 1)
                        may_be_deduced_from
                      [ Fin -> sorted(A, I, J),
                        element(A, [J]) <= element(A, [J + 1]) ] .

bubble_sort_rule(4):  sorted(A, Fst, Lst)
                        may_be_deduced_from
                      [ sorted(A, Fst, I),
                        I < Lst -> in_position(A, Fst, I + 1, Lst),
                        I <= Lst ] .

bubble_sort_rule(5):  in_position(A, Fst, I, Lst)
                        may_be_deduced_from
                      [ I < Lst -> in_position(A, Fst, I + 1, Lst),
                        for_all(K : integer, Fst <= K and K <= I - 1
                                  -> element(A, [K]) <= element(A, [I])),
                        I >= Fst,
                        I <= Lst ] .

bubble_sort_rule(6):  I < Lst -> in_position(A2, Fst, I + 1, Lst)
                        may_be_deduced_from
                      [ I < Lst -> in_position(A1, Fst, I + 1, Lst),
                        swapped(A1, A2, J + 1, J + 2),
                        J + 2 < I + 1,
                        J >= Fst ] .

bubble_sort_rule(7):  I - 1 < Lst -> in_position(A2, Fst, I, Lst)
                        may_be_deduced_from
                      [ in_position(A1, Fst, I, Lst),
                        swapped(A1, A2, J, J + 1),
                        J + 1 < I,
                        J >= Fst ] .

bubble_sort_rule(8):  for_all(K : integer, I <= K and K <= I
                                 -> element(A, [K]) <= element(A, [I + 1]))
                        may_be_deduced_from
                      [ element(A, [I]) <= element(A, [I + 1]) ] .

bubble_sort_rule(9):  for_all(K : integer, I <= K and K <= I
                                 -> element(A2, [K]) <= element(A2, [I + 1]))
                        may_be_deduced_from
                      [ element(A1, [I]) > element(A1, [I + 1]),
                        swapped(A1, A2, I, I + 1) ] .

bubble_sort_rule(10): for_all(K2 : integer, Fst <= K2 and K2 <= J + 1
                                 -> element(A, [K2]) <= element(A, [J + 2]))
                        may_be_deduced_from
                      [ for_all(K1 : integer, Fst <= K1 and K1 <= J
                                   -> element(A, [K1]) <= element(A, [J + 1])),
                        element(A, [J + 1]) <= element(A, [J + 2]) ] .

bubble_sort_rule(11): for_all(K2 : integer, Fst <= K2 and K2 <= J + 1
                                 -> element(A2, [K2]) <= element(A2, [J + 2]))
                        may_be_deduced_from
                      [ for_all(K1 : integer, Fst <= K1 and K1 <= J
                                   -> element(A1, [K1]) <= element(A1, [J + 1])),
                        element(A1, [J + 1]) > element(A1, [J + 2]),
                        swapped(A1, A2, J + 1, J + 2) ] .

[edit]Standard ML

Assumes a list of integers.
fun bubble_select [] = []
  | bubble_select [a] = [a]
  | bubble_select (a::b::xs) =
    if b < a then b::(bubble_select(a::xs)) else a::(bubble_select(b::xs))
 
fun bubblesort [] = []
  | bubblesort (x::xs) =bubble_select (x::(bubblesort xs))

[edit]Swift

func bubbleSort<T:Comparable>(inout list:[T]) {
    var done = false
    while !done {
        done = true
        for i in 1..<list.count {
            if list[i - 1] > list[i] {
                (list[i], list[i - 1]) = (list[i - 1], list[i])
                done = false
            }
        }
    }
}

[edit]TI-83 BASIC

Input your data into L1 and run this program to organize it.
:L1→L2
:1+dim(L2)→N
:For(D,1,dim(L2))
:N-1→N
:0→I
:For(C,1,dim(L2)-2)
:For(A,dim(L2)-N+1,dim(L2)-1)
:If L2(A)>L2(A+1)
:Then
:1→I
:L2(A)→B
:L2(A+1)→L2(A)
:B→L2(A+1)
:End
:End
:End
:If I=0
:Goto C
:End
:Lbl C
:If L2(1)>L2(2)
:Then
:L2(1)→B
:L2(2)→L2(1)
:B→L2(2)
:End
:DelVar A
:DelVar B
:DelVar C
:DelVar D
:DelVar N
:DelVar I
:Return
:"ODD-EVEN"
:L1→L2(
:1+dim(L2)→N
:For(D,1,dim(L2))
:N-1→N
:0→O
:For(C,1,dim(L2)-2)
:For(A,dim(L2)-N+2,dim(L2)-1,2)
:If L2(A)>L2(A+1)
:Then
:1→O
:L2(A)→B
:L2(A+1)→L2(A)
:B→L2(A+1)
:End
:End
:For(A,dim(L2)-N+1,dim(L2)-1,2)
:If L2(A)>L2(A+1)
:Then
:1→O
:L2(A)→B
:L2(A+1)→L2(A)
:B→L2(A+1)
:End
:End
:End
:If O=0
:Goto C
:End
:Lbl C
:If L2(1)>L2(2)
:Then
:L2(1)→B
:L2(2)→L2(1)
:B→L2(2)
:End
:DelVar A
:DelVar B
:DelVar C
:DelVar D
:DelVar N
:DelVar O
:Return
Implementation of the pseudo code given at the top of the page. Place data to be sorted in L1
:dim(L1)→D
:Repeat C=0
  :0→C
  :D–1→D
  :For(I,1,D)
    :If L1(I)>L1(I+1):Then
      :L1(I)→C
      :L1(I+1)→L1(I)
      :C→L1(I+1)
      :1→C
    :End
  :End
:End
:L1

[edit]Tcl

Library: Tcllib (Package: struct::list)
package require Tcl 8.5
package require struct::list
 
proc bubblesort {A} {
    set len [llength $A]
    set swapped true
    while {$swapped} {
        set swapped false
        for {set i 0} {$i < $len - 1} {incr i} {
            set j [expr {$i + 1}]
            if {[lindex $A $i] > [lindex $A $j]} {
                struct::list swap A $i $j
                set swapped true
            }
        }
        incr len -1
    }
    return $A
}
 
puts [bubblesort {8 6 4 2 1 3 5 7 9}] ;# => 1 2 3 4 5 6 7 8 9
Idiomatic code uses the builtin lsort instead, which is a stable O(n log n) sort.

[edit]Toka

Toka does not have a bubble sort predefined, but it is easy to code a simple one:
#! A simple Bubble Sort function
value| array count changed |
[ ( address count -- )
  to count to array
  count 0
  [ count 0
    [ i array array.get i 1 + array array.get 2dup >
      [ i array array.put  i 1 + array array.put ]
      [ 2drop ] ifTrueFalse
    ] countedLoop
    count 1 - to count
  ] countedLoop
] is bsort
 
#! Code to display an array
[ ( array count -- ) 
  0 swap [ dup i swap array.get . ] countedLoop drop cr 
] is .array
 
#! Create a 10-cell array
10 cells is-array foo
 
#! Fill it with random values
  20  1 foo array.put
  50  2 foo array.put
 650  3 foo array.put
 120  4 foo array.put
 110  5 foo array.put
 101  6 foo array.put
1321  7 foo array.put
1310  8 foo array.put
 987  9 foo array.put
 10 10 foo array.put
 
#! Display the array, sort it, and display it again
foo 10 .array
foo 10 bsort
foo 10 .array

[edit]TorqueScript

//Note that we're assuming that the list of numbers is separated by tabs.
function bubbleSort(%list)
{
 %ct = getFieldCount(%list);
 for(%i = 0; %i < %ct; %i++)
 {
  for(%k = 0; %k < (%ct - %i - 1); %k++)
  {
   if(getField(%list, %k) > getField(%list, %k+1))
   {
    %tmp = getField(%list, %k);
    %list = setField(%list, %k, getField(%list, %k+1));
    %list = setField(%list, %k+1, %tmp);
   }
  }
 }
 return %list;
}

[edit]Unicon

See Icon.

[edit]UnixPipes

rm -f _sortpass 
 
reset() {
   test -f _tosort || mv _sortpass _tosort
}
 
bpass() {
  (read a; read b
  test -n "$b" -a "$a" && (
      test $a -gt $b && (reset; echo $b;  (echo $a ; cat) | bpass ) || (echo $a;  (echo $b ; cat) | bpass )
  ) || echo $a)
}
 
bubblesort() {
  cat > _tosort
  while test -f _tosort
  do
      cat _tosort | (rm _tosort;cat) |bpass > _sortpass
  done
  cat _sortpass
}
 
cat to.sort | bubblesort

[edit]Ursala

The bubblesort function is parameterized by a relational predicate.
#import nat
 
bubblesort "p" = @iNX ^=T ^llPrEZryPrzPlrPCXlQ/~& @l ~&aitB^?\~&a "p"?ahthPX/~&ahPfatPRC ~&ath2fahttPCPRC
 
#cast %nL
 
example = bubblesort(nleq) <362,212,449,270,677,247,567,532,140,315>
Output:
<140,212,247,270,315,362,449,532,567,677>

[edit]VBScript

Doing the decr and incr thing is superfluous, really. I just had stumbled over the byref thing for swap and wanted to see where else it would work.
For those unfamiliar with Perth, WA Australia, the five strings being sorted are names of highways.
[edit]Implementation
 
sub decr( byref n )
 n = n - 1
end sub
 
sub incr( byref n )
 n = n + 1
end sub
 
sub swap( byref a, byref b)
 dim tmp
 tmp = a
 a = b
 b = tmp
end sub
 
function bubbleSort( a )
 dim changed
 dim itemCount
 itemCount = ubound(a) 
 do
  changed = false
  decr itemCount
  for i = 0 to itemCount
   if a(i) > a(i+1) then
    swap a(i), a(i+1)
    changed = true
   end if
  next
 loop until not changed
 bubbleSort = a
end function
 
[edit]Invocation
 
dim a
a = array( "great eastern", "roe", "stirling", "albany", "leach")
wscript.echo join(a,", ")
bubbleSort a
wscript.echo join(a,", ")
 
Output:
great eastern, roe, stirling, albany, leach
albany, great eastern, leach, roe, stirling

[edit]Visual Basic .NET

Platform: .NET
Works withVisual Basic .NET version 9.0+
Do Until NoMoreSwaps = True
     NoMoreSwaps = True
     For Counter = 1 To (NumberOfItems - 1)
         If List(Counter) > List(Counter + 1) Then
             NoMoreSwaps = False
             Temp = List(Counter)
             List(Counter) = List(Counter + 1)
             List(Counter + 1) = Temp
         End If
     Next
     NumberOfItems = NumberOfItems - 1
Loop

[edit]X86 Assembly

Translation of XPL0. Assemble with tasm, tlink /t
        .model  tiny
        .code
        .486
        org     100h
start:  mov     si, offset array
        mov     ax, 40          ;length of array (not including $)
        call    bsort
        mov     dx, si          ;point to array
        mov     ah, 09h         ;display it as a string
        int     21h
        ret
array   db      "Pack my box with five dozen liquor jugs.$"
 
;Bubble sort: si = array addrsss, ax = number of bytes
bsort:  pusha
        xchg    cx, ax          ;get size of array N
        dec     cx              ;for J:= N-1 downto 0
bs10:   xor     bx, bx          ;for I:= 0 to J-1
bs20:   mov     ax, [bx+si]
        cmp     al, ah          ;if A(I) > A(I+1) then
        jbe     bs30
         xchg   al, ah          ; swap bytes
         mov    [bx+si], ax
bs30:   inc     bx              ;next I
        cmp     bx, cx
        jb      bs20
        loop    bs10
        popa
        ret
        end     start
Output:
       .Pabcdeefghiiijklmnoooqrstuuvwxyz

[edit]XPL0

include c:\cxpl\codes;          \intrinsic 'code' declarations
string 0;                       \use zero-terminated strings
 
proc    BSort(A, N);            \Bubble sort array in ascending order
char    A;                      \address of array
int     N;                      \number of items in array (size)
int     I, J, T;
[for J:= N-1 downto 0 do
    for I:= 0 to J-1 do
        if A(I) > A(I+1) then
            [T:= A(I);  A(I):= A(I+1);  A(I+1):= T];    \swap items
];      \BSort
 
func    StrLen(Str);            \Return number of characters in an ASCIIZ string
char    Str;
int     I;
for I:= 0 to -1>>1-1 do
        if Str(I) = 0 then return I;
 
char    Str;
[Str:= "Pack my box with five dozen liquor jugs.";
BSort(Str, StrLen(Str));
Text(0, Str);  CrLf(0);
]
Output:
"       .Pabcdeefghiiijklmnoooqrstuuvwxyz"

[edit]Yorick

func bubblesort(&items) {
  itemCount = numberof(items);
  do {
    hasChanged = 0;
    itemCount--;
    for(index = 1; index <= itemCount; index++) {
      if(items(index) > items(index+1)) {
        items([index,index+1]) = items([index+1,index]);
        hasChanged = 1;
      }
    }
  } while(hasChanged);
}

[edit]ZX Spectrum Basic

5000 CLS 
5002 LET a$="": FOR f=1 TO 64: LET a$=a$+CHR$ (32+INT (RND*96)): NEXT f
5004 PRINT a$; AT 10,0;"ZigZag BubbleSORT"
5010 LET la=LEN a$
5011 LET i=1: LET u=0
5020 LET d=0: LET p=(u=0)-(u=1)
5021 LET l=(i AND u=0)+(la-i+u AND u=1)
5030 IF u=0 THEN  IF a$(l+1)>=a$(l) THEN  GO TO 5050
5031 IF u=1 THEN  IF a$(l-1)<=a$(l) THEN  GO TO 5050
5040 LET d=1
5042 LET t$=a$(l+p)
5043 LET a$(l+p)=a$(l)
5044 LET a$(l)=t$
5050 LET l=l+p
5051 PRINT AT 10,21;a$(l);AT 12,0;a$
5055 IF l<=la-i AND l>=i THEN  GO TO 5023
5061 LET i=i+NOT u
5063 LET u=NOT u
5064 IF d AND i<la THEN  GO TO 5020
5072 PRINT AT 12,0;a$
9000 STOP 

Sumber: http://rosettacode.org/wiki/Sorting_algorithms/Bubble_sort

No comments:

Post a Comment