-- | Abstract Stack data type
--
-- <https://en.wikipedia.org/wiki/Stack_(abstract_data_type)>
module Data.Stack (
    Stack,
    stackNew,
    stackPush,
    stackPeek,
    stackPop,
    stackIsEmpty,
    stackSize,
  )
  where

-- | Abstract Stack data type
data Stack a = Stack [a] deriving (Read,Show)

-- | Create new Stack
stackNew :: Stack a
stackNew = Stack []

-- | Push item onto Stack
--
-- > (∀x)(∀s)(stackPop (stackPush s x) == Just (s,x))
stackPush :: Stack a -> a -> Stack a
stackPush (Stack items) item = Stack (item : items)

-- | Pop most recently added item without removing from the Stack
--
-- > stackPeek stackNew == Nothing
-- > (∀x)(∀s)(stackPeek (stackPush s x) == Just x)
-- > (∀s)(stackPeek s == fmap snd (stackPop s))
stackPeek :: Stack a -> Maybe a
stackPeek (Stack []) = Nothing
stackPeek (Stack items) = Just (head items)

-- | Pop most recently added item from Stack
--
-- > stackPop stackNew == Nothing
-- > (∀x)(∀s)(stackPop (stackPush s x) == Just (s,x))
stackPop :: Stack a -> Maybe (Stack a, a)
stackPop (Stack []) = Nothing
stackPop (Stack items) = Just (Stack (tail items), head items)

-- | Test if stack is empty
--
-- > stackIsEmpty stackNew == True
-- > (∀x)(∀s)(stackIsEmpty (stackPush s x) == True)
-- > (∀s)((stackSize s == 0) ⇔ (stackIsEmpty s == True))
stackIsEmpty :: Stack a -> Bool
stackIsEmpty (Stack []) = True
stackIsEmpty (Stack _)  = False

-- | Compute number of elements contained in the Stack
--
-- > stackSize stackNew == 0
-- > (∀x)(∀s)((stackSize s == n) ⇒ (stackSize (stackPush s x) == n+1))
stackSize :: Stack a -> Int
stackSize (Stack items) = length items