{- This file is part of funbot. - - Written in 2015 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 FunBot.Util ( (!?) , replaceMaybe , passes , passesBy , getTimeStr , getHistoryLines ) where import Control.Monad (liftM) import Control.Monad.IO.Class (liftIO) import Data.Maybe (listToMaybe) import FunBot.Types import Network.IRC.Fun.Bot.State (askTimeGetter, getChanInfo) import Network.IRC.Fun.Bot.Types (ChanInfo (ciHistoryLines)) import qualified Data.HashMap.Lazy as M (lookup) -- | List index operator, starting from 0. Like @!!@ but returns a 'Maybe' -- instead of throwing an exception. On success, returns 'Just' the item. On -- out-of-bounds index, returns 'Nothing'. (!?) :: [a] -> Int -> Maybe a l !? i = listToMaybe $ drop i l -- | Replace the list item at the given position, with the given new item. -- Return the resulting list. If the position is out of range, return -- 'Nothing'. replaceMaybe :: [a] -> Int -> a -> Maybe [a] replaceMaybe l i y = case splitAt i l of (_, []) -> Nothing (b, x:xs) -> Just $ b ++ y : xs -- | Check whether a value passes a given filter. passes :: Eq a => a -> Filter a -> Bool v `passes` (Accept l) = v `elem` l v `passes` (Reject l) = v `notElem` l -- | Like 'passes', but using a given predicate to compare items. passesBy :: (a -> a -> Bool) -> a -> Filter a -> Bool passesBy p v (Accept l) = any (p v) l passesBy p v (Reject l) = all (not . p v) l -- | Get a string specifying the current UTC time using the time getter. getTimeStr :: BotSession String getTimeStr = do getTime <- askTimeGetter liftIO $ liftM snd getTime -- | Get the number of history lines recorded in memory for a given channel. If -- the channel doesn't have state held for it, 0 is returned. getHistoryLines :: String -> BotSession Int getHistoryLines chan = do cs <- getChanInfo return $ maybe 0 ciHistoryLines $ M.lookup chan cs