module Network.MoHWS.Logger (
Handle,
start,
stop,
log,
) where
import Network.MoHWS.Utility (dirname, )
import qualified Control.Exception as Exception
import Control.Exception (SomeException(SomeException), )
import Control.Concurrent (Chan, ThreadId, newChan, forkIO, writeChan, readChan, )
import System.Directory (createDirectoryIfMissing, )
import System.IO (IOMode(AppendMode), hPutStrLn, stderr, hClose, hFlush, )
import qualified System.IO as IO
import Prelude hiding (log, )
data Handle a = Handle
{
handleChan :: Chan (Command a),
handleThreadId :: ThreadId
}
data T a = Cons
{
chan :: Chan (Command a),
format :: (a -> IO String),
file :: FilePath
}
data Command a = Stop | Log a
start ::
(a -> IO String)
-> FilePath
-> IO (Handle a)
start format0 file0 =
do chan0 <- newChan
createDirectoryIfMissing True (dirname file0)
let l = Cons {
chan = chan0,
format = format0,
file = file0
}
t <- forkIO $
run l
`Exception.catch`
\(SomeException e) ->
hPutStrLn stderr
("Error starting logger: " ++ show e)
return $
Handle {
handleChan = chan0,
handleThreadId = t
}
stop :: Handle a -> IO ()
stop l = writeChan (handleChan l) Stop
log :: Handle a -> a -> IO ()
log l x = writeChan (handleChan l) (Log x)
run :: T a -> IO ()
run l =
run1 l
`Exception.catch`
\(SomeException e) ->
do hPutStrLn stderr ("Logger died: " ++ show e)
run l
run1 :: T a -> IO ()
run1 l =
Exception.bracket
(openFile (file l))
(\hdl -> hClose hdl)
(\hdl -> handleCommands l hdl)
where
openFile :: FilePath -> IO IO.Handle
openFile f =
IO.openFile f AppendMode
`Exception.catch`
\(SomeException e) ->
do hPutStrLn stderr ("Failed to open log file: " ++ show e)
Exception.throw e
handleCommands :: T a -> IO.Handle -> IO ()
handleCommands l hdl =
do comm <- readChan (chan l)
case comm of
Stop -> return ()
Log x ->
do writeLine hdl =<< format l x
handleCommands l hdl
where
writeLine :: IO.Handle -> String -> IO ()
writeLine hndl str =
do hPutStrLn hndl str
hFlush hndl