module Control.Concurrent.STM.Stack (
Stack,
stackNew,
stackPush,
stackPeek,
stackTryPeek,
stackPop,
stackTryPop,
stackIsEmpty,
stackSize,
)
where
import Control.Concurrent.STM.TVar
import Control.Monad.STM
import qualified Data.Stack as Pure
import Numeric.Natural
newtype Stack a = Stack (TVar (Pure.Stack a))
stackNew :: STM (Stack a)
stackNew = do
stackRef <- newTVar Pure.stackNew
return (Stack stackRef)
stackPush :: Stack a -> a -> STM ()
stackPush (Stack stackRef) item = modifyTVar' stackRef (\stack -> Pure.stackPush stack item)
stackTryPeek :: Stack a -> STM (Maybe a)
stackTryPeek (Stack stackRef) = do
stack <- readTVar stackRef
return (Pure.stackPeek stack)
stackPeek :: Stack a -> STM a
stackPeek (Stack stackRef) = do
stack <- readTVar stackRef
case Pure.stackPeek stack of
Just item -> return item
Nothing -> retry
stackTryPop :: Stack a -> STM (Maybe a)
stackTryPop (Stack stackRef) = do
stack <- readTVar stackRef
case Pure.stackPop stack of
Just (stack1,item) -> do writeTVar stackRef stack1
return (Just item)
Nothing -> return Nothing
stackPop :: Stack a -> STM a
stackPop (Stack stackRef) = do
stack <- readTVar stackRef
case Pure.stackPop stack of
Just (stack1,item) -> do writeTVar stackRef stack1
return item
Nothing -> retry
stackIsEmpty :: Stack a -> STM Bool
stackIsEmpty (Stack stackRef) = do
stack <- readTVar stackRef
return (Pure.stackIsEmpty stack)
stackSize :: Stack a -> STM Natural
stackSize (Stack stackRef) = do
stack <- readTVar stackRef
return (Pure.stackSize stack)