{- 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 #-} -- | Help and info commands -- -- Show command help, settings help, info topics module FunBot.Commands.Info ( cmdHelp' , cmdInfo ) 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.Config (introInfo) 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 Network.IRC.Fun.Client.IO (connNickname) 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 respondHelp :: Maybe Channel -> Nickname -> [Text] -> (MsgContent -> BotSession ()) -> BotSession () respondHelp _mchan nick [cname] send = do cset <- askBehaviorS $ head . commandSets let prefix = csetPrefix cset cname' = CommandName $ CI.mk $ case T.uncons cname of Nothing -> cname Just (c, r) -> if c == prefix then r else cname case find ((cname' `elem`) . cmdNames) $ csetCommands cset of Just cmd -> do bnick <- askConfigS $ unNickname . connNickname . cfgConnection let refs = [ T.singleton prefix , bnick <> ": " , bnick <> ", " ] refsC = cycle refs pseudoRandom = T.length (unNickname nick) `mod` length refs refsCR = drop pseudoRandom refsC exline p t = "\nExample: " <> p <> t examples = map (uncurry exline) $ zip refsCR (cmdExamples cmd) cmdnames = map (CI.original . unCommandName) $ cmdNames cmd send $ MsgContent $ T.concat $ cmdHelp cmd : "\nCommand names: " : T.intercalate ", " cmdnames : examples Nothing -> do succ <- respondSettingsHelp cname send unless succ $ send $ MsgContent "No such command, or invalid settings path. \ \Maybe try just ‘!help’ without a parameter." respondHelp _mchan nick _params send = send "!info intro - about me\n\ \!info commands - how to ask me to do things\n\ \!info - list of help/information topics\n\ \!help help - how to use this command\n\ \All of these work both in channels and in private messages to me." cmdHelp' = Command { cmdNames = cmds ["help", "h", "?"] , cmdRespond = respondHelp , cmdHelp = helps [ ( "help [ | ]" , "display help for the given command or settings option/section. \ \Also see ‘info’.\n\ \FunBot intends to provide interactive help, but some topics \ \may be missing. If that’s the case, check out the user manual \ \(call ‘!info links’ for the URL) or ask in #freepost." ) ] , cmdExamples = [ "help echo" , "help channels.#freepost.welcome" ] } topics = [ ( "intro" , introInfo <> "\nYou can start by trying ‘!help’." ) , ( "features" , "This is a high-level list of features and subsystems I provide. It \ \will hopefully be kept up-to-date by updating it every time new \ \features are added.\n\ \• Help and information system (!help, !info)\n\ \• A settings system (!get, !set, etc.)\n\ \• Announcing commits, tags, issues, merge requests, etc. in Git \ \repositories\n\ \• Announcing RSS/Atom feed items\n\ \• Leaving memos (requires enabling nick tracking for the channel)\n\ \• Announcing titles of URLs\n\ \• Expanding shortcuts (e.g. easily get a bug URL by its ID)\n\ \• Logging and reporting channel activity\n\ \• Welcoming new users\n\ \• Accepting events via an HTTP API, e.g. pastes added to a paste \ \bin\n\ \There is also an overview of the bot API features, useful to \ \contributors/developers, in the guide at \ \." ) , ( "contrib" , "Thinking about contributing to my development? Opening a ticket, \ \fixing a bug, implementing a feature? Check out the project page at \ \, which links to the \ \contribution guide, to the issues page and more." ) , ( "copying" , "♡ Copying is an act of love. Please copy, reuse and share me! Grab a \ \copy of me from ." ) , ( "links" , "Website: https://notabug.org/fr33domlover/funbot\n\ \Issues: https://notabug.org/fr33domlover/funbot/issues\n\ \Dev guide: https://notabug.org/fr33domlover/funbot/src/master/INSTALL.md\n\ \User manual: http://rel4tion.org/projects/funbot/manual" ) , ( "commands" , "A bot command is a specially formatted message sent either into an \ \IRC channel, or privately to me. Such a message specifies at least \ \the command name and a possibly empty list of whitespace-separated \ \parameters. Commands may have more than one name, e.g. the ‘help’ \ \command also has an alias ‘h’, among others. To see the details \ \about which parameters a specific command takes, which name aliases \ \it has and what it does, use ‘!help ’.\n\ \A command can be sent to me using a message starting with a command \ \prefix, e.g. ‘!echo hello’, or by starting a message with my \ \nickname, e.g. ‘funbot: echo hello’. Some commands work only when \ \used in a channel, some work only privately, some work in both \ \cases.\n\ \Use the ‘!info’ command to explore various aspects and features I \ \provide. Both !help and !info can be used privately."-- \n\ -- \Available commands: " <> -- T.unwords (map (CI.original . unCommandName . head . cmdNames) $ csetCommands commandSet) ) , ( "git-ann" , "I can announce development related events, such as git commits and \ \merge requests. To see the list of repos being announced and their \ \settings, run ‘!get repos’. Each repo has a list of specifications, \ \one per target channel (most projects announce to a single channel, \ \some announce to two). You can modify the spec details using the \ \settings system (!get, !set, etc.). To add a new spec (channel) to \ \an existing repo, use the !add-spec command. To remove a spec, use \ \!delete-spec. To add and remove repos, use !add-repo and \ \!delete-repo respectively." ) , ( "feeds" , "I can periodically visit news feeds (Atom, RSS, etc.) and report new \ \items to IRC channels. You can add and remove feeds using !add-feed \ \and !delete-feed respectively. You can use the settings system \ \(!get, !set, etc.) to control feed item display: activate and \ \deactivate feeds, change feed URLs, choose IRC channels in which new \ \items of a given feed are reported and control which information is \ \shown about new feed items reported." ) , ( "memos" , "You can leave a message for an offline user, and I will send them \ \the message when they come back. I can send them the message \ \privately or in the same channel you sent it to me. See the !tell \ \and !ctell commands. If you leave a memo for an online user, I will \ \send it to them instantly instead of storing it for later - but for \ \that to work, channel user list tracking needs to be enabled in my \ \settings for the relevant channel(s)." ) , ( "channels" , "Using bot commands, you can ask me to leave and join channels. The \ \list of channels I'm present in can therefore be controlled \ \dynamically. However, there is also an additional list of channels \ \in my configuration (in the source). Using !visit, you can ask me to \ \briefly join a channel. But I won't remember it next time. To make \ \me a permanent member, use !join. You can ask me to leave a channel \ \using !leave." ) , ( "chan-history" , "When you join a channel, I can send you the last messages sent there \ \so that you’ll know what was happening before you came. You can \ \enable this per channel, and set the number of last messages you’d \ \like to see per channel. Note that the number of messages you’ll get \ \also depends on how many messages I myself remember for this \ \purpose (which is set in my data files). See ‘!info user-options’ \ \for usage instructions. If you'd like to see channel history once, \ \without enabling the automatic service, see ‘!help show-history’." ) , ( "user-options" , "I keep private per-user options which affect our interaction. These \ \options are /separate/ from the public settings system. The commands \ \for managing them are available only in private messages to me, and \ \don't work in IRC channels. You can view your preferences using \ \!show-opts. Edit them using !enable-history, !disable-history and \ \!set-history-lines. Reset them to defaults using !erase-opts." ) , ( "quotes" , "See the !quote command. It works, but quotes aren’t being \ \automatically published, so perhaps it isn’t very useful at the \ \moment. Perhaps unless you setup the publishing yourself." ) , ( "shortcuts" , "I can detect special strings in your messages and send longer forms \ \of them, allowing you to define shortcuts. For example, you can \ \mention a bug ID and I will send a bug tracker URL for that bug. I \ \detect shortcuts by their prefix: Once you define a string, \ \I find occurrences of in channel messages, and resend \ \ into the channel, with and strings \ \surrounding it, thus expanding the shortcut. For example, if \ \=BUG =http://bug.org/ =.html, then if you \ \send a message containing BUG142, I will send \ \http://bug.org/142.html into the channel. See the !add-shortcut and \ \!delete-shortcut commands, and relevant settings." ) , ( "locations" , "I maintain a simple key-value mapping, where both keys and values \ \are text. The intended usage (but certainly not the only usage \ \possible) is to map short labels to URLs, therefore I call this \ \mapping the location map, or the Where map. There is a single \ \“global” map and each channel has its own map too. When searching \ \for a given label I go to the per-channel map, and if I can’t find \ \the label there, then I check in the global map. The commands for \ \querying the location map are !where, !lwhere and !gwhere. The \ \commands for adding and removing locations are !lwhere+, !gwhere+, \ \!lwhere- and !gwhere-. It’s also possible to view and modify the map \ \values (the URLs) using the settings system (e.g. !get and !set)." ) , ( "puppet" , "I have a puppet system which allows IRC users to send arbitrary \ \messages through me. This can be useful for manually identifying me \ \with NickServ and probably for various hacks. But this feature may \ \also be dangerous, therefore it has some safety mechanisms and in \ \general you should use it with care. It works as follows: There are \ \lists of “puppeteers”, which are users who can use the puppet \ \system. There’s one global list for users who can use the system in \ \any channel, and there are per-channel lists, in which users can use \ \the system only in the channel where they’re listed. The users in \ \the global list can also use the system in private messages. Once \ \you’re a puppeteer, you can start puppet mode using the \ \!puppet-start command. Then you can use !puppet-say or !puppet-echo \ \to ask me to send your message. Finally, use !puppet-end to turn off \ \puppet mode. TODO at the time of writing there are no commands yet \ \for private puppet mode. There are also no commands for managing the \ \puppeteer lists: This requires access to my JSON state files." ) ] respondInfo :: Maybe Channel -> Nickname -> [Text] -> (MsgContent -> BotSession ()) -> BotSession () respondInfo _mchan _nick [] send = send $ MsgContent $ "Topics: " <> T.intercalate ", " (map fst topics) respondInfo mchan nick [arg] send = case lookup arg topics of Just msg -> send $ MsgContent msg Nothing -> failBack mchan nick $ InvalidArg (Just 1) (Just arg) respondInfo mchan nick args _send = failBack mchan nick $ WrongNumArgsN (Just $ length args) Nothing cmdInfo = Command { cmdNames = cmds ["info", "i"] , cmdRespond = respondInfo , cmdHelp = helps [ ("info" , "list topics. Also see ‘help’.") , ("info " , "display topic information.") ] , cmdExamples = [ "info" , "info shortcuts" ] }