module Network.IRC.Conduit.Internal.Messages where
import Control.Applicative ((<$>))
import Data.ByteString (ByteString, singleton, unpack)
import Data.Char (ord)
import Data.Maybe (listToMaybe, isJust)
import Data.Monoid ((<>))
import Data.String (fromString)
import Network.IRC.CTCP (CTCPByteString, getUnderlyingByteString, orCTCP)
import Text.Read (readMaybe)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import qualified Network.IRC as I
type ChannelName a = a
type NickName a = a
type ServerName a = a
type Reason a = Maybe a
type IsModeSet = Bool
type ModeFlag a = a
type ModeArg a = a
type NumericArg a = a
type Target a = a
type IrcEvent = Event ByteString
type IrcSource = Source ByteString
type IrcMessage = Message ByteString
data Event a = Event
{ _raw :: ByteString
, _source :: Source a
, _message :: Message a
}
deriving (Eq, Functor, Show)
data Source a = User (NickName a)
| Channel (ChannelName a) (NickName a)
| Server (ServerName a)
deriving (Eq, Functor, Show)
data Message a = Privmsg (Target a) (Either CTCPByteString a)
| Notice (Target a) (Either CTCPByteString a)
| Nick (NickName a)
| Join (ChannelName a)
| Part (ChannelName a) (Reason a)
| Quit (Reason a)
| Mode (Target a) IsModeSet [ModeFlag a] [ModeArg a]
| Topic (ChannelName a) a
| Invite (ChannelName a) (NickName a)
| Kick (ChannelName a) (NickName a) (Reason a)
| Ping (ServerName a) (Maybe (ServerName a))
| Pong (ServerName a)
| Numeric Int [NumericArg a]
| RawMsg a
deriving (Eq, Functor, Show)
fromByteString :: ByteString -> Either ByteString IrcEvent
fromByteString bs = maybe (Left bs) Right $ uncurry (Event bs) <$> attemptDecode bs
attemptDecode :: ByteString -> Maybe (IrcSource, IrcMessage)
attemptDecode bs = I.decode bs >>= decode'
where
decode' msg = case msg of
I.Message (Just (I.NickName n _ _)) "PRIVMSG" [t, m] | isChan t -> Just (Channel t n, privmsg t m)
| otherwise -> Just (User n, privmsg t m)
I.Message (Just (I.NickName n _ _)) "NOTICE" [t, m] | isChan t -> Just (Channel t n, notice t m)
| otherwise -> Just (User n, notice t m)
I.Message (Just (I.NickName n _ _)) "NICK" [n'] -> Just (User n, Nick n')
I.Message (Just (I.NickName n _ _)) "JOIN" [c] -> Just (Channel c n, Join c)
I.Message (Just (I.NickName n _ _)) "PART" (c:r) -> Just (Channel c n, Part c $ listToMaybe r)
I.Message (Just (I.NickName n _ _)) "QUIT" r -> Just (User n, Quit $ listToMaybe r)
I.Message (Just (I.NickName n _ _)) "KICK" (c:u:r) -> Just (Channel c n, Kick c u $ listToMaybe r)
I.Message (Just (I.NickName n _ _)) "INVITE" [_, c] -> Just (User n, Invite c n)
I.Message (Just (I.NickName n _ _)) "TOPIC" [c, t] -> Just (Channel c n, Topic c t)
I.Message (Just (I.NickName n _ _)) "MODE" (t:fs:as) | n == t -> (User n,) <$> mode t fs as
| otherwise -> (Channel t n,) <$> mode t fs as
I.Message (Just (I.Server s)) "PING" (s1:s2) -> Just (Server s, Ping s1 $ listToMaybe s2)
I.Message Nothing "PING" (s1:s2) -> Just (Server s1, Ping s1 $ listToMaybe s2)
I.Message (Just (I.Server s)) n args | isNumeric n -> (Server s,) <$> numeric n args
_ -> Nothing
isChan t = B.take 1 t `elem` ["#", "&", "+", "!"]
privmsg t = Privmsg t . (Right `orCTCP` Left)
notice t = Notice t . (Right `orCTCP` Left)
mode t fs as = case unpack fs of
(f:fs') | f == fromIntegral (ord '+') -> Just $ Mode t True (map singleton fs') as
| f == fromIntegral (ord '-') -> Just $ Mode t False (map singleton fs') as
_ -> Nothing
isNumeric = isJust . (readMaybe :: String -> Maybe Int) . B8.unpack
numeric n args = flip Numeric args <$> readMaybe (B8.unpack n)
toByteString :: IrcMessage -> ByteString
toByteString (Privmsg t (Left ctcpbs)) = mkMessage "PRIVMSG" [t, getUnderlyingByteString ctcpbs]
toByteString (Privmsg t (Right bs)) = mkMessage "PRIVMSG" [t, bs]
toByteString (Notice t (Left ctcpbs)) = mkMessage "NOTICE" [t, getUnderlyingByteString ctcpbs]
toByteString (Notice t (Right bs)) = mkMessage "NOTICE" [t, bs]
toByteString (Nick n) = mkMessage "NICK" [n]
toByteString (Join c) = mkMessage "JOIN" [c]
toByteString (Part c (Just r)) = mkMessage "PART" [c, r]
toByteString (Part c Nothing) = mkMessage "PART" [c]
toByteString (Quit (Just r)) = mkMessage "QUIT" [r]
toByteString (Quit Nothing) = mkMessage "QUIT" []
toByteString (Mode t True ms as) = mkMessage "MODE" $ t : ("+" <> B.concat ms) : as
toByteString (Mode t False ms as) = mkMessage "MODE" $ t : ("-" <> B.concat ms) : as
toByteString (Invite c n) = mkMessage "INVITE" [c, n]
toByteString (Topic c bs) = mkMessage "TOPIC" [c, bs]
toByteString (Kick c n (Just r)) = mkMessage "KICK" [c, n, r]
toByteString (Kick c n Nothing) = mkMessage "KICK" [c, n]
toByteString (Ping s1 (Just s2)) = mkMessage "PING" [s1, s2]
toByteString (Ping s1 Nothing) = mkMessage "PING" [s1]
toByteString (Pong s) = mkMessage "PONG" [s]
toByteString (Numeric n as) = mkMessage (fromString $ show n) as
toByteString (RawMsg bs) = bs
mkMessage :: ByteString -> [ByteString] -> ByteString
mkMessage cmd = I.encode . I.Message Nothing cmd
rawMessage :: ByteString
-> [ByteString]
-> IrcMessage
rawMessage cmd = RawMsg . mkMessage cmd