module System.Log.Handler.Syslog(
                                       
                                       openlog,
                                       
#ifndef mingw32_HOST_OS
                                       openlog_local,
#endif
                                       openlog_remote,
                                       openlog_generic,
                                       
                                       Facility(..),
                                       Option(..)
                                       ) where
import System.Log
import System.Log.Formatter
import System.Log.Handler
import Data.Bits
import Network.Socket
import Network.BSD
import Data.List
#ifndef mingw32_HOST_OS
import System.Posix.Process(getProcessID)
#endif
import System.IO
code_of_pri :: Priority -> Int
code_of_pri p = case p of
                       EMERGENCY -> 0
                       ALERT -> 1
                       CRITICAL -> 2
                       ERROR -> 3
                       WARNING -> 4
                       NOTICE -> 5
                       INFO -> 6
                       DEBUG -> 7
data Facility = 
              KERN                      
              | USER                    
              | MAIL                    
              | DAEMON                  
              | AUTH                    
              | SYSLOG                  
              | LPR                     
              | NEWS                    
              | UUCP                    
              | CRON                    
              | AUTHPRIV                
              | FTP                     
              | LOCAL0                  
              | LOCAL1
              | LOCAL2
              | LOCAL3
              | LOCAL4
              | LOCAL5
              | LOCAL6
              | LOCAL7
                deriving (Eq, Show, Read)
code_of_fac :: Facility -> Int
code_of_fac f = case f of
                       KERN -> 0
                       USER -> 1
                       MAIL -> 2
                       DAEMON -> 3
                       AUTH -> 4
                       SYSLOG -> 5
                       LPR -> 6
                       NEWS -> 7
                       UUCP -> 8
                       CRON -> 9
                       AUTHPRIV -> 10
                       FTP -> 11
                       LOCAL0 -> 16
                       LOCAL1 -> 17
                       LOCAL2 -> 18
                       LOCAL3 -> 19
                       LOCAL4 -> 20
                       LOCAL5 -> 21
                       LOCAL6 -> 22
                       LOCAL7 -> 23
makeCode :: Facility -> Priority -> Int
makeCode fac pri =
    let faccode = code_of_fac fac
        pricode = code_of_pri pri in
        (faccode `shiftL` 3) .|. pricode
data Option = PID                       
            | PERROR                    
            deriving (Eq,Show,Read)
data SyslogHandler = SyslogHandler {options :: [Option],
                                    facility :: Facility,
                                    identity :: String,
                                    logsocket :: Socket,
                                    address :: SockAddr,
                                    priority :: Priority,
                                    formatter :: LogFormatter SyslogHandler
                                   }
openlog :: String                       
        -> [Option]                     
        -> Facility                     
        -> Priority                     
        -> IO SyslogHandler             
#ifdef mingw32_HOST_OS
openlog = openlog_remote AF_INET "localhost" 514
#elif darwin_HOST_OS
openlog = openlog_local "/var/run/syslog"
#else
openlog = openlog_local "/dev/log"
#endif
#ifndef mingw32_HOST_OS
openlog_local :: String                 
              -> String                 
              -> [Option]               
              -> Facility               
              -> Priority               
              -> IO SyslogHandler
openlog_local fifopath ident options fac pri =
    do
    s <- socket AF_UNIX Datagram 0
    openlog_generic s (SockAddrUnix fifopath) ident options fac pri
#endif
openlog_remote :: Family                
               -> HostName              
               -> PortNumber            
               -> String                
               -> [Option]              
               -> Facility              
               -> Priority              
               -> IO SyslogHandler
openlog_remote fam hostname port ident options fac pri =
    do
    he <- getHostByName hostname
    s <- socket fam Datagram 0
    let addr = SockAddrInet port (head (hostAddresses he))
    openlog_generic s addr ident options fac pri
    
openlog_generic :: Socket               
                -> SockAddr             
                -> String               
                -> [Option]             
                -> Facility             
                -> Priority             
                -> IO SyslogHandler
openlog_generic sock addr ident opt fac pri =
    return (SyslogHandler {options = opt,
                            facility = fac,
                            identity = ident,
                            logsocket = sock,
                            address = addr,
                            priority = pri,
                            formatter = syslogFormatter
                          })
syslogFormatter :: LogFormatter SyslogHandler
syslogFormatter sh (p,msg) logname =
    let code = makeCode (facility sh) p
        getpid :: IO String
        getpid = 
#ifndef mingw32_HOST_OS
                     getProcessID >>= return . show
#else
                     return "windows"
#endif
        vars = [("code", return $ show code)
               ,("identity", return $ identity sh)
               ,("pid", getpid)]
        withPid = if (elem PID (options sh)) then "[$pid]" else ""
        format = "<$code>$identity"++withPid++": [$loggername/$prio] $msg"
    in varFormatter vars format sh (p,msg) logname
instance LogHandler SyslogHandler where
    setLevel sh p = sh{priority = p}
    getLevel sh = priority sh
    setFormatter sh f = sh{formatter = f}
    getFormatter sh = formatter sh
    emit sh (_, msg) _ = 
        let                      
            sendstr :: String -> IO String
            sendstr [] = return []
            sendstr omsg = do
                           sent <- sendTo (logsocket sh) omsg (address sh)
                           sendstr (genericDrop sent omsg)
        in do
          if (elem PERROR (options sh))
               then hPutStrLn stderr msg
               else return ()
          sendstr (msg ++ "\0")
          return ()
    close sh = sClose (logsocket sh)