module Control.Distributed.Process.Extras.Internal.Queue.SeqQ
( SeqQ
, empty
, isEmpty
, singleton
, enqueue
, dequeue
, peek
)
where
import Data.Sequence
( Seq
, ViewR(..)
, (<|)
, viewr
)
import qualified Data.Sequence as Seq (empty, singleton, null)
newtype SeqQ a = SeqQ { q :: Seq a }
deriving (Show)
instance Eq a => Eq (SeqQ a) where
a == b = (q a) == (q b)
empty :: SeqQ a
empty = SeqQ Seq.empty
isEmpty :: SeqQ a -> Bool
isEmpty = Seq.null . q
singleton :: a -> SeqQ a
singleton = SeqQ . Seq.singleton
enqueue :: SeqQ a -> a -> SeqQ a
enqueue s a = SeqQ $ a <| q s
dequeue :: SeqQ a -> Maybe (a, SeqQ a)
dequeue s = maybe Nothing (\(s' :> a) -> Just (a, SeqQ s')) $ getR s
peek :: SeqQ a -> Maybe a
peek s = maybe Nothing (\(_ :> a) -> Just a) $ getR s
getR :: SeqQ a -> Maybe (ViewR a)
getR s =
case (viewr (q s)) of
EmptyR -> Nothing
a -> Just a