[Haskell-cafe] complexity of functions in PriorityQ.hs
Michael Litchard
michael at schmong.org
Wed Nov 30 18:15:09 UTC 2016
I'm trying to figure out the complexity of the functions in Melissa
O'Neill's Priority Queue library, Priority.Q.hs
Below find definitions, and what I think the complexity is. I'd appreciate
feedback, especially on the ones I have marked as guesses.
data PriorityQ k v = Lf
| Br {-# UNPACK #-} !k v !(PriorityQ k v) !(PriorityQ k
v)
deriving (Eq, Ord, Read, Show)
O(log n) .
This is a guess but alternating which side of the sub-tree is being
traversed is my hint.
insert :: Ord k => k -> v -> PriorityQ k v -> PriorityQ k v
insert wk wv (Br vk vv t1 t2)
| wk <= vk = Br wk wv (insert vk vv t2) t1
| otherwise = Br vk vv (insert wk wv t2) t1
insert wk wv Lf = Br wk wv Lf Lf
I have no idea. Reasoning help here please.
siftdown :: Ord k => k -> v -> PriorityQ k v -> PriorityQ k v -> PriorityQ
k v
siftdown wk wv Lf _ = Br wk wv Lf Lf
siftdown wk wv (t @ (Br vk vv _ _)) Lf
| wk <= vk = Br wk wv t Lf
| otherwise = Br vk vv (Br wk wv Lf Lf) Lf
siftdown wk wv (t1 @ (Br vk1 vv1 p1 q1)) (t2 @ (Br vk2 vv2 p2 q2))
| wk <= vk1 && wk <= vk2 = Br wk wv t1 t2
| vk1 <= vk2 = Br vk1 vv1 (siftdown wk wv p1 q1) t2
| otherwise = Br vk2 vv2 t1 (siftdown wk wv p2 q2)
Whatever the cost of siftdown is.
deleteMinAndInsert :: Ord k => k -> v -> PriorityQ k v -> PriorityQ k v
deleteMinAndInsert wk wv Lf = error "Empty PriorityQ"
deleteMinAndInsert wk wv (Br _ _ t1 t2) = siftdown wk wv t1 t2
This looks like O(log N) to me.
leftrem :: PriorityQ k v -> (k, v, PriorityQ k v)
leftrem (Br vk vv Lf Lf) = (vk, vv, Lf)
leftrem (Br vk vv t1 t2) = (wk, wv, Br vk vv t2 t) where
(wk, wv, t) = leftrem t1
leftrem _ = error "Empty heap!"
The cost of siftdown, which is probably more expensive than leftrem.
deleteMin :: Ord k => PriorityQ k v -> PriorityQ k v
deleteMin (Br vk vv Lf _) = Lf
deleteMin (Br vk vv t1 t2) = siftdown wk wv t2 t where
(wk,wv,t) = leftrem t1
deleteMin _ = error "Empty heap!"
Thanks for the feedback. I'm new to computational analysis and this is the
most complicated code I have tried to tackle thus far. I have Okasaki's
book, but am having trouble making best use of it.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20161130/276c4e47/attachment.html>
More information about the Haskell-Cafe
mailing list