Merge Sort vs. Heap Sort (ala Jon)

As far as I can see the difference between merge sort and heap sort as
described by Jon is almost non existing.

Merge sort as I wrote it in 92 (it might have been 93 :-).
Using Jon's naming:

runify x = [x]

merge [] ys = ys
merge xs [] = xs
merge xrun@(x:xs) yrun@(y:ys)
  | x <= y = x:merge xs yrun               -- <= to make it stable
  | otherwise = y : merge xrun ys

mergesort = treefold merge . map runify

to make it into a natural mergesort use 
( group (<=) ) instead of (map runify)
(group R) splits a list in sublists where the relation R holds between
two consecutive elements and is due to John Hughes. 

The main difference is that we call merge recursively instead of
building a heap node which is later taken apart in flatten_heap. I fail
to se how Jon's version can be superior and I cannot see that points a,
b, and c (below) holds (of course (a) can be argued)

Carsten Kehler Holst

>-----Original Message-----
>From:  [EMAIL PROTECTED] [SMTP:[EMAIL PROTECTED]]
>Sent:  1. oktober 1997 21:01
>To:    [EMAIL PROTECTED]
>Cc:    [EMAIL PROTECTED]; [EMAIL PROTECTED]
>Subject:       Re: Heap Sort
>
>Here is my version:
>
>First we need treefold:
>
>---
>module Treefold where
>
>-- I'm surprised treefold isn't in the standard prelude since it's so useful
>-- treefold (*) z [a,b,c,d,e,f] = (((a*b)*(c*d))*(e*f))
>
>-- translated from the version I wrote in Ponder in October 1992
>-- Jon Fairbairn
>
>treefold f zero [] = zero
>treefold f zero [x] = x
>treefold f zero (a:b:l) = treefold f zero (f a b: pairfold l)
>                     where pairfold (x:y:rest) = f x y: pairfold rest
>                           pairfold l = l -- here l will have fewer than two
>elements
>
>--
>
>module Heapsort where
>import Treefold
>
>-- translated from the version I wrote in Ponder in October 1992
>-- Jon Fairbairn
>
>data Heap a = Nil | Node a [Heap a]
>heapify x = Node x []
>
>heapsort :: Ord a => [a] -> [a]
>
>heapsort = flatten_heap . merge_heaps . map heapify
>
>    where merge_heaps :: Ord a => [Heap a] -> Heap a
>          merge_heaps = treefold merge_heap Nil
>
>          flatten_heap Nil = []
>          flatten_heap (Node x heaps) = x:flatten_heap (merge_heaps heaps)
>
>          merge_heap Nil                     Nil = Nil
>          merge_heap heap@(Node _ _)         Nil = heap
>          merge_heap node_a@(Node a heaps_a) node_b@(Node b heaps_b)
>                     | a < b = Node a (node_b: heaps_a)
>                     | otherwise = Node b (node_a: heaps_b)
>
>-- end
>
>
>On 21 Sep , Chris Dornan wrote:
>> When would a heap sort be preferable to a merge sort?
>
>a) When you want to explain the imperative heapsort
>b) When you know that the data are going to be in an order that is bad for
>   mergesort (take n . concat . repeat) [0,1] for example
>c) when you are worried about the worst-case behaviour more than the average
>   case
>
>Most of the time, mergesort with a phase that breaks the input into
>runs will be faster.  However, it's possible to write a heapsort that
>starts with a run phase; this is slightly slower than mergesort for
>the average case, but the worst case is better.
>
>  Jon
>
>-- 
>Jon Fairbairn                                 [EMAIL PROTECTED]
>18 Kimberley Road                                        [EMAIL PROTECTED]
>Cambridge CB4 1HH                      +44 1223 570179 (pm only, please)
>
>
>
>


Reply via email to