{- 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 , ircSendToChannel , ircQuit ) where import Control.Monad (unless) import Data.Maybe (isNothing) import Network.IRC.Fun.Messages import Network.IRC.Fun.Messages.Types import Network.IRC.Fun.Client.IO -- | Log in as an IRC user with nickname and optional password, using the given -- connection parameters. ircLogin :: Handle -- ^ Handle to the open socket, returned from -- 'ircConnect' -> Connection -- ^ Connection configuration -> Bool -- ^ Whether you want to be invisible (mode @+i@) -> Bool -- ^ Whether you want to see wallops (mode @+w@) -> IO () ircLogin h conn i w = do let pass = password conn pass' = case pass of Just p -> p Nothing -> "" unless (isNothing pass) $ hPutIrc h $ PassMessage pass' hPutIrc h $ UserMessage (nick conn) i w (nick conn) hPutIrc h $ NickMessage $ nick conn -- | 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 :: Handle -- ^ Handle to the open socket -> String -- ^ Server name -> Maybe String -- ^ Optional server to forward to -> IO () ircPong h s ms = hPutIrc h $ PongMessage s ms -- | Join an IRC channel. ircJoin :: Handle -- ^ Handle to the open socket -> String -- ^ Channel name -> Maybe String -- ^ Optional channel key (password) -> IO () ircJoin h chan key = ircJoinMulti h [(chan, key)] -- | Join one or more IRC channels. ircJoinMulti :: Handle -- ^ Handle to the open socket -> [(String, Maybe String)] -- ^ List of channels and optional -- keys -> IO () ircJoinMulti _ [] = return () ircJoinMulti h l = do let nokey = [ chan | (chan, Nothing) <- l ] (chans, keys) = unzip [ (chan, key) | (chan, (Just key)) <- l ] unless (null nokey) $ hPutIrc h $ JoinMessage $ Just (nokey, []) unless (null chans) $ hPutIrc h $ JoinMessage $ Just (chans, keys) -- | Leave an IRC channel. ircPart :: Handle -> String -> Maybe String -> IO () ircPart h chan = ircPartMulti h [chan] -- | Leave one or more IRC channels. ircPartMulti :: Handle -> [String] -> Maybe String -> IO () ircPartMulti _ [] _ = return () ircPartMulti h chans msg = hPutIrc h $ PartMessage chans msg -- | Leave all IRC channels you joined. ircPartAll :: Handle -> IO () ircPartAll h = hPutIrc h $ JoinMessage Nothing -- | Send a private message to an IRC user. ircSendToUser :: Handle -- ^ Handle to the open socket -> String -- ^ The user's nickname -> String -- ^ The message to send -> IO () ircSendToUser h nick msg = hPutIrc h $ PrivMsgMessage (UserTarget (Just nick) Nothing Nothing) msg -- | Send a message to an IRC channel. ircSendToChannel :: Handle -- ^ Handle to the open socket -> String -- ^ The channel name -> String -- ^ The message to send -> IO () ircSendToChannel h chan msg = hPutIrc h $ PrivMsgMessage (ChannelTarget chan) msg -- | Finish the IRC session, asking the server to close the connection. ircQuit :: Handle -- ^ Handle to the open socket -> Maybe String -- ^ Optional message, e.g. the reason you quit -> IO () ircQuit h m = hPutIrc h $ QuitMessage m