{- This file is part of irc-fun-bot. - - 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 - . -} -- | This module provides utilities for working with the bot's behavior -- definition. While the library handles event dispatch by itself, custom -- commands and bot features may benefit from having this module available to -- them (e.g. a bot's help system). module Network.IRC.Fun.Bot.Behavior ( -- * Searching findCmdInSet , findCmdInSets , findCmd , findSet , searchCmds ) where import Data.List (find) import Data.Text (Text) import Network.IRC.Fun.Bot.Types import qualified Data.CaseInsensitive as CI import qualified Data.Text as T ------------------------------------------------------------------------------- -- Searching ------------------------------------------------------------------------------- -- | Take a command name (without prefix) and a command set, and return the -- (leftmost) command which has that name, or 'Nothing' if there is no such -- command. findCmdInSet :: CommandName -> CommandSet e s -> Maybe (Command e s) findCmdInSet name = find ((name `elem`) . cmdNames) . csetCommands -- | Find a command in a list of command sets, using the given prefix character -- and command name. This is a shortcut for 'findCmd' which doesn't return the -- matched command set (for the cases you only need to find the command). findCmdInSets :: Char -> CommandName -> [CommandSet e s] -> Maybe (Command e s) findCmdInSets cpref cname sets = case findCmd cpref cname sets of Just (Right cmd) -> Just cmd _ -> Nothing -- | Find a command in a list of command sets, using the given prefix character -- and command name. If the prefix isn't matched, 'Nothing' is returned. If -- the prefix is matched but the command isn't, 'Just' 'Left' the command set -- is returned. Otherwise, 'Just' 'Right' the matched command is returned. findCmd :: Char -- ^ Command prefix to search for -> CommandName -- ^ Command name to search for -> [CommandSet e s] -- ^ Command set in which to search -> Maybe (Either (CommandSet e s) (Command e s)) findCmd cpref cname sets = case findSet cpref sets of Nothing -> Nothing Just cset -> case findCmdInSet cname cset of Nothing -> Just $ Left cset Just cmd -> Just $ Right cmd -- | Take a command prefix and a list of command sets, and return the -- (leftmost) set which has that prefex, or 'Nothing' if there is no such set. findSet :: Char -> [CommandSet e s] -> Maybe (CommandSet e s) findSet p = find ((== p) . csetPrefix) -- | Search for commands by testing a search string against their textual -- fields: Names and help strings. Each returned pair is a command and the -- prefix under which it was found. searchCmds :: Text -> [CommandSet e s] -> [(Char, Command e s)] searchCmds search = concatMap (f $ T.toCaseFold search) where match t cmd = any (t `T.isInfixOf`) (map (CI.foldedCase . unCommandName) $ cmdNames cmd) || t `T.isInfixOf` (T.toCaseFold $ cmdHelp cmd) f s cset = [(csetPrefix cset, cmd) | cmd <- csetCommands cset, match s cmd]