[Haskell-cafe] Re: Splay tree in a pattern matching way

larry.liuxinyu liuxinyu95 at gmail.com
Sun Oct 24 04:17:48 EDT 2010


Hi,

I just tried a smoke test case, seems the tree is balanced enough:

import System.Random

lookup :: (Ord a) => STree a -> a -> STree a
lookup E _ = E
lookup t@(Node l x r) y
    | x == y    = t
    | x > y     = splay (Node (lookup l y) x r) y
    | otherwise = splay (Node l x (lookup r y)) y

testSplay = do
  xs <- sequence (replicate 100 (randomRIO(1, 10)))
  putStrLn $ show (foldl lookup t xs)
      where
        t = foldl insert (E::STree Int) [1..10]

Where STree a and insert are defined as in my previous email, except I
changed `x<y' to `x>y' (sorry for the mistake).
By running the testSplay I got a BST like this:

*SplayHeap> testSplay
Node (Node E 1 (Node (Node E 2 E) 3 (Node (Node E 4 (Node E 5 E)) 6
(Node E 7 E)))) 8 (Node (Node E 9 E) 10 E)

So I got a bit more confident about the correctness of my code.

Best regards
--
Larry, LIU Xinyu
http://sites.google.com/site/algoxy

On Oct 24, 11:06 am, Xinyu LIU <liuxiny... at gmail.com> wrote:
> Hi,
>
> I checked the Hackage Splay Tree implementation from.http://hackage.haskell.org/packages/archive/TreeStructures/0.0.1/doc/...
>
> Basically it's based on the strategy mentioned in Okasaki's ``Purely
> Functional Programming'', Chapter 5.4.
> That in case we traverse twice in left (or right), we rotate the tree, so in
> long term of view, the tree turns more and more balanced.
>
> There are 3 cases for splay: zig-zig case, zig-zag case and zig case
> according tohttp://en.wikipedia.org/wiki/Splay_tree
>
> So I wonder if Splay tree can also be implemented by using pattern matching
> in a similar way as red black tree.
>
> Here is a draft source code:
>
>
>
> data STree a = E -- Empty
>              | Node (STree a) a (STree a) -- left, element, right
>                deriving (Eq, Show)
>
> -- splay by pattern matching
> splay :: (Eq a) => STree a -> a ->STree a
> -- zig-zig
> splay t@(Node (Node (Node a x b) p c) g d) y =
>    if x == y then Node a x (Node b p (Node c g d)) else t
> splay t@(Node a g (Node b p (Node c x d))) y =
>    if x == y then Node (Node (Node a g b) p c) x d else t
> -- zig-zag
> splay t@(Node (Node a p (Node b x c)) g d) y =
>    if x == y then Node (Node a p b) x (Node c g d) else t
> splay t@(Node a g (Node (Node b x c) p d)) y =
>    if x == y then Node (Node a g b) x (Node c p d) else t
> -- zig
> splay t@(Node (Node a x b) p c) y = if x == y then Node a x (Node b p
> c) else t
> splay t@(Node a p (Node b x c)) y = if x == y then Node (Node a p b) x
> c else t
> -- otherwise
> splay t _ = t
>
> -- insert by using pattern matching
> insert :: (Ord a) => STree a -> a -> STree a
> insert E y = Node E y E
> insert (Node l x r) y
>    | x < y     = splay (Node (insert l y) x r) y
>    | otherwise = splay (Node l x (insert r y)) y
> <<<
>
> I am not quite sure if the solution is correct and what about the
> efficiency of this code.
>
> Regards.
>
> --
> Larry. LIU Xinyuhttp://sites.google.com/site/algoxy<http://sites.google.com/site/algoxy/home>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list