{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RankNTypes #-}
module Network.Yak.Responses
where
import Control.Lens
import Data.Text (Text)
import Data.Void (Void)
import Data.ByteString.Char8 (ByteString)
import Data.Time.Clock.POSIX
import Network.Yak.Types
import Network.Yak.Modes
import Network.Yak.TH
type Client = Username
type RplWelcome = Msg "001" '[Client, Message]
makeMsgLenses ''RplWelcome ["client", "message"]
type RplYourhost = Msg "002" '[Client, Message]
makeMsgLenses ''RplYourhost ["client", "message"]
type RplCreated = Msg "003" '[Client, Message]
makeMsgLenses ''RplCreated ["client", "message"]
type RplMyinfo = Msg "004" '[Client, Hostname, Text, Modes, Modes, Maybe Modes]
makeMsgLenses ''RplMyinfo ["client", "server", "version", "umodes", "cmodes"
,"cmodesParam"]
type RplIsupport = Msg "005" '[Client, SList Token, Message]
makeMsgLenses ''RplIsupport ["client", "tokens", "message"]
type RplBounce = Msg "010" '[Client, Hostname, Int, Message]
makeMsgLenses ''RplBounce ["client", "hostname", "port", "message"]
type RplUmodeis = Msg "221" '[Client, Modes]
makeMsgLenses ''RplUmodeis ["client", "umodes"]
type RplLuserclient = Msg "251" '[Client, Message]
makeMsgLenses ''RplLuserclient ["client", "message"]
type RplLuserop = Msg "252" '[Client, Int, Message]
makeMsgLenses ''RplLuserop ["client", "ops", "message"]
type RplLuserunknown = Msg "253" '[Client, Int, Message]
makeMsgLenses ''RplLuserunknown ["client", "connections", "message"]
type RplLuserchannels = Msg "254" '[Client, Int, Message]
makeMsgLenses ''RplLuserchannels ["client", "channels", "message"]
type RplLuserme = Msg "255" '[Client, Message]
makeMsgLenses ''RplLuserme ["client", "message"]
type RplAdminme = Msg "256" '[Client, Maybe Hostname, Message]
makeMsgLenses ''RplAdminme ["client", "server", "message"]
type RplAdminemail = Msg "259" '[Client, Message]
makeMsgLenses ''RplAdminemail ["client", "message"]
type RplTryagain = Msg "263" '[Client, Text, Message]
makeMsgLenses ''RplTryagain ["client", "command", "message"]
type RplLocalusers = Msg "265" '[Client, Maybe (Int, Int), Message]
makeMsgLenses ''RplLocalusers ["client", "users", "message"]
rplLocalusersCurrent :: Traversal' RplLocalusers Int
rplLocalusersCurrent = rplLocalusersUsers . _Just . _1
rplLocalusersMaximum :: Traversal' RplLocalusers Int
rplLocalusersMaximum = rplLocalusersUsers . _Just . _2
type RplGlobalusers = Msg "266" '[Client, Maybe (Int, Int), Message]
makeMsgLenses ''RplGlobalusers ["client", "users", "message"]
rplGlobalusersCurrent :: Traversal' RplGlobalusers Int
rplGlobalusersCurrent = rplGlobalusersUsers . _Just . _1
rplGlobalusersMaximum :: Traversal' RplGlobalusers Int
rplGlobalusersMaximum = rplGlobalusersUsers . _Just . _2
type RplWhoiscertfp = Msg "276" '[Client, Nickname, Message]
makeMsgLenses ''RplWhoiscertfp ["client", "nick", "message"]
type RplNone = Msg "300" '[Void]
type RplAway = Msg "301" '[Client, Nickname, Message]
makeMsgLenses ''RplAway ["client", "nick", "message"]
type RplUserhost = Msg "302" '[Client, CList UReply]
makeMsgLenses ''RplUserhost ["client", "replies"]
type RplIson = Msg "303" '[Client, CList Nickname]
makeMsgLenses ''RplIson ["client", "nicks"]
type RplUnaway = Msg "305" '[Client, Message]
makeMsgLenses ''RplUnaway ["client", "message"]
type RplNowaway = Msg "306" '[Client, Message]
makeMsgLenses ''RplNowaway ["client", "message"]
type RplWhoisuser = Msg "311" '[Client, Nickname, Username, Hostname
,Unused "*", Message]
makeMsgLenses ''RplWhoisuser ["client", "nick", "username", "host"
,"unused", "message"]
type RplWhoisserver = Msg "312" '[Client, Nickname, Hostname, Message]
makeMsgLenses ''RplWhoisserver ["client", "nick", "server", "message"]
type RplWhoisoperator = Msg "313" '[Client, Nickname, Message]
makeMsgLenses ''RplWhoisoperator ["client", "nick", "message"]
type RplWhowasuser = Msg "314" '[Client, Nickname, Username, Hostname
,Unused "*", Message]
makeMsgLenses ''RplWhowasuser ["client", "nick", "username", "host"
,"unused", "message"]
type RplWhoisidle = Msg "317" '[Client, Nickname, Int, Maybe POSIXTime, Message]
makeMsgLenses ''RplWhoisidle ["client", "nick", "secs", "signon", "message"]
type RplEndofwhois = Msg "318" '[Client, Nickname, Message]
makeMsgLenses ''RplEndofwhois ["client", "nick", "message"]
type RplWhoischannels = Msg "319" '[Client, Nickname, CList (Member Channel)]
makeMsgLenses ''RplWhoischannels ["client", "nick", "channels"]
type RplListstart = Msg "321" '[Client]
makeMsgLenses ''RplListstart ["client"]
type RplList = Msg "322" '[Client, Channel, Int, Message]
makeMsgLenses ''RplList ["client", "channel", "visibleClients", "message"]
type RplListend = Msg "323" '[Client, Message]
makeMsgLenses ''RplListend ["client", "message"]
type RplChannelmodeis = Msg "324" '[Client, Channel, ByteString]
makeMsgLenses ''RplChannelmodeis ["client", "channel", "rawmode" ]
rplChannelmodeisMode :: ServerModes -> Fold RplChannelmodeis ModeStr
rplChannelmodeisMode m = rplChannelmodeisRawmode . to (fetchModeStr m) . _Just
type RplNotopic = Msg "331" '[Client, Channel, Message]
makeMsgLenses ''RplNotopic ["client", "channel", "message"]
type RplTopic = Msg "332" '[Client, Channel, Message]
makeMsgLenses ''RplTopic ["client", "channel", "message"]
type RplTopictime = Msg "333" '[Client, Channel, Nickname, POSIXTime]
makeMsgLenses ''RplTopictime ["client", "channel", "nick", "setAt"]
type RplInviting = Msg "341" '[Client, Channel, Nickname]
makeMsgLenses ''RplInviting ["client", "channel", "nick"]
type RplInvitelist = Msg "346" '[Client, Channel, Mask]
makeMsgLenses ''RplInvitelist ["client", "channel", "mask"]
type RplEndofinvitelist = Msg "349" '[Client, Channel, Message]
makeMsgLenses ''RplEndofinvitelist ["client", "channel", "message"]
type RplExceptlist = Msg "348" '[Client, Channel, Mask]
makeMsgLenses ''RplExceptlist ["client", "channel", "mask"]
type RplEndofexceptlist = Msg "349" '[Client, Channel, Message]
makeMsgLenses ''RplEndofexceptlist ["client", "channel", "message"]
type RplVersion = Msg "351" '[Client, Text, Hostname, Message]
makeMsgLenses ''RplVersion ["client", "version", "server", "message"]
type RplNamreply = Msg "353" '[Client, Char, Channel, CList (Member Nickname)]
makeMsgLenses ''RplNamreply ["client", "symbol", "channel", "nicks"]
type RplEndofnames = Msg "366" '[Client, Channel, Message]
makeMsgLenses ''RplEndofnames ["client", "channel", "message"]
type RplBanlist = Msg "367" '[Client, Channel, Mask]
makeMsgLenses ''RplBanlist ["client", "channel", "mask"]
type RplEndofbanlist = Msg "368" '[Client, Channel, Message]
makeMsgLenses ''RplEndofbanlist ["client", "channel", "message"]
type RplEndofwhowas = Msg "369" '[Client, Nickname, Message]
makeMsgLenses ''RplEndofwhowas ["client", "nick", "message"]
type RplMotdstart = Msg "375" '[Client, Unused ":-", Hostname]
makeMsgLenses ''RplMotdstart ["client", "unused", "server"]
type RplMotd = Msg "372" '[Client, Message]
makeMsgLenses ''RplMotd ["client", "message"]
type RplEndofmotd = Msg "376" '[Client, Message]
makeMsgLenses ''RplEndofmotd ["client", "message"]
type RplYoureoper = Msg "381" '[Client, Message]
makeMsgLenses ''RplYoureoper ["client", "message"]
type RplRehashing = Msg "382" '[Client, Text, Message]
makeMsgLenses ''RplRehashing ["client", "configFile", "message"]
type ErrUnknownerror = Msg "400" '[Client, SList Text, Message]
makeMsgLenses ''ErrUnknownerror ["client", "commands", "message"]
type ErrNosuchnick = Msg "401" '[Client, Nickname, Message]
makeMsgLenses ''ErrNosuchnick ["client", "nickname", "message"]
type ErrNosuchserver = Msg "402" '[Client, Hostname, Message]
makeMsgLenses ''ErrNosuchserver ["client", "server", "message"]
type ErrNosuchchannel = Msg "403" '[Client, Channel, Message]
makeMsgLenses ''ErrNosuchchannel ["client", "channel", "message"]
type ErrCannotsendtochan = Msg "404" '[Client, Channel, Message]
makeMsgLenses ''ErrCannotsendtochan ["client", "channel", "message"]
type ErrToomanychannels = Msg "405" '[Client, Channel, Message]
makeMsgLenses ''ErrToomanychannels ["client", "channel", "message"]
type ErrUnknowncommand = Msg "421" '[Client, Text, Message]
makeMsgLenses ''ErrUnknowncommand ["client", "command", "message"]
type ErrNomotd = Msg "422" '[Client, Message]
makeMsgLenses ''ErrNomotd ["client", "message"]
type ErrErroneusnickname = Msg "432" '[Client, Nickname, Message]
makeMsgLenses ''ErrErroneusnickname ["client", "nick", "message"]
type ErrNicknameinuse = Msg "433" '[Client, Nickname, Message]
makeMsgLenses ''ErrNicknameinuse ["client", "nick", "message"]
type ErrNotregistered = Msg "451" '[Client, Message]
makeMsgLenses ''ErrNotregistered ["client", "message"]
type ErrNeedmoreparams = Msg "461" '[Client, Text, Message]
makeMsgLenses ''ErrNeedmoreparams ["client", "command", "message"]
type ErrAlreadyregistered = Msg "462" '[Client, Message]
makeMsgLenses ''ErrAlreadyregistered ["client", "message"]
type ErrPasswdmismatch = Msg "464" '[Client, Message]
makeMsgLenses ''ErrPasswdmismatch ["client", "message"]
type ErrYourebannedcreep = Msg "465" '[Client, Message]
makeMsgLenses ''ErrYourebannedcreep ["client", "message"]
type ErrChannelisfull = Msg "471" '[Client, Channel, Message]
makeMsgLenses ''ErrChannelisfull ["client", "channel", "message"]
type ErrUnknownmode = Msg "472" '[Client, Char, Message]
makeMsgLenses ''ErrUnknownmode ["client", "modeChar", "message"]
type ErrInviteonlychan = Msg "473" '[Client, Channel, Message]
makeMsgLenses ''ErrInviteonlychan ["client", "channel", "message"]
type ErrBannedfromchan = Msg "474" '[Client, Channel, Message]
makeMsgLenses ''ErrBannedfromchan ["client", "channel", "message"]
type ErrBadchannelkey = Msg "475" '[Client, Channel, Message]
makeMsgLenses ''ErrBadchannelkey ["client", "channel", "message"]
type ErrNoprivileges = Msg "481" '[Client, Message]
makeMsgLenses ''ErrNoprivileges ["client", "message"]
type ErrChanoprivsneeded = Msg "482" '[Client, Channel, Message]
makeMsgLenses ''ErrChanoprivsneeded ["client", "channel", "message"]
type ErrCantkillserver = Msg "483" '[Client, Message]
makeMsgLenses ''ErrCantkillserver ["client", "message"]
type ErrNooperhost = Msg "491" '[Client, Message]
makeMsgLenses ''ErrNooperhost ["client", "message"]
type ErrUmodeunknownflag = Msg "501" '[Client, Message]
makeMsgLenses ''ErrUmodeunknownflag ["client", "message"]
type ErrUsersdontmatch = Msg "502" '[Client, Message]
makeMsgLenses ''ErrUsersdontmatch ["client", "message"]
type RplStarttls = Msg "670" '[Client, Message]
makeMsgLenses ''RplStarttls ["client", "message"]
type ErrStarttls = Msg "691" '[Client, Message]
makeMsgLenses ''ErrStarttls ["client", "message"]
type ErrNoprivs = Msg "723" '[Client, Text, Message]
makeMsgLenses ''ErrNoprivs ["client", "priv", "message"]
type RplLoggedin = Msg "900" '[Client, Host, Text, Message]
makeMsgLenses ''RplLoggedin ["client", "host", "account", "message"]
type RplLoggedout = Msg "901" '[Client, Host, Message]
makeMsgLenses ''RplLoggedout ["client", "host", "message"]
type ErrNicklocked = Msg "902" '[Client, Message]
makeMsgLenses ''ErrNicklocked ["client", "message"]
type RplSaslsuccess = Msg "903" '[Client, Message]
makeMsgLenses ''RplSaslsuccess ["client", "message"]
type ErrSaslfail = Msg "904" '[Client, Message]
makeMsgLenses ''ErrSaslfail ["client", "message"]
type ErrSasltoolong = Msg "905" '[Client, Message]
makeMsgLenses ''ErrSasltoolong ["client", "message"]
type ErrSaslaborted = Msg "906" '[Client, Message]
makeMsgLenses ''ErrSaslaborted ["client", "message"]
type ErrSaslalready = Msg "907" '[Client, Message]
makeMsgLenses ''ErrSaslalready ["client", "message"]
type RplSaslmechs = Msg "908" '[Client, [Text], Message]
makeMsgLenses ''RplSaslmechs ["client", "mechanisms", "message"]