Implementing a queue using two stacks

Question 3.5 of Cracking the Coding Interview:

Implement a MyQueue class which implements a queue using two stacks.

First, let’s try this with one stack, which we’ll call queueBack. We’ll treat the top of the stack as the back of the queue: so enqueueing an element is just pushing it on the stack. But when we need to to dequeue an element, we need to access to the bottom of the stack.

One way to access the bottom of a stack is to reverse the stack. And one way to reverse a stack is to repeatedly pop items off of it, pushing them onto a second stack. Notice that the top of this second stack then contains the front of the queue, in the right order to be dequeued. So let’s call this second stack queueFront.

So we have two stacks, queueBack and queueFront, with easy access to the back and the front of the queue! The only issue arises when we need to dequeue but queueFront is empty. In this case, we reverse queueBack onto queueFront before continuing. This means dequeue is a linear-time operation.

There are better algorithms than this. In a language with mutation, you could just keep pointers to the head and tail of a linked list. This will give you a queue with constant-time dequeue and enqueue, which is optimal. In a functional language, you could use a balanced tree, which will give you logarithmic-time dequeue and enqueue.

Regardless, here’s an implementation in Haskell:

module TwoStackQueue where

import Test.QuickCheck

data Queue a = Queue {
  queueBack :: [a],  -- head is back of queue
  queueFront :: [a]  -- head is front of queue
}

emptyQueue :: Queue a
emptyQueue = Queue [] []

enqueue :: a -> Queue a -> Queue a
enqueue x q = q { queueBack = x:(queueBack q) }

dequeue :: Queue a -> Maybe (a, Queue a)
dequeue q = 
  case queueFront q of
    front:rest -> 
      Just (front, q { queueFront = rest })
    [] -> 
      case reverse (queueBack q) of
        front:rest -> 
          Just (front, Queue [] rest)
        [] -> Nothing


-----------------------------------------
----------------- TESTS -----------------

data Op = Enqueue Int | Dequeue deriving (Show)

instance Arbitrary Op where
  arbitrary = oneof [Enqueue <$> arbitrary, return Dequeue]

-- returns all elems dequeued when running all ops
runOps :: [Op] -> [Int]
runOps ops = snd $ foldl runOp (emptyQueue, []) ops where
  runOp :: (Queue Int, [Int]) -> Op -> (Queue Int, [Int])
  runOp (q,out) (Enqueue x) = (enqueue x q, out)
  runOp (q,out) Dequeue     = case dequeue q of
                                Just (x, q2) -> (q2, out++[x])
                                Nothing -> (q, out)

-- model is a plain list
runOpsModel :: [Op] -> [Int]
runOpsModel ops = snd $ foldl runOp ([],[]) ops where
  runOp :: ([Int], [Int]) -> Op -> ([Int], [Int])
  runOp (q,  out) (Enqueue x) = (x:q, out)
  runOp (q, out) Dequeue = case reverse q of
                            [] -> ([], out)
                            front:rest -> (reverse rest, out ++ [front])

prop_modelcheck :: [Op] -> Bool
prop_modelcheck ops = runOps ops == runOpsModel ops

main = quickCheck prop_modelcheck
Tagged #stack, #queue, #ctci, #haskell, #c, #data-structures, #algorithms, #programming.

Similar posts

More by Jim

👋 I'm Jim, a full-stack product engineer. Want to build an amazing product and a profitable business? Read more about me or Get in touch!

This page copyright James Fisher 2020. Content is not associated with my employer. Found an error? Edit this page.