{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE BangPatterns #-}
module Data.Queue
( Queue
, newQueue
, peek
, tryPeek
, enqueue
, dequeue
, tryDequeue
, flush
) where
import Control.Concurrent
import Control.Concurrent.STM
data Queue a = Queue
{-# UNPACK #-} !(TVar ([a], [a]))
{-# UNPACK #-} !(TVar ([a], [a]))
newQueue :: STM (Queue a)
newQueue = Queue
<$> newTVar ([], [])
<*> newTVar ([], [])
rotate :: [a] -> [a] -> [a]
rotate xs ys = go xs ys []
where
go [] bottom acc = bottom ++ acc
go (t:ts) (b:bs) acc = t : go ts bs (b:acc)
go ts [] acc = ts ++ acc
enqueue :: Queue a -> a -> STM ()
enqueue q@(Queue top bottom) a = do
(bs, sbs) <- readTVar bottom
let bs' = a : bs
case sbs of
_:_:sbs' -> do
writeTVar bottom (bs', sbs')
_ -> do
(ts, _sts) <- readTVar top
let ts' = rotate ts bs'
writeTVar bottom ([], ts')
writeTVar top (ts', ts')
dequeue :: Queue a -> STM a
dequeue q@(Queue top bottom) = do
(ts, sts) <- readTVar top
case ts of
[] -> retry
t:ts' ->
case sts of
_:_:sts' -> do
writeTVar top (ts', sts')
pure t
_ -> do
(bs, _) <- readTVar bottom
let !ts'' = rotate ts' bs
writeTVar bottom ([], ts'')
writeTVar top (ts'', ts'')
pure t
tryDequeue :: Queue a -> STM (Maybe a)
tryDequeue q@(Queue top bottom) = do
(ts, sts) <- readTVar top
case ts of
[] -> pure Nothing
t:ts' ->
case sts of
_:_:sts' -> do
writeTVar top (ts', sts')
pure (Just t)
_ -> do
(bs, _) <- readTVar bottom
let !ts'' = rotate ts' bs
writeTVar bottom ([], ts'')
writeTVar top (ts'', ts'')
pure (Just t)
peek :: Queue a -> STM a
peek (Queue top _bottom) =
readTVar top >>= \case
(x : xs, _) -> pure x
([], _) -> retry
tryPeek :: Queue a -> STM (Maybe a)
tryPeek (Queue top _bottom) =
readTVar top >>= \case
(x : xs, _) -> pure (Just x)
([], _) -> pure Nothing
flush :: Queue a -> STM [a]
flush (Queue top bottom) = do
(xs, _) <- swapTVar top ([], [])
(ys, _) <- swapTVar bottom ([], [])
pure (rotate xs ys)