module Lambdabot.Plugin.IRC.Log (logPlugin) where
import Lambdabot.Compat.FreenodeNick
import Lambdabot.IRC
import Lambdabot.Monad
import qualified Lambdabot.Message as Msg
import Lambdabot.Nick
import Lambdabot.Plugin
import Lambdabot.Util
import Control.Monad
import qualified Data.Map as M
import Data.Time
import System.Directory (createDirectoryIfMissing)
import System.FilePath
import System.IO
type Channel = Nick
type DateStamp = (Int, Int, Integer)
data ChanState = CS { chanHandle :: Handle,
chanDate :: DateStamp }
deriving (Show, Eq)
type LogState = M.Map Channel ChanState
type Log = ModuleT LogState LB
data Event =
Said Nick UTCTime String
| Joined Nick String UTCTime
| Parted Nick String UTCTime
| Kicked Nick Nick String UTCTime String
| Renick Nick String UTCTime Nick
| Mode Nick String UTCTime String
deriving (Eq)
instance Show Event where
show (Said nick ct what) = timeStamp ct ++ " <" ++ nName nick ++ "> " ++ what
show (Joined nick usr ct) = timeStamp ct ++ " " ++ show (FreenodeNick nick)
++ " (" ++ usr ++ ") joined."
show (Parted nick usr ct) = timeStamp ct ++ " " ++ show (FreenodeNick nick)
++ " (" ++ usr ++ ") left."
show (Kicked nick op usrop ct reason) = timeStamp ct ++ " " ++ show (FreenodeNick nick)
++ " was kicked by " ++ show (FreenodeNick op)
++ " (" ++ usrop ++ "): " ++ reason ++ "."
show (Renick nick usr ct new) = timeStamp ct ++ " " ++ show (FreenodeNick nick)
++ " (" ++ usr ++ ") is now " ++ show (FreenodeNick new) ++ "."
show (Mode nick usr ct mode) = timeStamp ct ++ " " ++ show (FreenodeNick nick)
++ " (" ++ usr ++ ") changed mode to " ++ mode ++ "."
logPlugin :: Module (M.Map Channel ChanState)
logPlugin = newModule
{ moduleDefState = return M.empty
, moduleExit = cleanLogState
, moduleInit = do
let doLog f m hdl = logString hdl . show . f m
connect signal cb = registerCallback signal $ \msg -> do
now <- io getCurrentTime
mapM_ (withValidLog (doLog cb msg) now) (Msg.channels msg)
connect "PRIVMSG" msgCB
connect "JOIN" joinCB
connect "PART" partCB
connect "KICK" kickCB
connect "NICK" nickCB
connect "MODE" modeCB
}
showWidth :: Int
-> Int
-> String
showWidth width n = zeroes ++ num
where num = show n
zeroes = replicate (width - length num) '0'
timeStamp :: UTCTime -> String
timeStamp (UTCTime _ ct) =
(showWidth 2 (hours `mod` 24)) ++ ":" ++
(showWidth 2 (mins `mod` 60)) ++ ":" ++
(showWidth 2 (secs `mod` 60))
where
secs = round ct :: Int
mins = secs `div` 60
hours = mins `div` 60
dateToString :: DateStamp -> String
dateToString (d, m, y) = (showWidth 2 $ fromInteger y) ++ "-" ++
(showWidth 2 $ fromEnum m + 1) ++ "-" ++
(showWidth 2 d)
dateStamp :: UTCTime -> DateStamp
dateStamp (UTCTime day _) = (d, m, y)
where (y,m,d) = toGregorian day
cleanLogState :: Log ()
cleanLogState =
withMS $ \state writer -> do
io $ M.foldr (\cs iom -> iom >> hClose (chanHandle cs)) (return ()) state
writer M.empty
getChannel :: Channel -> Log ChanState
getChannel c = (readMS >>=) . mLookup $ c
where mLookup k = maybe (fail "getChannel: not found") return . M.lookup k
getDate :: Channel -> Log DateStamp
getDate c = fmap chanDate . getChannel $ c
getHandle :: Channel -> Log Handle
getHandle c = fmap chanHandle . getChannel $ c
putHdlAndDS :: Channel -> Handle -> DateStamp -> Log ()
putHdlAndDS c hdl ds =
modifyMS (M.adjust (\cs -> cs {chanHandle = hdl, chanDate = ds}) c)
openChannelFile :: Channel -> UTCTime -> Log Handle
openChannelFile chan ct = do
logDir <- lb $ findLBFileForWriting "Log"
let dir = logDir </> nTag chan </> nName chan
file = dir </> (dateToString date) <.> "txt"
io $ createDirectoryIfMissing True dir >> openFile file AppendMode
where date = dateStamp ct
reopenChannelMaybe :: Channel -> UTCTime -> Log ()
reopenChannelMaybe chan ct = do
date <- getDate chan
when (date /= dateStamp ct) $ do
hdl <- getHandle chan
io $ hClose hdl
hdl' <- openChannelFile chan ct
putHdlAndDS chan hdl' (dateStamp ct)
initChannelMaybe :: Nick -> UTCTime -> Log ()
initChannelMaybe chan ct = do
chanp <- liftM (M.member chan) readMS
unless chanp $ do
hdl <- openChannelFile chan ct
modifyMS (M.insert chan $ CS hdl (dateStamp ct))
withValidLog :: (Handle -> UTCTime -> Log a) -> UTCTime -> Channel -> Log a
withValidLog f ct chan = do
initChannelMaybe chan ct
reopenChannelMaybe chan ct
hdl <- getHandle chan
rv <- f hdl ct
return rv
logString :: Handle -> String -> Log ()
logString hdl str = io $ hPutStrLn hdl str >> hFlush hdl
joinCB :: IrcMessage -> UTCTime -> Event
joinCB msg ct = Joined (Msg.nick msg) (Msg.fullName msg) ct
partCB :: IrcMessage -> UTCTime -> Event
partCB msg ct = Parted (Msg.nick msg) (Msg.fullName msg) ct
kickCB :: IrcMessage -> UTCTime -> Event
kickCB msg ct = Kicked (Msg.nick msg) { nName = head $ tail $ ircMsgParams msg }
(Msg.nick msg)
(Msg.fullName msg)
ct
(tail . concat . tail . tail $ ircMsgParams msg)
nickCB :: IrcMessage -> UTCTime -> Event
nickCB msg ct = Renick (Msg.nick msg) (Msg.fullName msg) ct
(parseNick (Msg.server msg) $ drop 1 $ head $ ircMsgParams msg)
modeCB :: IrcMessage -> UTCTime -> Event
modeCB msg ct = Mode (Msg.nick msg) (Msg.fullName msg) ct
(unwords $ tail $ ircMsgParams msg)
msgCB :: IrcMessage -> UTCTime -> Event
msgCB msg ct = Said (Msg.nick msg) ct
(tail . concat . tail $ ircMsgParams msg)