{- This file is part of irc-fun-client. - - 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 convenient functions for performing common IRC client -- actions. Some of them simply send a single IRC message, while othere send a -- sequence of several messages. module Network.IRC.Fun.Client.Commands ( ircLogin , ircPong , ircJoin , ircJoinMulti , ircPart , ircPartMulti , ircPartAll , ircSendToUser , ircNoticeToUser , ircActToUser , ircSendToChannel , ircNoticeToChannel , ircActToChannel , ircQuit ) where import Control.Monad (unless) import Data.Maybe (fromMaybe, isNothing) import Network.IRC.Fun.Messages import Network.IRC.Fun.Types import Network.IRC.Fun.Client.IO import qualified Data.Text as T -- | Log in as an IRC user with nickname and optional password, using the given -- connection parameters. ircLogin :: Connection -- ^ Handle to the open socket, returned from 'ircConnect' -> ConnConfig -- ^ Connection configuration -> Bool -- ^ Whether you want to be invisible (mode @+i@) -> Bool -- ^ Whether you want to see wallops (mode @+w@) -> IO () ircLogin c cfg i w = do case connPassword cfg of Just pass -> hPutIrc c $ PassMessage pass Nothing -> return () let nick = connNickname cfg t = unNickname nick hPutIrc c $ UserMessage (Username t) i w (RealName t) hPutIrc c $ NickMessage nick -- | IRC servers send PING messages at regular intervals to test the presence -- of an active client, at least if no other activity is detected on the -- connection. The server closes the connection automatically if a PONG -- response isn't sent from the client within a certain amount of time. -- -- Therefore, an IRC client usually listens to these PINGs and sends back PONG -- messages. This function sends a PONG. The parameters should simply be the -- ones received in the PING message. ircPong :: Connection -- ^ Handle to the open socket -> Hostname -- ^ Server name -> Maybe Hostname -- ^ Optional server to forward to -> IO () ircPong c s ms = hPutIrc c $ PongMessage s ms -- | Join an IRC channel. ircJoin :: Connection -- ^ Handle to the open socket -> Channel -- ^ Channel name -> Maybe ChannelKey -- ^ Optional channel key (password) -> IO () ircJoin c chan key = ircJoinMulti c [(chan, key)] -- | Join one or more IRC channels. ircJoinMulti :: Connection -- ^ Handle to the open socket -> [(Channel, Maybe ChannelKey)] -- ^ List of channels and optional keys -> IO () ircJoinMulti _ [] = return () ircJoinMulti c l = do let nokey = [ chan | (chan, Nothing) <- l ] (chans, keys) = unzip [ (chan, key) | (chan, (Just key)) <- l ] unless (null nokey) $ hPutIrc c $ JoinMessage $ Just (nokey, []) unless (null chans) $ hPutIrc c $ JoinMessage $ Just (chans, keys) -- | Leave an IRC channel. ircPart :: Connection -> Channel -> Maybe Comment -> IO () ircPart c chan = ircPartMulti c [chan] -- | Leave one or more IRC channels. ircPartMulti :: Connection -> [Channel] -> Maybe Comment -> IO () ircPartMulti _ [] _ = return () ircPartMulti c chans msg = hPutIrc c $ PartMessage chans msg -- | Leave all IRC channels you joined. ircPartAll :: Connection -> IO () ircPartAll c = hPutIrc c $ JoinMessage Nothing -- | Send a private message to an IRC user. ircSendToUser :: Connection -- ^ Handle to the open socket -> Nickname -- ^ The user's nickname -> MsgContent -- ^ The message to send -> IO () ircSendToUser c nick msg = hPutIrc c $ PrivMsgMessage (UserTarget (Just nick) Nothing Nothing) msg -- | Send a private notice to an IRC user. ircNoticeToUser :: Connection -- ^ Handle to the open socket -> Nickname -- ^ The user's nickname -> MsgContent -- ^ The message to send -> IO () ircNoticeToUser c nick msg = hPutIrc c $ NoticeMessage (UserTarget (Just nick) Nothing Nothing) msg -- | Send a private /me message to an IRC user. ircActToUser :: Connection -- ^ Handle to the open socket -> Nickname -- ^ The user's nickname -> MsgContent -- ^ The message to send -> IO () ircActToUser c nick msg = hPutIrc c $ PrivActionMessage (UserTarget (Just nick) Nothing Nothing) msg -- | Send a message to an IRC channel. ircSendToChannel :: Connection -- ^ Handle to the open socket -> Channel -- ^ The channel name -> MsgContent -- ^ The message to send -> IO () ircSendToChannel c chan msg = hPutIrc c $ PrivMsgMessage (ChannelTarget chan) msg -- | Send a notice to an IRC channel. ircNoticeToChannel :: Connection -- ^ Handle to the open socket -> Channel -- ^ The channel name -> MsgContent -- ^ The message to send -> IO () ircNoticeToChannel c chan msg = hPutIrc c $ NoticeMessage (ChannelTarget chan) msg -- | Send a \/me message to an IRC channel. ircActToChannel :: Connection -- ^ Handle to the open socket -> Channel -- ^ The channel name -> MsgContent -- ^ The message to send -> IO () ircActToChannel c chan msg = hPutIrc c $ PrivActionMessage (ChannelTarget chan) msg -- | Finish the IRC session, asking the server to close the connection. ircQuit :: Connection -- ^ Handle to the open socket -> Maybe Comment -- ^ Optional message, e.g. the reason you quit -> IO () ircQuit c m = hPutIrc c $ QuitMessage m