module System.Log.Handler.Simple(streamHandler, fileHandler,
                                      GenericHandler (..),
                                      verboseStreamHandler)
    where
import Control.Exception (SomeException, tryJust)
import Data.Char (ord)
import System.Log
import System.Log.Handler
import System.Log.Formatter
import System.IO
import System.IO.Error
import Control.Concurrent.MVar
data GenericHandler a = GenericHandler {priority :: Priority,
                                        formatter :: LogFormatter (GenericHandler a),
                                        privData :: a,
                                        writeFunc :: a -> String -> IO (),
                                        closeFunc :: a -> IO () }
instance LogHandler (GenericHandler a) where
    setLevel sh p = sh{priority = p}
    getLevel sh = priority sh
    setFormatter sh f = sh{formatter = f}
    getFormatter sh = formatter sh
    emit sh (_,msg) _ = (writeFunc sh) (privData sh) msg
    close sh = (closeFunc sh) (privData sh)
streamHandler :: Handle -> Priority -> IO (GenericHandler Handle)
streamHandler h pri =
    do lock <- newMVar ()
       let mywritefunc hdl msg =
               withMVar lock (\_ -> do writeToHandle hdl msg
                                       hFlush hdl
                             )
       return (GenericHandler {priority = pri,
                               formatter = nullFormatter,
                               privData = h,
                               writeFunc = mywritefunc,
                               closeFunc = \x -> return ()})
    where
      writeToHandle hdl msg = do
          rv <- tryJust myException (hPutStrLn hdl msg)
          either (handleWriteException hdl msg) return rv
      myException e
          | isDoesNotExistError e = Just e
          | otherwise = Nothing
      handleWriteException hdl msg e =
          let msg' = "Error writing log message: " ++ show e ++
                     " (original message: " ++ msg ++ ")"
          in hPutStrLn hdl (encodingSave msg')
      encodingSave = concatMap (\c -> if ord c > 127
                                         then "\\" ++ show (ord c)
                                         else [c])
fileHandler :: FilePath -> Priority -> IO (GenericHandler Handle)
fileHandler fp pri = do
                     h <- openFile fp AppendMode
                     sh <- streamHandler h pri
                     return (sh{closeFunc = hClose})
verboseStreamHandler :: Handle -> Priority -> IO (GenericHandler Handle)
verboseStreamHandler h pri = let fmt = simpleLogFormatter "[$loggername/$prio] $msg"
                             in do hndlr <- streamHandler h pri
                                   return $ setFormatter hndlr fmt