--------------167E2781446B
Content-Type: text/plain; charset="us-ascii"

Ralf Hinze wrote:
> Practitioners are probably surprised to learn that `pairingSort' is the
> algorithm of choice for sorting. Any objections to this recommendation?
> I was surprised to see that it performs so well: sorting 50.000 Int's
> in roughly three seconds and 100.000 Int's in roughly nine seconds is
> quite acceptable.

I ran some similar experiments in Standard ML a few years ago.  In those
experiments pairingSort also performed extremely well.  The only 
algorithm that performed better, and even then only by a small amount,
was splaySort, based on splay trees[1].  However, my experiment
only considered algorithms that were good choices as heaps -- I
did not consider any of the mergesort variations.  Ralf, could I
ask you to run my code below through your experiments (I don't have
easy access to anything but hugs at the moment)?

According to Ralf's criteria, splaySort is
  A. asymptotically optimal
  B. stable
  C. smooth  (In fact, it has been conjectured that splaySort is
              optimal with respect to any reasonable notion of
              "presortedness".[2])
However, I believe--although I'm positive--that splaySort is
  D. not lazy
Ralf considered the situation where the creation phase takes O(n) time
and the selection phase takes O(n log n) time, but for splaySort these
are reversed.

Chris

--------------

[1] Sleator and Tarjan
    "Self-adjusting binary search trees"
    Journal of the ACM 32(3):652-686 (July '85)

[2] Moffat, Eddy, and Petersson
    "Splaysort: Fast, Versatile, Practical"
    Software P&E 26(7):781-797 (July '96)

-------------

--------------167E2781446B
Content-Disposition: inline; filename="Splay.lhs"
Content-Type: text/plain; charset="us-ascii"; name="Splay.lhs"

> data Splay a = SEmpty | SNode (Splay a) a (Splay a)
>
> instance PriorityQueue Splay where
>  empty = SEmpty
>  single x = SNode SEmpty x SEmpty
>
>  fromList xs = foldr insert empty xs
>  
>  toOrderedList t = tol t []
>    where tol SEmpty rest = rest
>          tol (SNode a x b) rest = tol a (x : tol b rest)
>
>  insert k t = SNode a k b
>    where 
>      (a, b) = partition t  -- elements of a <= k, elements of b > k
>
>      partition SEmpty = (SEmpty,SEmpty)
>      partition t@(SNode tl x tr)
>        | x < k =
>            case tr of
>              SEmpty -> (t,SEmpty)
>              SNode trl y trr
>                | y < k ->
>                    let tl' = SNode tl x trl
>                        (lt,ge) = partition trr
>                    in (SNode tl' y lt,ge)
>                | otherwise ->
>                    let (lt,ge) = partition trl
>                    in (SNode tl x lt,SNode ge y trr)
>        | otherwise =
>            case tl of
>              SEmpty -> (SEmpty,t)
>              SNode tll y tlr
>                | y < k ->
>                    let (lt,ge) = partition tlr
>                    in (SNode tll y lt,SNode ge x tr)
>                | otherwise ->
>                    let tr' = SNode tlr x tr
>                        (lt,ge) = partition tll
>                    in (lt,SNode ge y tr')
>
> splaySort                     :: (Ord a) => [a] -> [a]
> splaySort                     =  toOrderedList
>                               .  (fromList :: (Ord a) => [a] -> Splay a)

--------------167E2781446B--


Reply via email to