
Eugene Kirpichov wrote:
Hi, I've recently tried to use the priority queue from the ONeillPrimes.hs, which is famous for being a very fast prime generator: actually, I translated the code to Scheme and dropped the values, to end up with a key-only heap implementation. However, the code didn't work quite well, and I decided to check the haskell code itself.
Turns out that it is broken.
module PQ where
import Test.QuickCheck
data PriorityQ k v = Lf | Br {-# UNPACK #-} !k v !(PriorityQ k v) !(PriorityQ k v) deriving (Eq, Ord, Read, Show)
Let size Lf = 0 size (Br _ _ l r) = 1 + sizePQ l + sizePQ r be the size of the priority queue. To work, the code maintains heap order and the invariant that the left subtree is at least as large as the right one, and at most one element larger. validSize Lf = True validSize (Br _ _ l r) = validSize l && validSize r && 0 <= d && d <= 1 where d = size l - size r This invariant justifies the assumption that Daniel Fischer pointed out. The code is careful to maintain this invariant, but it is broken in one place:
leftrem :: PriorityQ k v -> (k, v, PriorityQ k v) leftrem (Br vk vv Lf Lf) = (vk, vv, Lf)
(Why not this?) leftrem (Br vk vv Lf _) = (vk, vv, Lf)
leftrem (Br vk vv t1 t2) = (wk, wv, Br vk vv t t2) where (wk, wv, t) = leftrem t1
Here, the left subtree is replaced by one that is one element smaller. This breaks the invariant if the two original subtrees had equal size. The bug is easy to fix; just swap the two subtrees on the right side: leftrem (Br vk vv t1 t2) = (wk, wv, Br vk vv t2 t) where (wk, wv, t) = leftrem t1
leftrem _ = error "Empty heap!" *PQ> s [3,1,4,1,5,9,2,6,5,3,5,8] [1,1,2*** Exception: Empty heap!
*PQ> s [3,1,4,1,5,9,2,6,5,3,5,8] [1,1,2,3,3,4,5,5,5,6,8,9] HTH, Bertram