{- This file is part of funbot. - - Written in 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 - . -} {-# LANGUAGE OverloadedStrings #-} -- | Where, lwhere, gwhere, lwhere+, lwhere-, gwhere+, gwhere- commands -- -- Manage and query locations module FunBot.Commands.Locations ( cmdWhere , cmdWhereLocal , cmdWhereGlobal , cmdAddWhereLocal , cmdRemoveWhereLocal , cmdAddWhereGlobal , cmdRemoveWhereGlobal ) where import Control.Monad (unless, when) import Data.List (find, intercalate) import Data.Monoid ((<>)) import Data.Settings.Types (showOption) import Data.Text (Text) import Formatting ((%)) import FunBot.History (quote, reportHistory') import FunBot.Locations import FunBot.Memos (submitMemo) import FunBot.Settings import FunBot.Settings.Sections.Channels import FunBot.Settings.Sections.Locations import FunBot.Types import FunBot.UserOptions import FunBot.Util import Network.IRC.Fun.Bot.Behavior import Network.IRC.Fun.Bot.Chat import Network.IRC.Fun.Bot.State import Network.IRC.Fun.Bot.Types import Network.IRC.Fun.Color.Format (formatMsg) import Network.IRC.Fun.Color.Format.Long import Network.IRC.Fun.Types.Base import Text.Read (readMaybe) import qualified Data.CaseInsensitive as CI import qualified Data.Text as T import qualified Data.Text.Read as TR --import qualified Network.IRC.Fun.Color.Format.Short as F respondLookup :: (LocationLabel -> BotSession (Maybe Location)) -> Nickname -> Text -> (MsgContent -> BotSession ()) -> BotSession () respondLookup flookup nick labelt send = do let label = LocationLabel $ CI.mk labelt mloc <- flookup label case mloc of Nothing -> send $ formatMsg (nickname % ", location ‘" % text % "’ not found.") nick labelt Just loc -> send $ MsgContent $ labelt <> " : " <> unLocation loc respondLookupBoth :: Channel -> Nickname -> Text -> (MsgContent -> BotSession ()) -> BotSession () respondLookupBoth chan = respondLookup $ lookupBoth chan respondLookupLocal :: Channel -> Nickname -> Text -> (MsgContent -> BotSession ()) -> BotSession () respondLookupLocal chan = respondLookup $ lookupLocal chan respondLookupGlobal :: Nickname -> Text -> (MsgContent -> BotSession ()) -> BotSession () respondLookupGlobal = respondLookup lookupGlobal respondWhere :: Maybe Channel -> Nickname -> [Text] -> (MsgContent -> BotSession ()) -> BotSession () respondWhere mchan nick [labelt] send = let respond = maybe respondLookupGlobal respondLookupBoth mchan in respond nick labelt send respondWhere mchan nick [labelt, chant] send = let chan = Channel chant in if looksLikeChan chan then respondLookupBoth chan nick labelt send else send $ notchan chan respondWhere mchan nick args _send = failBack mchan nick $ WrongNumArgsN (Just $ length args) Nothing cmdWhere = Command { cmdNames = cmds ["where"] , cmdRespond = respondWhere , cmdHelp = "‘where