{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UnicodeSyntax #-}
module System.Logger.Internal.Queue
( BoundedCloseableQueue(..)
, FairTBMQueue
, TBMQueue
, TBMChan
) where
import Control.Concurrent
import Control.Concurrent.STM
import Control.Concurrent.STM.TBMChan
import Control.Concurrent.STM.TBMQueue
import Control.Monad.Unicode
import Numeric.Natural
import Prelude.Unicode
class BoundedCloseableQueue q a | q → a where
newQueue ∷ Natural → IO q
closeQueue ∷ q → IO ()
writeQueue ∷ q → a → IO Bool
tryWriteQueue ∷ q → a → IO (Maybe Bool)
readQueue ∷ q → IO (Maybe a)
instance BoundedCloseableQueue (TBMQueue a) a where
newQueue = newTBMQueueIO ∘ fromIntegral
closeQueue = atomically ∘ closeTBMQueue
writeQueue q a = atomically $ isClosedTBMQueue q ≫= \case
True → return False
False → do
writeTBMQueue q a
return True
tryWriteQueue q a = atomically $ tryWriteTBMQueue q a ≫= \case
Nothing → return $ Just False
Just False → return Nothing
Just True → return $ Just True
readQueue q = atomically $ readTBMQueue q
instance BoundedCloseableQueue (TBMChan a) a where
newQueue = newTBMChanIO ∘ fromIntegral
closeQueue = atomically ∘ closeTBMChan
writeQueue q a = atomically $ isClosedTBMChan q ≫= \case
True → return False
False → do
writeTBMChan q a
return True
tryWriteQueue q a = atomically $ tryWriteTBMChan q a ≫= \case
Nothing → return $ Just False
Just False → return Nothing
Just True → return $ Just True
readQueue q = atomically $ readTBMChan q
data FairTBMQueue α = FairTBMQueue
{ fairTBMQueueQueue ∷ !(TBMQueue α)
, fairTBMQueueLock ∷ !(MVar ())
}
instance BoundedCloseableQueue (FairTBMQueue a) a where
newQueue i = FairTBMQueue <$> newTBMQueueIO (fromIntegral i) <*> newMVar ()
closeQueue = closeQueue ∘ fairTBMQueueQueue
readQueue = readQueue ∘ fairTBMQueueQueue
writeQueue FairTBMQueue{..} a = do
withMVar fairTBMQueueLock $ \_ → do
writeQueue fairTBMQueueQueue a
tryWriteQueue FairTBMQueue{..} a = do
withMVar fairTBMQueueLock $ \_ → do
tryWriteQueue fairTBMQueueQueue a