module Log.Logger (
Logger
, mkLogger
, mkBulkLogger
, execLogger
, waitForLogger
, shutdownLogger
) where
import Control.Applicative
import Control.Concurrent
import Control.Concurrent.STM
import Control.Exception
import Control.Monad
import Data.Semigroup
import Prelude
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Log.Data
import Log.Internal.Logger
mkLogger :: T.Text -> (LogMessage -> IO ()) -> IO Logger
mkLogger name exec = mkLoggerImpl
newTQueueIO isEmptyTQueue readTQueue writeTQueue (return ())
name exec (return ())
mkBulkLogger :: T.Text -> ([LogMessage] -> IO ()) -> IO () -> IO Logger
mkBulkLogger = mkLoggerImpl
newSQueueIO isEmptySQueue readSQueue writeSQueue (threadDelay 1000000)
newtype SQueue a = SQueue (TVar [a])
newSQueueIO :: IO (SQueue a)
newSQueueIO = SQueue <$> newTVarIO []
isEmptySQueue :: SQueue a -> STM Bool
isEmptySQueue (SQueue queue) = null <$> readTVar queue
readSQueue :: SQueue a -> STM [a]
readSQueue (SQueue queue) = do
elems <- readTVar queue
when (null elems) retry
writeTVar queue []
return $ reverse elems
writeSQueue :: SQueue a -> a -> STM ()
writeSQueue (SQueue queue) a = modifyTVar queue (a :)
mkLoggerImpl :: IO queue
-> (queue -> STM Bool)
-> (queue -> STM msgs)
-> (queue -> LogMessage -> STM ())
-> IO ()
-> T.Text
-> (msgs -> IO ())
-> IO ()
-> IO Logger
mkLoggerImpl newQueue isQueueEmpty readQueue writeQueue afterExecDo
name exec sync = do
queue <- newQueue
inProgress <- newTVarIO False
isRunning <- newTVarIO True
tid <- forkFinally (forever $ loop queue inProgress)
(\_ -> cleanup queue inProgress)
return Logger {
loggerWriteMessage = \msg -> atomically $ do
checkIsRunning isRunning
writeQueue queue msg,
loggerWaitForWrite = do
atomically $ waitForWrite queue inProgress
sync,
loggerShutdown = do
killThread tid
atomically $ writeTVar isRunning False
}
where
checkIsRunning isRunning' = do
isRunning <- readTVar isRunning'
when (not isRunning) $
throwSTM (AssertionFailed $ "Log.Logger.mkLoggerImpl: "
++ "attempt to write to a shut down logger")
loop queue inProgress = do
step queue inProgress
afterExecDo
step queue inProgress = do
msgs <- atomically $ do
writeTVar inProgress True
readQueue queue
exec msgs
atomically $ writeTVar inProgress False
cleanup queue inProgress = do
step queue inProgress
sync
printLoggerTerminated
waitForWrite queue inProgress = do
isEmpty <- isQueueEmpty queue
isInProgress <- readTVar inProgress
when (not isEmpty || isInProgress) retry
printLoggerTerminated = T.putStrLn $ name <> ": logger thread terminated"