module Lambdabot.IRC
( IrcMessage(..)
, joinChannel
, partChannel
, getTopic
, setTopic
, codepage
, privmsg
, quit
, timeReply
, pass
, user
, setNick
) where
import Lambdabot.Message
import Lambdabot.Nick
import Data.Char (chr,isSpace)
import Data.List.Split
import Control.Monad (liftM2)
data IrcMessage
= IrcMessage {
ircMsgServer :: !String,
ircMsgLBName :: !String,
ircMsgPrefix :: !String,
ircMsgCommand :: !String,
ircMsgParams :: ![String]
}
deriving (Show)
instance Message IrcMessage where
nick = liftM2 Nick ircMsgServer (takeWhile (/= '!') . ircMsgPrefix)
server = ircMsgServer
fullName = dropWhile (/= '!') . ircMsgPrefix
channels msg =
let cstr = head $ ircMsgParams msg
in map (Nick (server msg)) $
map (\(x:xs) -> if x == ':' then xs else x:xs) (splitOn "," cstr)
lambdabotName msg = Nick (server msg) (ircMsgLBName msg)
mkMessage :: String
-> String
-> [String]
-> IrcMessage
mkMessage svr cmd params = IrcMessage
{ ircMsgServer = svr
, ircMsgPrefix = ""
, ircMsgCommand = cmd
, ircMsgParams = params
, ircMsgLBName = "urk!<outputmessage>"
}
joinChannel :: Nick -> IrcMessage
joinChannel loc = mkMessage (nTag loc) "JOIN" [nName loc]
partChannel :: Nick -> IrcMessage
partChannel loc = mkMessage (nTag loc) "PART" [nName loc]
getTopic :: Nick -> IrcMessage
getTopic chan = mkMessage (nTag chan) "TOPIC" [nName chan]
setTopic :: Nick -> String -> IrcMessage
setTopic chan topic = mkMessage (nTag chan) "TOPIC" [nName chan, ':' : topic]
privmsg :: Nick
-> String
-> IrcMessage
privmsg who msg = if action then mk [nName who, ':':(chr 0x1):("ACTION " ++ clean_msg ++ ((chr 0x1):[]))]
else mk [nName who, ':' : clean_msg]
where mk = mkMessage (nTag who) "PRIVMSG"
cleaned_msg = case filter (/= '\CR') msg of
str@('@':_) -> ' ':str
str -> str
(clean_msg,action) = case cleaned_msg of
('/':'m':'e':r) -> (dropWhile isSpace r,True)
str -> (str,False)
codepage :: String -> String -> IrcMessage
codepage svr codepage = mkMessage svr "CODEPAGE" [' ':codepage]
quit :: String -> String -> IrcMessage
quit svr msg = mkMessage svr "QUIT" [':' : msg]
timeReply :: IrcMessage -> IrcMessage
timeReply msg = msg
{ ircMsgCommand = "PRIVMSG"
, ircMsgParams = [head (ircMsgParams msg)
,":@localtime-reply " ++ (nName $ nick msg) ++ ":" ++
(init $ drop 7 (last (ircMsgParams msg))) ]
}
user :: String -> String -> String -> String -> IrcMessage
user svr nick_ server_ ircname = mkMessage svr "USER" [nick_, "localhost", server_, ircname]
pass :: String -> String -> IrcMessage
pass svr pwd = mkMessage svr "PASS" [pwd]
setNick :: Nick -> IrcMessage
setNick nick_ = mkMessage (nTag nick_) "NICK" [nName nick_]