
Greetings. I have just implemented a heap. But... um... I can't acutally figure out *which kind* of heap it is! LOL. Any ideas? (Seems to work really well, whatever it is. Oh, and I discovered that you can sort data just by shoving it all into a heap, and then taking it all out again. Apparently this is a standard algorithm, and it's known as a "heap sort", unsurprisingly. You learn something every day...) module Heap where import Data.List (intersperse, unfoldr) data Heap t = Node !t !(Heap t) !(Heap t) | Null instance (Show t) => Show (Heap t) where show = work "" where work p (Null) = p ++ "-" work p (Node v t0 t1) = concat $ intersperse "\n" $ [work (' ':p) t0, p ++ show v, work (' ':p) t1] empty = Null is_empty Null = True is_empty _ = False insert v (Null) = Node v Null Null insert v (Node v0 t0 t1) = let lo = min v v0 hi = max v v0 in Node hi (insert lo t1) t0 get_max (Null) = error "heap is empty" get_max (Node v _ _) = v delete_max (Null) = error "heap is empty" delete_max (Node _ Null Null) = Null delete_max (Node _ Null t1) = t1 delete_max (Node _ t0 Null) = t0 delete_max (Node _ t0 t1) | get_max t0 > get_max t1 = Node (get_max t0) (delete_max t0) t1 | otherwise = Node (get_max t1) t0 (delete_max t1) size (Null) = 0 size (Node _ t0 t1) = 1 + (size t0) + (size t1) from_list :: (Ord t) => [t] -> Heap t from_list = foldr insert empty to_list :: (Ord t) => Heap t -> [t] to_list = unfoldr (\h -> if is_empty h then Nothing else Just (get_max h, delete_max h)) heap_sort :: (Ord t) => [t] -> [t] heap_sort = to_list . from_list