Eugene Kirpichov wrote:
> 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)

For the record, we can exploit the invariant that the sizes of the left
and right subtrees have difference 0 or 1 to implement 'size' in better
than O(n) time, where n is the size of the heap:

-- Return number of elements in the priority queue.
-- /O(log(n)^2)/
size :: PriorityQ k v -> Int
size Lf = 0
size (Br _ _ t1 t2) = 2*n + rest n t1 t2 where
    n = size t2
    -- rest n p q, where n = size q, and size p - size q = 0 or 1
    -- returns 1 + size p - size q.
    rest :: Int -> PriorityQ k v -> PriorityQ k v -> Int
    rest 0 Lf _ = 1
    rest 0 _  _ = 2
    rest n (Br _ _ p1 p2) (Br _ _ q1 q2) = case r of
        0 -> rest d p1 q1 -- subtree sizes: (d or d+1), d; d, d
        1 -> rest d p2 q2 -- subtree sizes: d+1, (d or d+1); d+1, d
      where (d, r) = (n-1) `quotRem` 2

Of course we can reduce the cost to O(1) by annotating the heap with its
size, but that is less interesting, and incurs a little overhead in the
other heap operations.

Bertram
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to