[Haskell-cafe] Re: Red-Blue Stack

apfelmus apfelmus at quantentunnel.de
Thu Sep 25 15:07:22 EDT 2008


Jamie Brandon wrote:
> Try writing
> 
> data RBStack = RBS [RBSItem] [RBSItem]
> 
> where the first list are all the same colour and the start of the second list
> is a different colour. The rest should follow naturally and you will get
> amortised O(1) push and pop (you occasionally have to juggle the lists).

I am afraid, but this does not give constant amortized time. Let me reformulate
the data type you have in mind as follows:

    data Stack2 r b = Empty | S [r] (Stack2 b r) deriving (Eq, Show)

We're using the type system to distinguish between red (r) and blue (b)
elements. The list [r] corresponds to your first list and means that the stack
has red elements on top. The rest is a stack with blue elements on top.

Using different types for red and blue is extremely cool :) because the compiler
will complain about buggy code that deletes red elements instead of blue ones
and the like. It already helped me to find a bug in my implementation below.


All stack operations like  push  and  pop  will be performed on the red
elements. We can switch between red and blue by making the list empty

    recolor :: Stack2 r b -> Stack2 b r
    recolor (S [] t) = t
    recolor t        = S [] t

In other words, a stack with blue elements on top is a red stack with an empty
list of red elements on top :). We impose the /invariant/ that only the topmost
list may be empty.

Pushing a red element onto the stack is straightforward.

    push :: r -> Stack2 r b -> Stack2 r b
    push r Empty    = S [r] Empty
    push r (S rs t) = S (r:rs) t

and so is pushing blue elements thanks to recoloring

    pushB :: b -> Stack2 r b -> Stack2 r b
    pushB b = recolor . push b . recolor

The topmost element may be either blue or red

    top :: Stack2 r b -> Maybe (Either r b)
    top Empty       = Nothing
    top (S []    t) = fmap (\(Left b) -> Right b) (top t)
    top (S (r:_) t) = Just (Left r)

Most importantly, we want to remove elements. Removing a red element is easy if
there are red elements on the top

    pop :: Stack2 r b -> Stack2 r b
    pop (S (_:rs) t       ) = S rs t

otherwise we will have to remove them from behind the blue elements while taking
care that our /invariant/ still holds.

    pop (S []     (S bs t)) = S [] . s bs . pop $ t
        where
        -- s is like S but takes care of the invariant
        s bs (S [] Empty     ) = S bs Empty
        s bs (S [] (S bs' t')) = S (bs ++ bs') t'
        s bs t                 = t
    pop _                   = Empty

Exercise: Find and correct the bug in this implementation of  pop ! Hint: let
the type checker tell you where it is.
Quiz question: How to remove blue elements?


Unfortunately, this whole implementation is not O(1) time. The problem is our
use of ++. Consider the stack

  S [R] $ S [B] $ S [R] $ S [B] $ S [R] $ S [B] $ S [R] $ S [B] $ Empty

Removing all the blue elements from this stack will give

  S ((([R] ++ [R]) ++ [R]) ++ [R]) Empty

and we see the feared left-parenthesized application of list concatenation.
Removing all red elements but one and asking for top will take quadratic time
which doesn't amortize to O(1).


In other words, while cool, the above implementation is not really what you
want, Matthew. Quite a disappointing result for such a long e-mail ;). But don't
worry, in a subsequent post, I'll turn the above ideas into a better solution
and I'll also explain why implementing this data structure seems more difficult
in Haskell than in Java.


Regards,
apfelmus



More information about the Haskell-Cafe mailing list