{- This file is part of irc-fun-bot. - - Written in 2015, 2016 by fr33domlover . - - ♡ Copying is an act of love. Please copy, reuse and share. - - The author(s) have dedicated all copyright and related and neighboring - rights to this software to the public domain worldwide. This software is - distributed without any warranty. - - You should have received a copy of the CC0 Public Domain Dedication along - with this software. If not, see - . -} module Network.IRC.Fun.Bot.Internal.History ( rememberMsg , checkEvent ) where import Control.Monad (liftM, when) import Control.Monad.IO.Class (liftIO) import Data.Sequence ((|>)) import Network.IRC.Fun.Bot.Internal.Monad (modify) import Network.IRC.Fun.Bot.Internal.State import Network.IRC.Fun.Bot.Internal.Types import Network.IRC.Fun.Types import qualified Data.HashMap.Lazy as M import qualified Data.Sequence as Q import qualified Data.Sequence.Util as QU import qualified Network.IRC.Fun.Client.Events as C (Event (..)) -- | Remember someone said something, for use later when quoting. rememberMsg :: Channel -> Nickname -> MsgContent -> Bool -- ^ Whether a /me action (True) or regular message (False) -> Session e s () rememberMsg chan nick msg action = do maxlines <- liftM (maybe 0 csHistoryLines . M.lookup chan) getChans when (maxlines > 0) $ do h <- getHistory t <- askTimeGetter >>= liftIO . liftM snd m <- getMinutes let hl = HistoryLine { hlTime = t , hlNick = nick , hlMessage = msg , hlAction = action , hlMinute = m } shorten s = if Q.length s > maxlines then QU.tail s else s hls' = case M.lookup chan h of Just hls -> shorten $ hls |> hl Nothing -> Q.singleton hl modify $ \ s -> s { bsHistory = M.insert chan hls' h } -- | If a client event is a message to remember, get details. checkEvent :: C.Event -> Maybe (Msg a) checkEvent (C.ChannelMessage chan nick msg _) = Just $ MsgHistoryEvent nick chan msg False checkEvent (C.ChannelAction chan nick msg) = Just $ MsgHistoryEvent nick chan msg True checkEvent _ = Nothing