module System.Log.Handler.Growl(addTarget, growlHandler)
where
import Data.Char
import Data.Word
import Network.Socket
import Network.BSD
import System.Log
import System.Log.Handler
import System.Log.Formatter
data GrowlHandler = GrowlHandler { priority :: Priority,
formatter :: LogFormatter GrowlHandler,
appName :: String,
skt :: Socket,
targets :: [HostAddress] }
instance LogHandler GrowlHandler where
setLevel gh p = gh { priority = p }
getLevel = priority
setFormatter gh f = gh { formatter = f }
getFormatter = formatter
emit gh lr _ = let pkt = buildNotification gh nmGeneralMsg lr
in mapM_ (sendNote (skt gh) pkt) (targets gh)
close gh = let pkt = buildNotification gh nmClosingMsg
(WARNING, "Connection closing.")
s = skt gh
in mapM_ (sendNote s pkt) (targets gh) >> sClose s
sendNote :: Socket -> String -> HostAddress -> IO Int
sendNote s pkt ha = sendTo s pkt (SockAddrInet 9887 ha)
nmGeneralMsg :: String
nmGeneralMsg = "message"
nmClosingMsg :: String
nmClosingMsg = "disconnecting"
growlHandler :: String
-> Priority
-> IO GrowlHandler
growlHandler nm pri =
do { s <- socket AF_INET Datagram 0
; return GrowlHandler { priority = pri, appName = nm, formatter=nullFormatter,
skt = s, targets = [] }
}
emit16 :: Word16 -> String
emit16 v = let (h, l) = (fromEnum v) `divMod` 256 in [chr h, chr l]
emitLen16 :: [a] -> String
emitLen16 = emit16 . fromIntegral . length
buildRegistration :: GrowlHandler -> String
buildRegistration s = concat fields
where fields = [ ['\x1', '\x4'],
emitLen16 (appName s),
emitLen8 appNotes,
emitLen8 appNotes,
appName s,
foldl packIt [] appNotes,
['\x0' .. (chr (length appNotes 1))] ]
packIt a b = a ++ (emitLen16 b) ++ b
appNotes = [ nmGeneralMsg, nmClosingMsg ]
emitLen8 v = [chr $ length v]
addTarget :: HostName -> GrowlHandler -> IO GrowlHandler
addTarget hn gh = do { he <- getHostByName hn
; let ha = hostAddress he
sa = SockAddrInet 9887 ha
in do { sendTo (skt gh) (buildRegistration gh) sa
; return gh { targets = ha:(targets gh) } } }
toFlags :: Priority -> Word16
toFlags DEBUG = 12
toFlags INFO = 10
toFlags NOTICE = 0
toFlags WARNING = 2
toFlags ERROR = 3
toFlags CRITICAL = 3
toFlags ALERT = 4
toFlags EMERGENCY = 5
buildNotification :: GrowlHandler
-> String
-> LogRecord
-> String
buildNotification gh nm (p, msg) = concat fields
where fields = [ ['\x1', '\x5'],
emit16 (toFlags p),
emitLen16 nm,
emit16 0,
emitLen16 msg,
emitLen16 (appName gh),
nm,
[],
msg,
appName gh ]