<div dir="ltr">Thank you Xia for your generous help. Enclosed find the file with PriorityQ.hs, and the web page where I found the link.<br><br><a href="https://wiki.haskell.org/Prime_numbers#External_links">https://wiki.haskell.org/Prime_numbers#External_links</a><br><a href="http://www.cs.hmc.edu/~oneill/code/haskell-primes.zip">http://www.cs.hmc.edu/~oneill/code/haskell-primes.zip</a><br></div><div class="gmail_extra"><br><div class="gmail_quote">On Wed, Nov 30, 2016 at 12:54 PM, Li-yao Xia <span dir="ltr"><<a href="mailto:li-yao.xia@ens.fr" target="_blank">li-yao.xia@ens.fr</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Hello Michael,<br>
<br>
Would you have a link to this library? I couldn't find it.<br>
<br>
Alternating the subtree in which we recursively call insert is indeed a good hint. Another detail is that the keys do not affect the shape of the tree (that is, what is left if you ignore the keys and the values, or replace them all with ()).<br>
<br>
- The only difference between the first two branches of insert is that the key-value pairs are swapped. In both cases, the shape of the tree is transformed in the same way.<br>
<br>
- We can also see that "siftdown wk wv t1 t2" has the same shape as "Br wk wv t1 t2", and as the primary component of deleteMinAndInsert, it follows that this function does not change the shape of the tree, it only moves the key-value pairs in it.<br>
<br>
We have insert, deleteMin, and deleteMinAndInsert. It is natural to wonder whether deleteMinAndInsert behaves the same as the composition of insert and deleteMin. While the key-value pairs may be shuffled around differently, the swapping of subtrees that happens in insert appears to be mirrored by leftRem (called by deleteMin).<br>
<br>
In other words, we have that "insert () ()" and deleteMin are inverses of each other. (The units make the key-values undinstiguishable.)<br>
<br>
All this means that the shape of a PriorityQ is entirely determined by the number n of elements in it, and in particular that shape can be obtained by iterating "insert () ()" n times starting from the empty queue Lf.<br>
<br>
shape :: Int -> PriorityQ () ()<br>
shape 0 = Lf<br>
shape n = insert () () (shape (n-1))<br>
<br>
Since "insert () ()" simply calls itself alternatingly on each subtree, which both start off as Lf after the first insertion, the subtrees of a "shape n" are also "shape k" for some value(s) of k:<br>
<br>
shape (2 * n + 1) = Br () () (shape n) (shape n)<br>
shape (2 * n + 2) = Br () () (shape (n + 1)) (shape n)<br>
<br>
That is a good characterization of that shape. We can get their depth:<br>
<br>
depth :: PriorityQ k v -> Int<br>
depth Lf = 0<br>
depth (Br _ _ l r) = 1 + max (depth l) (depth r)<br>
<br>
Let us do some empirical measurements:<br>
<br>
depth (shape n): 0 1 2 2 3 3 3 3 ...<br>
floor (log2 n):  _ 0 1 1 2 2 2 2 ...<br>
<br>
Generalize:<br>
<br>
depth (shape n) = floor (log2 n) + 1<br>
<br>
And since the functions presented all recurse through the tree in depth, their complexities are proportional to it, thus logarithmic.<br>
<br>
Li-yao<div><div class="h5"><br>
<br>
Le 11/30/2016 6:15 PM, Michael Litchard a écrit :<br>
</div></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div><div class="h5">
I'm trying to figure out the complexity of the functions in Melissa<br>
O'Neill's Priority Queue library, Priority.Q.hs<br>
<br>
Below find definitions, and what I think the complexity is. I'd<br>
appreciate feedback, especially on the ones I have marked as guesses.<br>
<br>
data PriorityQ k v = Lf<br>
                    | Br {-# UNPACK #-} !k v !(PriorityQ k v)<br>
!(PriorityQ k v)<br>
                deriving (Eq, Ord, Read, Show)<br>
<br>
O(log n) .<br>
This is a guess but alternating which side of the sub-tree is being<br>
traversed is my hint.<br>
<br>
insert :: Ord k => k -> v -> PriorityQ k v -> PriorityQ k v<br>
insert wk wv (Br vk vv t1 t2)<br>
                | wk <= vk   = Br wk wv (insert vk vv t2) t1<br>
                | otherwise  = Br vk vv (insert wk wv t2) t1<br>
insert wk wv Lf             = Br wk wv Lf Lf<br>
<br>
I have no idea. Reasoning help here please.<br>
siftdown :: Ord k => k -> v -> PriorityQ k v -> PriorityQ k v -><br>
PriorityQ k v<br>
siftdown wk wv Lf _             = Br wk wv Lf Lf<br>
siftdown wk wv (t @ (Br vk vv _ _)) Lf<br>
     | wk <= vk                  = Br wk wv t Lf<br>
     | otherwise                 = Br vk vv (Br wk wv Lf Lf) Lf<br>
siftdown wk wv (t1 @ (Br vk1 vv1 p1 q1)) (t2 @ (Br vk2 vv2 p2 q2))<br>
     | wk <= vk1 && wk <= vk2    = Br wk wv t1 t2<br>
     | vk1 <= vk2                = Br vk1 vv1 (siftdown wk wv p1 q1) t2<br>
     | otherwise                 = Br vk2 vv2 t1 (siftdown wk wv p2 q2)<br>
<br>
Whatever the cost of siftdown is.<br>
deleteMinAndInsert :: Ord k => k -> v -> PriorityQ k v -> PriorityQ k v<br>
deleteMinAndInsert wk wv Lf             = error "Empty PriorityQ"<br>
deleteMinAndInsert wk wv (Br _ _ t1 t2) = siftdown wk wv t1 t2<br>
<br>
This looks like O(log N) to me.<br>
leftrem :: PriorityQ k v -> (k, v, PriorityQ k v)<br>
leftrem (Br vk vv Lf Lf) = (vk, vv, Lf)<br>
leftrem (Br vk vv t1 t2) = (wk, wv, Br vk vv t2 t) where<br>
     (wk, wv, t) = leftrem t1<br>
leftrem _                = error "Empty heap!"<br>
<br>
The cost of siftdown, which is probably more expensive than leftrem.<br>
<br>
deleteMin :: Ord k => PriorityQ k v -> PriorityQ k v<br>
deleteMin (Br vk vv Lf _) = Lf<br>
deleteMin (Br vk vv t1 t2) = siftdown wk wv t2 t where<br>
     (wk,wv,t) = leftrem t1<br>
deleteMin _ = error "Empty heap!"<br>
<br>
Thanks for the feedback. I'm new to computational analysis and this is<br>
the most complicated code I have tried to tackle thus far. I have<br>
Okasaki's book, but am having trouble making best use of it.<br>
<br>
<br>
<br>
<br>
<br></div></div>
______________________________<wbr>_________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bi<wbr>n/mailman/listinfo/haskell-caf<wbr>e</a><br>
Only members subscribed via the mailman list are allowed to post.<br>
<br>
</blockquote>
</blockquote></div><br></div>