{- This file is part of funbot. - - 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 - . -} {-# LANGUAGE OverloadedStrings #-} -- | Show-opts, enable-history, disable-history, set-history-lines, -- get-history-lines, erase-opts commands -- -- Manage user options module FunBot.Commands.UserOptions ( cmdShowOpts , cmdEnableHistory , cmdDisableHistory , cmdSetLines , cmdEraseOpts ) where import Control.Monad (unless, when) import Data.List (find, intercalate) import Data.Monoid ((<>)) import Data.Settings.Types (showOption) import Data.Text (Text) import FunBot.History (quote, reportHistory') import FunBot.Memos (submitMemo) import FunBot.Settings import FunBot.Settings.Sections.Channels (addChannel) import FunBot.Settings.Sections.Feeds (addFeed, deleteFeed) import FunBot.Settings.Sections.Repos import FunBot.Settings.Sections.Shortcuts (addShortcut, deleteShortcut) 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 Text.Read (readMaybe) import Network.IRC.Fun.Types.Base import qualified Data.CaseInsensitive as CI import qualified Data.Text as T import qualified Data.Text.Read as TR priv = MsgContent "That command works only in private conversation with me." respondShowOpts :: Maybe Channel -> Nickname -> [Text] -> (MsgContent -> BotSession ()) -> BotSession () respondShowOpts (Just _chan) _nick _args send = send priv respondShowOpts Nothing nick [] _send = sendChannels nick respondShowOpts Nothing nick [chan] send = if looksLikeChan $ Channel chan then sendHistoryOpts nick $ Channel chan else send $ notchan $ Channel chan respondShowOpts Nothing nick args _send = failToUser nick $ WrongNumArgsN (Just $ length args) Nothing cmdShowOpts = Command { cmdNames = cmds ["show-opts", "show-options"] , cmdRespond = respondShowOpts , cmdHelp = helps [ ( "show-opts" , "list channels for which you set history display options." ) , ( "show-opts " , "show history display options for the given channel." ) ] , cmdExamples = [ "show-opts" , "show-opts #snowdrift" ] } respondHistory :: Bool -> Maybe Channel -> Nickname -> [Text] -> (MsgContent -> BotSession ()) -> BotSession () respondHistory _enable (Just _chan) _nick _args send = send priv respondHistory enable Nothing nick [chan] send = if looksLikeChan $ Channel chan then do setEnabled nick (Channel chan) enable hls <- getHistoryLines $ Channel chan when (enable && hls < 1) $ send $ MsgContent "Note that while you enabled personal history display, \ \history logging is disabled for that channel, therefore you \ \won’t be getting history messages. Ask the bot maintainer(s) \ \to enable it." else send $ notchan $ Channel chan respondHistory _enable Nothing nick args _send = failToUser nick $ WrongNumArgsN (Just $ length args) (Just 1) cmdEnableHistory = Command { cmdNames = cmds ["history+", "enable-history"] , cmdRespond = respondHistory True , cmdHelp = helps [ ( "history+ " , "enable automatic history private display for the given channel." ) ] , cmdExamples = [ "history+ #snowdrift" ] } cmdDisableHistory = Command { cmdNames = cmds ["history-", "disable-history"] , cmdRespond = respondHistory False , cmdHelp = helps [ ( "history- " , "disable automatic history private display for the given channel." ) ] , cmdExamples = [ "history- #snowdrift-test" ] } respondSetLines :: Maybe Channel -> Nickname -> [Text] -> (MsgContent -> BotSession ()) -> BotSession () respondSetLines (Just _chan) _nick _args send = send priv respondSetLines Nothing nick [chan, len] send = if looksLikeChan $ Channel chan then case TR.decimal len of Right (n, "") -> setMaxLines nick (Channel chan) n _ -> badLen else send $ notchan $ Channel chan where badLen = failToUser nick $ InvalidArg (Just 2) (Just len) respondSetLines Nothing nick args _send = failToUser nick $ WrongNumArgsN (Just $ length args) (Just 2) cmdSetLines = Command { cmdNames = cmds ["set-history-lines"] , cmdRespond = respondSetLines , cmdHelp = helps [ ( "set-history-lines " , "set the maximal number of channel history lines to display." ) ] , cmdExamples = [ "set-history-lines #snowdrift 10" ] } respondEraseOpts :: Maybe Channel -> Nickname -> [Text] -> (MsgContent -> BotSession ()) -> BotSession () respondEraseOpts (Just _chan) _nick _args send = send priv respondEraseOpts Nothing nick [] _send = eraseOpts nick respondEraseOpts Nothing nick args _send = failToUser nick $ WrongNumArgsN (Just $ length args) (Just 0) cmdEraseOpts = Command { cmdNames = cmds ["erase-opts", "erase-options"] , cmdRespond = respondEraseOpts , cmdHelp = helps [ ( "erase-opts" , "reset all your options back to defaults." ) ] , cmdExamples = [ "erase-opts" ] }