{-# Language QuasiQuotes, OverloadedStrings #-}
module Client.Hook.FreRelay
( freRelayHook
) where
import Data.List (uncons)
import qualified Data.Text as Text
import Data.Text (Text)
import Data.Foldable (asum)
import Text.Regex.TDFA (match, defaultCompOpt, defaultExecOpt, Regex)
import Text.Regex.TDFA.String (compile)
import Client.Hook (MessageHook(..), MessageResult(..))
import Irc.Message
import Irc.Identifier (mkId, Identifier)
import Irc.UserInfo (UserInfo(..))
import StrQuote (str)
freRelayHook :: [Text] -> Maybe MessageHook
freRelayHook args = Just (MessageHook "frerelay" False (remap (map mkId args)))
remap :: [Identifier] -> IrcMsg -> MessageResult
remap nicks (Privmsg (UserInfo nick _ _) chan@"#dronebl" msg)
| nick `elem` nicks
, Just sub <- rules chan msg = RemapMessage sub
remap _ _ = PassMessage
rules ::
Identifier ->
Text ->
Maybe IrcMsg
rules chan msg =
asum
[ rule (chatMsg chan) chatRe msg
, rule (actionMsg chan) actionRe msg
, rule (joinMsg chan) joinRe msg
, rule (partMsg chan) partRe msg
, rule quitMsg quitRe msg
, rule nickMsg nickRe msg
, rule (kickMsg chan) kickRe msg
, rule (modeMsg chan) modeRe msg
]
rule ::
Rule r =>
r ->
Regex ->
Text ->
Maybe IrcMsg
rule mk re s =
case map (map Text.pack) (match re (Text.unpack s)) of
[_:xs] -> matchRule xs mk
_ -> Nothing
chatRe, actionRe, joinRe, quitRe, nickRe, partRe, kickRe, modeRe :: Regex
Right chatRe = compRe [str|^<([^>]+)> (.*)$|]
Right actionRe = compRe [str|^\* ([^ ]+) (.*)$|]
Right joinRe = compRe [str|^\*\*\* \[([^]]+)\] ([^ ]+) \(([^@]+)@([^)]+)\) has joined the channel$|]
Right quitRe = compRe [str|^\*\*\* \[([^]]+)\] ([^ ]+) has signed off \((.*)\)$|]
Right nickRe = compRe [str|^\*\*\* \[([^]]+)\] ([^ ]+) changed nick to ([^ ]+)$|]
Right partRe = compRe [str|^\*\*\* \[([^]]+)\] ([^ ]+) has left the channel( \((.*)\))?$|]
Right kickRe = compRe [str|^\*\*\* \[([^]]+)\] ([^ ]+) has been kicked by ([^ ]+) \((.*)\)$|]
Right modeRe = compRe [str|^\*\*\* \[([^]]+)\] ([^ ]+) sets mode (.*)$|]
compRe ::
Text ->
Either String Regex
compRe = compile defaultCompOpt defaultExecOpt . Text.unpack
chatMsg ::
Identifier ->
Text ->
Text ->
IrcMsg
chatMsg chan nick msg =
Privmsg
(userInfo nick)
chan
msg
actionMsg ::
Identifier ->
Text ->
Text ->
IrcMsg
actionMsg chan nick msg =
Ctcp
(userInfo nick)
chan
"ACTION"
msg
joinMsg ::
Identifier ->
Text ->
Text ->
Text ->
Text ->
IrcMsg
joinMsg chan srv nick user host =
Join
(UserInfo (mkId (nick <> "@" <> srv)) user host)
chan
""
partMsg ::
Identifier ->
Text ->
Text ->
Text ->
Text ->
IrcMsg
partMsg chan srv nick msg_outer msg =
Part
(userInfo (nick <> "@" <> srv))
chan
(if Text.null msg_outer then Nothing else Just msg)
quitMsg ::
Text ->
Text ->
Text ->
IrcMsg
quitMsg srv nick msg =
Quit
(userInfo (nick <> "@" <> srv))
(Just msg)
nickMsg ::
Text ->
Text ->
Text ->
IrcMsg
nickMsg srv old new =
Nick
(userInfo (old <> "@" <> srv))
(mkId (new <> "@" <> srv))
kickMsg ::
Identifier ->
Text ->
Text ->
Text ->
Text ->
IrcMsg
kickMsg chan srv kickee kicker reason =
Kick
(userInfo (kicker <> "@" <> srv))
chan
(mkId (kickee <> "@" <> srv))
reason
modeMsg ::
Identifier ->
Text ->
Text ->
Text ->
IrcMsg
modeMsg chan srv nick modes =
Mode
(userInfo (nick <> "@" <> srv))
chan
(Text.words modes)
userInfo ::
Text ->
UserInfo
userInfo nick = UserInfo (mkId nick) "*" "*"
class Rule a where
matchRule :: [Text] -> a -> Maybe IrcMsg
instance (RuleArg a, Rule b) => Rule (a -> b) where
matchRule tts f =
do (t,ts) <- uncons tts
a <- matchArg t
matchRule ts (f a)
instance Rule IrcMsg where
matchRule args ircMsg
| null args = Just ircMsg
| otherwise = Nothing
class RuleArg a where matchArg :: Text -> Maybe a
instance RuleArg Text where matchArg = Just