-- | Datatypes for representing IRC messages, as well as formatting them.
module Network.IRC.Base (
    -- * Type Synonyms
    Parameter
  , ServerName
  , UserName
  , RealName
  , Command

    -- * IRC Datatypes
  , Prefix(..)
  , Message(..)

    -- * Formatting functions
  , encode         -- :: Message -> String
  , showMessage, showPrefix, showParameters
  , translateReply -- :: String -> String
  , replyTable     -- :: [(String,String)]

    -- * Deprecated
  , render
  ) where

import Data.Maybe
import Data.Char
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as B8

-- ---------------------------------------------------------
-- Data Types

type Parameter  = ByteString
type ServerName = ByteString
type UserName   = ByteString
type RealName   = ByteString
type Command    = ByteString


-- | IRC messages are parsed as:
--   [ ':' prefix space ] command { space param } crlf
data Message = Message 
  { Message -> Maybe Prefix
msg_prefix  :: Maybe Prefix
  , Message -> Command
msg_command :: Command
  , Message -> [Command]
msg_params  :: [Parameter]
  } deriving (Int -> Message -> ShowS
[Message] -> ShowS
Message -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Message] -> ShowS
$cshowList :: [Message] -> ShowS
show :: Message -> String
$cshow :: Message -> String
showsPrec :: Int -> Message -> ShowS
$cshowsPrec :: Int -> Message -> ShowS
Show,ReadPrec [Message]
ReadPrec Message
Int -> ReadS Message
ReadS [Message]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Message]
$creadListPrec :: ReadPrec [Message]
readPrec :: ReadPrec Message
$creadPrec :: ReadPrec Message
readList :: ReadS [Message]
$creadList :: ReadS [Message]
readsPrec :: Int -> ReadS Message
$creadsPrec :: Int -> ReadS Message
Read,Message -> Message -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Message -> Message -> Bool
$c/= :: Message -> Message -> Bool
== :: Message -> Message -> Bool
$c== :: Message -> Message -> Bool
Eq)


-- | The optional beginning of an IRC messages
data Prefix
  = -- | Server Prefix
    Server ServerName
  | -- | Nickname Prefix
    NickName ByteString (Maybe UserName) (Maybe ServerName)
    deriving (Int -> Prefix -> ShowS
[Prefix] -> ShowS
Prefix -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Prefix] -> ShowS
$cshowList :: [Prefix] -> ShowS
show :: Prefix -> String
$cshow :: Prefix -> String
showsPrec :: Int -> Prefix -> ShowS
$cshowsPrec :: Int -> Prefix -> ShowS
Show,ReadPrec [Prefix]
ReadPrec Prefix
Int -> ReadS Prefix
ReadS [Prefix]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Prefix]
$creadListPrec :: ReadPrec [Prefix]
readPrec :: ReadPrec Prefix
$creadPrec :: ReadPrec Prefix
readList :: ReadS [Prefix]
$creadList :: ReadS [Prefix]
readsPrec :: Int -> ReadS Prefix
$creadsPrec :: Int -> ReadS Prefix
Read,Prefix -> Prefix -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Prefix -> Prefix -> Bool
$c/= :: Prefix -> Prefix -> Bool
== :: Prefix -> Prefix -> Bool
$c== :: Prefix -> Prefix -> Bool
Eq)


-- ---------------------------------------------------------
-- Formatting


-- | Encode a message to its string representation
encode :: Message -> ByteString
encode :: Message -> Command
encode = Message -> Command
showMessage

-- | This is the deprecated version of encode
render :: Message -> ByteString
render :: Message -> Command
render  = Message -> Command
encode

showMessage :: Message -> ByteString
showMessage :: Message -> Command
showMessage (Message Maybe Prefix
p Command
c [Command]
ps) = Maybe Prefix -> Command
showMaybe Maybe Prefix
p Command -> Command -> Command
`BS.append` Command
c Command -> Command -> Command
`BS.append` [Command] -> Command
showParameters [Command]
ps
  where showMaybe :: Maybe Prefix -> Command
showMaybe Maybe Prefix
Nothing = Command
BS.empty
        showMaybe (Just Prefix
prefix) = [Command] -> Command
BS.concat [ String -> Command
B8.pack String
":"
                                            , Prefix -> Command
showPrefix Prefix
prefix
                                            , String -> Command
B8.pack String
" " ]

bsConsAscii :: Char -> ByteString -> ByteString
bsConsAscii :: Char -> Command -> Command
bsConsAscii Char
c = Word8 -> Command -> Command
BS.cons (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord forall a b. (a -> b) -> a -> b
$ Char
c)

showPrefix :: Prefix -> ByteString
showPrefix :: Prefix -> Command
showPrefix (Server Command
s)       = Command
s
showPrefix (NickName Command
n Maybe Command
u Maybe Command
h) = [Command] -> Command
BS.concat [Command
n, Char -> Maybe Command -> Command
showMaybe Char
'!' Maybe Command
u, Char -> Maybe Command -> Command
showMaybe Char
'@' Maybe Command
h]
  where showMaybe :: Char -> Maybe Command -> Command
showMaybe Char
c Maybe Command
e = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Command
BS.empty (Char -> Command -> Command
bsConsAscii Char
c) Maybe Command
e

showParameters :: [Parameter] -> ByteString
showParameters :: [Command] -> Command
showParameters []     = Command
BS.empty
showParameters [Command]
params = Command -> [Command] -> Command
BS.intercalate (String -> Command
B8.pack String
" ") (Command
BS.empty forall a. a -> [a] -> [a]
: [Command] -> [Command]
showp [Command]
params)
  where showp :: [Command] -> [Command]
showp [Command
p]    = [Char -> Command -> Command
bsConsAscii Char
':' Command
p]
        showp (Command
p:[Command]
ps) = Command
p forall a. a -> [a] -> [a]
: [Command] -> [Command]
showp [Command]
ps
        showp []     = []

-- ---------------------------------------------------------
-- Message Translation

-- | Translate a reply into its text description.
--   If no text is available, the argument is returned.
translateReply :: Command -- ^ Reply
               -> ByteString  -- ^ Text translation
translateReply :: Command -> Command
translateReply Command
r = forall a. a -> Maybe a -> a
fromMaybe Command
r forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Command
r [(Command, Command)]
replyTable


-- One big lookup table of codes and errors
replyTable :: [(ByteString, ByteString)]
replyTable :: [(Command, Command)]
replyTable  = forall a b. (a -> b) -> [a] -> [b]
map (String, String) -> (Command, Command)
mkPair
  [ (String
"401",String
"ERR_NOSUCHNICK")
  , (String
"402",String
"ERR_NOSUCHSERVER")
  , (String
"403",String
"ERR_NOSUCHCHANNEL")
  , (String
"404",String
"ERR_CANNOTSENDTOCHAN")
  , (String
"405",String
"ERR_TOOMANYCHANNELS")
  , (String
"406",String
"ERR_WASNOSUCHNICK")
  , (String
"407",String
"ERR_TOOMANYTARGETS")
  , (String
"409",String
"ERR_NOORIGIN")
  , (String
"411",String
"ERR_NORECIPIENT")
  , (String
"412",String
"ERR_NOTEXTTOSEND")
  , (String
"413",String
"ERR_NOTOPLEVEL")
  , (String
"414",String
"ERR_WILDTOPLEVEL")
  , (String
"421",String
"ERR_UNKNOWNCOMMAND")
  , (String
"422",String
"ERR_NOMOTD")
  , (String
"423",String
"ERR_NOADMININFO")
  , (String
"424",String
"ERR_FILEERROR")
  , (String
"431",String
"ERR_NONICKNAMEGIVEN")
  , (String
"432",String
"ERR_ERRONEUSNICKNAME")
  , (String
"433",String
"ERR_NICKNAMEINUSE")
  , (String
"436",String
"ERR_NICKCOLLISION")
  , (String
"441",String
"ERR_USERNOTINCHANNEL")
  , (String
"442",String
"ERR_NOTONCHANNEL")
  , (String
"443",String
"ERR_USERONCHANNEL")
  , (String
"444",String
"ERR_NOLOGIN")
  , (String
"445",String
"ERR_SUMMONDISABLED")
  , (String
"446",String
"ERR_USERSDISABLED")
  , (String
"451",String
"ERR_NOTREGISTERED")
  , (String
"461",String
"ERR_NEEDMOREPARAMS")
  , (String
"462",String
"ERR_ALREADYREGISTRED")
  , (String
"463",String
"ERR_NOPERMFORHOST")
  , (String
"464",String
"ERR_PASSWDMISMATCH")
  , (String
"465",String
"ERR_YOUREBANNEDCREEP")
  , (String
"467",String
"ERR_KEYSET")
  , (String
"471",String
"ERR_CHANNELISFULL")
  , (String
"472",String
"ERR_UNKNOWNMODE")
  , (String
"473",String
"ERR_INVITEONLYCHAN")
  , (String
"474",String
"ERR_BANNEDFROMCHAN")
  , (String
"475",String
"ERR_BADCHANNELKEY")
  , (String
"481",String
"ERR_NOPRIVILEGES")
  , (String
"482",String
"ERR_CHANOPRIVSNEEDED")
  , (String
"483",String
"ERR_CANTKILLSERVER")
  , (String
"491",String
"ERR_NOOPERHOST")
  , (String
"501",String
"ERR_UMODEUNKNOWNFLAG")
  , (String
"502",String
"ERR_USERSDONTMATCH")
  , (String
"300",String
"RPL_NONE")
  , (String
"302",String
"RPL_USERHOST")
  , (String
"303",String
"RPL_ISON")
  , (String
"301",String
"RPL_AWAY")
  , (String
"305",String
"RPL_UNAWAY")
  , (String
"306",String
"RPL_NOWAWAY")
  , (String
"311",String
"RPL_WHOISUSER")
  , (String
"312",String
"RPL_WHOISSERVER")
  , (String
"313",String
"RPL_WHOISOPERATOR")
  , (String
"317",String
"RPL_WHOISIDLE")
  , (String
"318",String
"RPL_ENDOFWHOIS")
  , (String
"319",String
"RPL_WHOISCHANNELS")
  , (String
"314",String
"RPL_WHOWASUSER")
  , (String
"369",String
"RPL_ENDOFWHOWAS")
  , (String
"321",String
"RPL_LISTSTART")
  , (String
"322",String
"RPL_LIST")
  , (String
"323",String
"RPL_LISTEND")
  , (String
"324",String
"RPL_CHANNELMODEIS")
  , (String
"331",String
"RPL_NOTOPIC")
  , (String
"332",String
"RPL_TOPIC")
  , (String
"341",String
"RPL_INVITING")
  , (String
"342",String
"RPL_SUMMONING")
  , (String
"351",String
"RPL_VERSION")
  , (String
"352",String
"RPL_WHOREPLY")
  , (String
"315",String
"RPL_ENDOFWHO")
  , (String
"353",String
"RPL_NAMREPLY")
  , (String
"366",String
"RPL_ENDOFNAMES")
  , (String
"364",String
"RPL_LINKS")
  , (String
"365",String
"RPL_ENDOFLINKS")
  , (String
"367",String
"RPL_BANLIST")
  , (String
"368",String
"RPL_ENDOFBANLIST")
  , (String
"371",String
"RPL_INFO")
  , (String
"374",String
"RPL_ENDOFINFO")
  , (String
"375",String
"RPL_MOTDSTART")
  , (String
"372",String
"RPL_MOTD")
  , (String
"376",String
"RPL_ENDOFMOTD")
  , (String
"381",String
"RPL_YOUREOPER")
  , (String
"382",String
"RPL_REHASHING")
  , (String
"391",String
"RPL_TIME")
  , (String
"392",String
"RPL_USERSSTART")
  , (String
"393",String
"RPL_USERS")
  , (String
"394",String
"RPL_ENDOFUSERS")
  , (String
"395",String
"RPL_NOUSERS")
  , (String
"200",String
"RPL_TRACELINK")
  , (String
"201",String
"RPL_TRACECONNECTING")
  , (String
"202",String
"RPL_TRACEHANDSHAKE")
  , (String
"203",String
"RPL_TRACEUNKNOWN")
  , (String
"204",String
"RPL_TRACEOPERATOR")
  , (String
"205",String
"RPL_TRACEUSER")
  , (String
"206",String
"RPL_TRACESERVER")
  , (String
"208",String
"RPL_TRACENEWTYPE")
  , (String
"261",String
"RPL_TRACELOG")
  , (String
"211",String
"RPL_STATSLINKINFO")
  , (String
"212",String
"RPL_STATSCOMMANDS")
  , (String
"213",String
"RPL_STATSCLINE")
  , (String
"214",String
"RPL_STATSNLINE")
  , (String
"215",String
"RPL_STATSILINE")
  , (String
"216",String
"RPL_STATSKLINE")
  , (String
"218",String
"RPL_STATSYLINE")
  , (String
"219",String
"RPL_ENDOFSTATS")
  , (String
"241",String
"RPL_STATSLLINE")
  , (String
"242",String
"RPL_STATSUPTIME")
  , (String
"243",String
"RPL_STATSOLINE")
  , (String
"244",String
"RPL_STATSHLINE")
  , (String
"221",String
"RPL_UMODEIS")
  , (String
"251",String
"RPL_LUSERCLIENT")
  , (String
"252",String
"RPL_LUSEROP")
  , (String
"253",String
"RPL_LUSERUNKNOWN")
  , (String
"254",String
"RPL_LUSERCHANNELS")
  , (String
"255",String
"RPL_LUSERME")
  , (String
"256",String
"RPL_ADMINME")
  , (String
"257",String
"RPL_ADMINLOC1")
  , (String
"258",String
"RPL_ADMINLOC2")
  , (String
"259",String
"RPL_ADMINEMAIL")
  ]
  where
  mkPair :: (String, String) -> (Command, Command)
mkPair (String
a,String
b) = (String -> Command
B8.pack String
a, String -> Command
B8.pack String
b)