{-# Language PatternSynonyms, OverloadedStrings #-}
{-# OPTIONS_GHC -Wno-missing-pattern-synonym-signatures #-}
module Irc.Codes where
import Data.Vector (Vector)
import qualified Data.Vector as Vector
import Data.Text (Text)
import qualified Data.Text as Text
newtype ReplyCode = ReplyCode Word
deriving (ReplyCode -> ReplyCode -> Bool
(ReplyCode -> ReplyCode -> Bool)
-> (ReplyCode -> ReplyCode -> Bool) -> Eq ReplyCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReplyCode -> ReplyCode -> Bool
$c/= :: ReplyCode -> ReplyCode -> Bool
== :: ReplyCode -> ReplyCode -> Bool
$c== :: ReplyCode -> ReplyCode -> Bool
Eq, Eq ReplyCode
Eq ReplyCode
-> (ReplyCode -> ReplyCode -> Ordering)
-> (ReplyCode -> ReplyCode -> Bool)
-> (ReplyCode -> ReplyCode -> Bool)
-> (ReplyCode -> ReplyCode -> Bool)
-> (ReplyCode -> ReplyCode -> Bool)
-> (ReplyCode -> ReplyCode -> ReplyCode)
-> (ReplyCode -> ReplyCode -> ReplyCode)
-> Ord ReplyCode
ReplyCode -> ReplyCode -> Bool
ReplyCode -> ReplyCode -> Ordering
ReplyCode -> ReplyCode -> ReplyCode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReplyCode -> ReplyCode -> ReplyCode
$cmin :: ReplyCode -> ReplyCode -> ReplyCode
max :: ReplyCode -> ReplyCode -> ReplyCode
$cmax :: ReplyCode -> ReplyCode -> ReplyCode
>= :: ReplyCode -> ReplyCode -> Bool
$c>= :: ReplyCode -> ReplyCode -> Bool
> :: ReplyCode -> ReplyCode -> Bool
$c> :: ReplyCode -> ReplyCode -> Bool
<= :: ReplyCode -> ReplyCode -> Bool
$c<= :: ReplyCode -> ReplyCode -> Bool
< :: ReplyCode -> ReplyCode -> Bool
$c< :: ReplyCode -> ReplyCode -> Bool
compare :: ReplyCode -> ReplyCode -> Ordering
$ccompare :: ReplyCode -> ReplyCode -> Ordering
$cp1Ord :: Eq ReplyCode
Ord)
instance Show ReplyCode where
showsPrec :: Int -> ReplyCode -> ShowS
showsPrec Int
p (ReplyCode Word
x) = Int -> Word -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p Word
x
instance Read ReplyCode where
readsPrec :: Int -> ReadS ReplyCode
readsPrec Int
p String
str = [ (Word -> ReplyCode
ReplyCode Word
x, String
xs) | (Word
x,String
xs) <- Int -> ReadS Word
forall a. Read a => Int -> ReadS a
readsPrec Int
p String
str ]
data ReplyType
= ClientServerReply
| CommandReply
| ErrorReply
| UnknownReply
deriving (ReplyType -> ReplyType -> Bool
(ReplyType -> ReplyType -> Bool)
-> (ReplyType -> ReplyType -> Bool) -> Eq ReplyType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReplyType -> ReplyType -> Bool
$c/= :: ReplyType -> ReplyType -> Bool
== :: ReplyType -> ReplyType -> Bool
$c== :: ReplyType -> ReplyType -> Bool
Eq, Eq ReplyType
Eq ReplyType
-> (ReplyType -> ReplyType -> Ordering)
-> (ReplyType -> ReplyType -> Bool)
-> (ReplyType -> ReplyType -> Bool)
-> (ReplyType -> ReplyType -> Bool)
-> (ReplyType -> ReplyType -> Bool)
-> (ReplyType -> ReplyType -> ReplyType)
-> (ReplyType -> ReplyType -> ReplyType)
-> Ord ReplyType
ReplyType -> ReplyType -> Bool
ReplyType -> ReplyType -> Ordering
ReplyType -> ReplyType -> ReplyType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReplyType -> ReplyType -> ReplyType
$cmin :: ReplyType -> ReplyType -> ReplyType
max :: ReplyType -> ReplyType -> ReplyType
$cmax :: ReplyType -> ReplyType -> ReplyType
>= :: ReplyType -> ReplyType -> Bool
$c>= :: ReplyType -> ReplyType -> Bool
> :: ReplyType -> ReplyType -> Bool
$c> :: ReplyType -> ReplyType -> Bool
<= :: ReplyType -> ReplyType -> Bool
$c<= :: ReplyType -> ReplyType -> Bool
< :: ReplyType -> ReplyType -> Bool
$c< :: ReplyType -> ReplyType -> Bool
compare :: ReplyType -> ReplyType -> Ordering
$ccompare :: ReplyType -> ReplyType -> Ordering
$cp1Ord :: Eq ReplyType
Ord, ReadPrec [ReplyType]
ReadPrec ReplyType
Int -> ReadS ReplyType
ReadS [ReplyType]
(Int -> ReadS ReplyType)
-> ReadS [ReplyType]
-> ReadPrec ReplyType
-> ReadPrec [ReplyType]
-> Read ReplyType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReplyType]
$creadListPrec :: ReadPrec [ReplyType]
readPrec :: ReadPrec ReplyType
$creadPrec :: ReadPrec ReplyType
readList :: ReadS [ReplyType]
$creadList :: ReadS [ReplyType]
readsPrec :: Int -> ReadS ReplyType
$creadsPrec :: Int -> ReadS ReplyType
Read, Int -> ReplyType -> ShowS
[ReplyType] -> ShowS
ReplyType -> String
(Int -> ReplyType -> ShowS)
-> (ReplyType -> String)
-> ([ReplyType] -> ShowS)
-> Show ReplyType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplyType] -> ShowS
$cshowList :: [ReplyType] -> ShowS
show :: ReplyType -> String
$cshow :: ReplyType -> String
showsPrec :: Int -> ReplyType -> ShowS
$cshowsPrec :: Int -> ReplyType -> ShowS
Show)
pattern $bRPL_WELCOME :: ReplyCode
$mRPL_WELCOME :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WELCOME = ReplyCode 001
pattern $bRPL_YOURHOST :: ReplyCode
$mRPL_YOURHOST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_YOURHOST = ReplyCode 002
pattern $bRPL_CREATED :: ReplyCode
$mRPL_CREATED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_CREATED = ReplyCode 003
pattern $bRPL_MYINFO :: ReplyCode
$mRPL_MYINFO :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_MYINFO = ReplyCode 004
pattern $bRPL_ISUPPORT :: ReplyCode
$mRPL_ISUPPORT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ISUPPORT = ReplyCode 005
pattern $bRPL_SNOMASK :: ReplyCode
$mRPL_SNOMASK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SNOMASK = ReplyCode 008
pattern $bRPL_STATMEMTOT :: ReplyCode
$mRPL_STATMEMTOT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATMEMTOT = ReplyCode 009
pattern $bRPL_REDIR :: ReplyCode
$mRPL_REDIR :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_REDIR = ReplyCode 010
pattern $bRPL_YOURCOOKIE :: ReplyCode
$mRPL_YOURCOOKIE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_YOURCOOKIE = ReplyCode 014
pattern $bRPL_MAP :: ReplyCode
$mRPL_MAP :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_MAP = ReplyCode 015
pattern $bRPL_MAPEND :: ReplyCode
$mRPL_MAPEND :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_MAPEND = ReplyCode 017
pattern $bRPL_YOURID :: ReplyCode
$mRPL_YOURID :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_YOURID = ReplyCode 042
pattern $bRPL_SAVENICK :: ReplyCode
$mRPL_SAVENICK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SAVENICK = ReplyCode 043
pattern $bRPL_ATTEMPTINGJUNC :: ReplyCode
$mRPL_ATTEMPTINGJUNC :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ATTEMPTINGJUNC = ReplyCode 050
pattern $bRPL_ATTEMPTINGREROUTE :: ReplyCode
$mRPL_ATTEMPTINGREROUTE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ATTEMPTINGREROUTE = ReplyCode 051
pattern $bRPL_REMOTESUPPORT :: ReplyCode
$mRPL_REMOTESUPPORT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_REMOTESUPPORT = ReplyCode 105
pattern $bRPL_TRACELINK :: ReplyCode
$mRPL_TRACELINK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACELINK = ReplyCode 200
pattern $bRPL_TRACECONNECTING :: ReplyCode
$mRPL_TRACECONNECTING :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACECONNECTING = ReplyCode 201
pattern $bRPL_TRACEHANDSHAKE :: ReplyCode
$mRPL_TRACEHANDSHAKE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACEHANDSHAKE = ReplyCode 202
pattern $bRPL_TRACEUNKNOWN :: ReplyCode
$mRPL_TRACEUNKNOWN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACEUNKNOWN = ReplyCode 203
pattern $bRPL_TRACEOPERATOR :: ReplyCode
$mRPL_TRACEOPERATOR :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACEOPERATOR = ReplyCode 204
pattern $bRPL_TRACEUSER :: ReplyCode
$mRPL_TRACEUSER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACEUSER = ReplyCode 205
pattern $bRPL_TRACESERVER :: ReplyCode
$mRPL_TRACESERVER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACESERVER = ReplyCode 206
pattern $bRPL_TRACESERVICE :: ReplyCode
$mRPL_TRACESERVICE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACESERVICE = ReplyCode 207
pattern $bRPL_TRACENEWTYPE :: ReplyCode
$mRPL_TRACENEWTYPE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACENEWTYPE = ReplyCode 208
pattern $bRPL_TRACECLASS :: ReplyCode
$mRPL_TRACECLASS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACECLASS = ReplyCode 209
pattern $bRPL_TRACERECONNECT :: ReplyCode
$mRPL_TRACERECONNECT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACERECONNECT = ReplyCode 210
pattern $bRPL_STATS :: ReplyCode
$mRPL_STATS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATS = ReplyCode 210
pattern $bRPL_STATSLINKINFO :: ReplyCode
$mRPL_STATSLINKINFO :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSLINKINFO = ReplyCode 211
pattern $bRPL_STATSCOMMANDS :: ReplyCode
$mRPL_STATSCOMMANDS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSCOMMANDS = ReplyCode 212
pattern $bRPL_STATSCLINE :: ReplyCode
$mRPL_STATSCLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSCLINE = ReplyCode 213
pattern $bRPL_STATSNLINE :: ReplyCode
$mRPL_STATSNLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSNLINE = ReplyCode 214
pattern $bRPL_STATSILINE :: ReplyCode
$mRPL_STATSILINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSILINE = ReplyCode 215
pattern $bRPL_STATSKLINE :: ReplyCode
$mRPL_STATSKLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSKLINE = ReplyCode 216
pattern $bRPL_STATSQLINE :: ReplyCode
$mRPL_STATSQLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSQLINE = ReplyCode 217
pattern $bRPL_STATSYLINE :: ReplyCode
$mRPL_STATSYLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSYLINE = ReplyCode 218
pattern $bRPL_ENDOFSTATS :: ReplyCode
$mRPL_ENDOFSTATS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFSTATS = ReplyCode 219
pattern $bRPL_STATSPLINE :: ReplyCode
$mRPL_STATSPLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSPLINE = ReplyCode 220
pattern $bRPL_UMODEIS :: ReplyCode
$mRPL_UMODEIS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_UMODEIS = ReplyCode 221
pattern $bRPL_SQLINE_NICK :: ReplyCode
$mRPL_SQLINE_NICK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SQLINE_NICK = ReplyCode 222
pattern $bRPL_STATSDLINE :: ReplyCode
$mRPL_STATSDLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSDLINE = ReplyCode 225
pattern $bRPL_STATSCOUNT :: ReplyCode
$mRPL_STATSCOUNT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSCOUNT = ReplyCode 226
pattern $bRPL_SERVICEINFO :: ReplyCode
$mRPL_SERVICEINFO :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SERVICEINFO = ReplyCode 231
pattern $bRPL_ENDOFSERVICES :: ReplyCode
$mRPL_ENDOFSERVICES :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFSERVICES = ReplyCode 232
pattern $bRPL_SERVICE :: ReplyCode
$mRPL_SERVICE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SERVICE = ReplyCode 233
pattern $bRPL_SERVLIST :: ReplyCode
$mRPL_SERVLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SERVLIST = ReplyCode 234
pattern $bRPL_SERVLISTEND :: ReplyCode
$mRPL_SERVLISTEND :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SERVLISTEND = ReplyCode 235
pattern $bRPL_STATSVERBOSE :: ReplyCode
$mRPL_STATSVERBOSE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSVERBOSE = ReplyCode 236
pattern $bRPL_STATSIAUTH :: ReplyCode
$mRPL_STATSIAUTH :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSIAUTH = ReplyCode 239
pattern $bRPL_STATSLLINE :: ReplyCode
$mRPL_STATSLLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSLLINE = ReplyCode 241
pattern $bRPL_STATSUPTIME :: ReplyCode
$mRPL_STATSUPTIME :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSUPTIME = ReplyCode 242
pattern $bRPL_STATSOLINE :: ReplyCode
$mRPL_STATSOLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSOLINE = ReplyCode 243
pattern $bRPL_STATSHLINE :: ReplyCode
$mRPL_STATSHLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSHLINE = ReplyCode 244
pattern $bRPL_STATSSLINE :: ReplyCode
$mRPL_STATSSLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSSLINE = ReplyCode 245
pattern $bRPL_STATSPING :: ReplyCode
$mRPL_STATSPING :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSPING = ReplyCode 246
pattern $bRPL_STATSXLINE :: ReplyCode
$mRPL_STATSXLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSXLINE = ReplyCode 247
pattern $bRPL_STATSULINE :: ReplyCode
$mRPL_STATSULINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSULINE = ReplyCode 248
pattern $bRPL_STATSDEBUG :: ReplyCode
$mRPL_STATSDEBUG :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSDEBUG = ReplyCode 249
pattern $bRPL_STATSCONN :: ReplyCode
$mRPL_STATSCONN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSCONN = ReplyCode 250
pattern $bRPL_LUSERCLIENT :: ReplyCode
$mRPL_LUSERCLIENT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LUSERCLIENT = ReplyCode 251
pattern $bRPL_LUSEROP :: ReplyCode
$mRPL_LUSEROP :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LUSEROP = ReplyCode 252
pattern $bRPL_LUSERUNKNOWN :: ReplyCode
$mRPL_LUSERUNKNOWN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LUSERUNKNOWN = ReplyCode 253
pattern $bRPL_LUSERCHANNELS :: ReplyCode
$mRPL_LUSERCHANNELS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LUSERCHANNELS = ReplyCode 254
pattern $bRPL_LUSERME :: ReplyCode
$mRPL_LUSERME :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LUSERME = ReplyCode 255
pattern $bRPL_ADMINME :: ReplyCode
$mRPL_ADMINME :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ADMINME = ReplyCode 256
pattern $bRPL_ADMINLOC1 :: ReplyCode
$mRPL_ADMINLOC1 :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ADMINLOC1 = ReplyCode 257
pattern $bRPL_ADMINLOC2 :: ReplyCode
$mRPL_ADMINLOC2 :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ADMINLOC2 = ReplyCode 258
pattern $bRPL_ADMINEMAIL :: ReplyCode
$mRPL_ADMINEMAIL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ADMINEMAIL = ReplyCode 259
pattern $bRPL_TRACELOG :: ReplyCode
$mRPL_TRACELOG :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACELOG = ReplyCode 261
pattern $bRPL_ENDOFTRACE :: ReplyCode
$mRPL_ENDOFTRACE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFTRACE = ReplyCode 262
pattern $bRPL_LOAD2HI :: ReplyCode
$mRPL_LOAD2HI :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LOAD2HI = ReplyCode 263
pattern $bRPL_LOCALUSERS :: ReplyCode
$mRPL_LOCALUSERS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LOCALUSERS = ReplyCode 265
pattern $bRPL_GLOBALUSERS :: ReplyCode
$mRPL_GLOBALUSERS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_GLOBALUSERS = ReplyCode 266
pattern $bRPL_START_NETSTAT :: ReplyCode
$mRPL_START_NETSTAT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_START_NETSTAT = ReplyCode 267
pattern $bRPL_NETSTAT :: ReplyCode
$mRPL_NETSTAT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NETSTAT = ReplyCode 268
pattern $bRPL_END_NETSTAT :: ReplyCode
$mRPL_END_NETSTAT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_END_NETSTAT = ReplyCode 269
pattern $bRPL_PRIVS :: ReplyCode
$mRPL_PRIVS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_PRIVS = ReplyCode 270
pattern $bRPL_SILELIST :: ReplyCode
$mRPL_SILELIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SILELIST = ReplyCode 271
pattern $bRPL_ENDOFSILELIST :: ReplyCode
$mRPL_ENDOFSILELIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFSILELIST = ReplyCode 272
pattern $bRPL_NOTIFY :: ReplyCode
$mRPL_NOTIFY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NOTIFY = ReplyCode 273
pattern $bRPL_ENDNOTIFY :: ReplyCode
$mRPL_ENDNOTIFY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDNOTIFY = ReplyCode 274
pattern $bRPL_STATSDELTA :: ReplyCode
$mRPL_STATSDELTA :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STATSDELTA = ReplyCode 274
pattern $bRPL_WHOISCERTFP :: ReplyCode
$mRPL_WHOISCERTFP :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISCERTFP = ReplyCode 276
pattern $bRPL_VCHANLIST :: ReplyCode
$mRPL_VCHANLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_VCHANLIST = ReplyCode 277
pattern $bRPL_VCHANHELP :: ReplyCode
$mRPL_VCHANHELP :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_VCHANHELP = ReplyCode 278
pattern $bRPL_GLIST :: ReplyCode
$mRPL_GLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_GLIST = ReplyCode 280
pattern $bRPL_ACCEPTLIST :: ReplyCode
$mRPL_ACCEPTLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ACCEPTLIST = ReplyCode 281
pattern $bRPL_ENDOFACCEPT :: ReplyCode
$mRPL_ENDOFACCEPT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFACCEPT = ReplyCode 282
pattern $bRPL_ENDOFJUPELIST :: ReplyCode
$mRPL_ENDOFJUPELIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFJUPELIST = ReplyCode 283
pattern $bRPL_FEATURE :: ReplyCode
$mRPL_FEATURE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_FEATURE = ReplyCode 284
pattern $bRPL_DATASTR :: ReplyCode
$mRPL_DATASTR :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_DATASTR = ReplyCode 290
pattern $bRPL_END_CHANINFO :: ReplyCode
$mRPL_END_CHANINFO :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_END_CHANINFO = ReplyCode 299
pattern $bRPL_NONE :: ReplyCode
$mRPL_NONE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NONE = ReplyCode 300
pattern $bRPL_AWAY :: ReplyCode
$mRPL_AWAY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_AWAY = ReplyCode 301
pattern $bRPL_USERHOST :: ReplyCode
$mRPL_USERHOST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_USERHOST = ReplyCode 302
pattern $bRPL_ISON :: ReplyCode
$mRPL_ISON :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ISON = ReplyCode 303
pattern $bRPL_TEXT :: ReplyCode
$mRPL_TEXT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TEXT = ReplyCode 304
pattern $bRPL_UNAWAY :: ReplyCode
$mRPL_UNAWAY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_UNAWAY = ReplyCode 305
pattern $bRPL_NOWAWAY :: ReplyCode
$mRPL_NOWAWAY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NOWAWAY = ReplyCode 306
pattern $bRPL_WHOISREGNICK :: ReplyCode
$mRPL_WHOISREGNICK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISREGNICK = ReplyCode 307
pattern $bRPL_SUSERHOST :: ReplyCode
$mRPL_SUSERHOST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SUSERHOST = ReplyCode 307
pattern $bRPL_NOTIFYACTION :: ReplyCode
$mRPL_NOTIFYACTION :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NOTIFYACTION = ReplyCode 308
pattern $bRPL_WHOISADMIN :: ReplyCode
$mRPL_WHOISADMIN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISADMIN = ReplyCode 308
pattern $bRPL_NICKTRACE :: ReplyCode
$mRPL_NICKTRACE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NICKTRACE = ReplyCode 309
pattern $bRPL_WHOISSADMIN :: ReplyCode
$mRPL_WHOISSADMIN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISSADMIN = ReplyCode 309
pattern $bRPL_WHOISHELPER :: ReplyCode
$mRPL_WHOISHELPER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISHELPER = ReplyCode 309
pattern $bRPL_WHOISHELPOP :: ReplyCode
$mRPL_WHOISHELPOP :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISHELPOP = ReplyCode 310
pattern $bRPL_WHOISUSER :: ReplyCode
$mRPL_WHOISUSER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISUSER = ReplyCode 311
pattern $bRPL_WHOISSERVER :: ReplyCode
$mRPL_WHOISSERVER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISSERVER = ReplyCode 312
pattern $bRPL_WHOISOPERATOR :: ReplyCode
$mRPL_WHOISOPERATOR :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISOPERATOR = ReplyCode 313
pattern $bRPL_WHOWASUSER :: ReplyCode
$mRPL_WHOWASUSER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOWASUSER = ReplyCode 314
pattern $bRPL_ENDOFWHO :: ReplyCode
$mRPL_ENDOFWHO :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFWHO = ReplyCode 315
pattern $bRPL_WHOISCHANOP :: ReplyCode
$mRPL_WHOISCHANOP :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISCHANOP = ReplyCode 316
pattern $bRPL_WHOISIDLE :: ReplyCode
$mRPL_WHOISIDLE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISIDLE = ReplyCode 317
pattern $bRPL_ENDOFWHOIS :: ReplyCode
$mRPL_ENDOFWHOIS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFWHOIS = ReplyCode 318
pattern $bRPL_WHOISCHANNELS :: ReplyCode
$mRPL_WHOISCHANNELS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISCHANNELS = ReplyCode 319
pattern $bRPL_WHOISSPECIAL :: ReplyCode
$mRPL_WHOISSPECIAL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISSPECIAL = ReplyCode 320
pattern $bRPL_LISTSTART :: ReplyCode
$mRPL_LISTSTART :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LISTSTART = ReplyCode 321
pattern $bRPL_LIST :: ReplyCode
$mRPL_LIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LIST = ReplyCode 322
pattern $bRPL_LISTEND :: ReplyCode
$mRPL_LISTEND :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LISTEND = ReplyCode 323
pattern $bRPL_CHANNELMODEIS :: ReplyCode
$mRPL_CHANNELMODEIS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_CHANNELMODEIS = ReplyCode 324
pattern $bRPL_CHANNELMLOCKIS :: ReplyCode
$mRPL_CHANNELMLOCKIS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_CHANNELMLOCKIS = ReplyCode 325
pattern $bRPL_NOCHANPASS :: ReplyCode
$mRPL_NOCHANPASS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NOCHANPASS = ReplyCode 326
pattern $bRPL_CHPASSUNKNOWN :: ReplyCode
$mRPL_CHPASSUNKNOWN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_CHPASSUNKNOWN = ReplyCode 327
pattern $bRPL_CHANNEL_URL :: ReplyCode
$mRPL_CHANNEL_URL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_CHANNEL_URL = ReplyCode 328
pattern $bRPL_CREATIONTIME :: ReplyCode
$mRPL_CREATIONTIME :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_CREATIONTIME = ReplyCode 329
pattern $bRPL_WHOISACCOUNT :: ReplyCode
$mRPL_WHOISACCOUNT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISACCOUNT = ReplyCode 330
pattern $bRPL_NOTOPIC :: ReplyCode
$mRPL_NOTOPIC :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NOTOPIC = ReplyCode 331
pattern $bRPL_TOPIC :: ReplyCode
$mRPL_TOPIC :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TOPIC = ReplyCode 332
pattern $bRPL_TOPICWHOTIME :: ReplyCode
$mRPL_TOPICWHOTIME :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TOPICWHOTIME = ReplyCode 333
pattern $bRPL_LISTUSAGE :: ReplyCode
$mRPL_LISTUSAGE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LISTUSAGE = ReplyCode 334
pattern $bRPL_COMMANDSYNTAX :: ReplyCode
$mRPL_COMMANDSYNTAX :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_COMMANDSYNTAX = ReplyCode 334
pattern $bRPL_LISTSYNTAX :: ReplyCode
$mRPL_LISTSYNTAX :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LISTSYNTAX = ReplyCode 334
pattern $bRPL_WHOISACTUALLY :: ReplyCode
$mRPL_WHOISACTUALLY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISACTUALLY = ReplyCode 338
pattern $bRPL_BADCHANPASS :: ReplyCode
$mRPL_BADCHANPASS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_BADCHANPASS = ReplyCode 339
pattern $bRPL_INVITING :: ReplyCode
$mRPL_INVITING :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_INVITING = ReplyCode 341
pattern $bRPL_SUMMONING :: ReplyCode
$mRPL_SUMMONING :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SUMMONING = ReplyCode 342
pattern $bRPL_INVITED :: ReplyCode
$mRPL_INVITED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_INVITED = ReplyCode 345
pattern $bRPL_INVEXLIST :: ReplyCode
$mRPL_INVEXLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_INVEXLIST = ReplyCode 346
pattern $bRPL_ENDOFINVEXLIST :: ReplyCode
$mRPL_ENDOFINVEXLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFINVEXLIST = ReplyCode 347
pattern $bRPL_EXCEPTLIST :: ReplyCode
$mRPL_EXCEPTLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_EXCEPTLIST = ReplyCode 348
pattern $bRPL_ENDOFEXCEPTLIST :: ReplyCode
$mRPL_ENDOFEXCEPTLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFEXCEPTLIST = ReplyCode 349
pattern $bRPL_VERSION :: ReplyCode
$mRPL_VERSION :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_VERSION = ReplyCode 351
pattern $bRPL_WHOREPLY :: ReplyCode
$mRPL_WHOREPLY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOREPLY = ReplyCode 352
pattern $bRPL_NAMREPLY :: ReplyCode
$mRPL_NAMREPLY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NAMREPLY = ReplyCode 353
pattern $bRPL_WHOSPCRPL :: ReplyCode
$mRPL_WHOSPCRPL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOSPCRPL = ReplyCode 354
pattern $bRPL_NAMREPLY_ :: ReplyCode
$mRPL_NAMREPLY_ :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NAMREPLY_ = ReplyCode 355
pattern $bRPL_WHOWASREAL :: ReplyCode
$mRPL_WHOWASREAL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOWASREAL = ReplyCode 360
pattern $bRPL_KILLDONE :: ReplyCode
$mRPL_KILLDONE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_KILLDONE = ReplyCode 361
pattern $bRPL_CLOSING :: ReplyCode
$mRPL_CLOSING :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_CLOSING = ReplyCode 362
pattern $bRPL_CLOSEEND :: ReplyCode
$mRPL_CLOSEEND :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_CLOSEEND = ReplyCode 363
pattern $bRPL_LINKS :: ReplyCode
$mRPL_LINKS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LINKS = ReplyCode 364
pattern $bRPL_ENDOFLINKS :: ReplyCode
$mRPL_ENDOFLINKS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFLINKS = ReplyCode 365
pattern $bRPL_ENDOFNAMES :: ReplyCode
$mRPL_ENDOFNAMES :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFNAMES = ReplyCode 366
pattern $bRPL_BANLIST :: ReplyCode
$mRPL_BANLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_BANLIST = ReplyCode 367
pattern $bRPL_ENDOFBANLIST :: ReplyCode
$mRPL_ENDOFBANLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFBANLIST = ReplyCode 368
pattern $bRPL_ENDOFWHOWAS :: ReplyCode
$mRPL_ENDOFWHOWAS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFWHOWAS = ReplyCode 369
pattern $bRPL_INFO :: ReplyCode
$mRPL_INFO :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_INFO = ReplyCode 371
pattern $bRPL_MOTD :: ReplyCode
$mRPL_MOTD :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_MOTD = ReplyCode 372
pattern $bRPL_INFOSTART :: ReplyCode
$mRPL_INFOSTART :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_INFOSTART = ReplyCode 373
pattern $bRPL_ENDOFINFO :: ReplyCode
$mRPL_ENDOFINFO :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFINFO = ReplyCode 374
pattern $bRPL_MOTDSTART :: ReplyCode
$mRPL_MOTDSTART :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_MOTDSTART = ReplyCode 375
pattern $bRPL_ENDOFMOTD :: ReplyCode
$mRPL_ENDOFMOTD :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFMOTD = ReplyCode 376
pattern $bRPL_WHOISHOST :: ReplyCode
$mRPL_WHOISHOST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISHOST = ReplyCode 378
pattern $bRPL_WHOISMODES :: ReplyCode
$mRPL_WHOISMODES :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISMODES = ReplyCode 379
pattern $bRPL_YOUREOPER :: ReplyCode
$mRPL_YOUREOPER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_YOUREOPER = ReplyCode 381
pattern $bRPL_REHASHING :: ReplyCode
$mRPL_REHASHING :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_REHASHING = ReplyCode 382
pattern $bRPL_YOURESERVICE :: ReplyCode
$mRPL_YOURESERVICE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_YOURESERVICE = ReplyCode 383
pattern $bRPL_MYPORTIS :: ReplyCode
$mRPL_MYPORTIS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_MYPORTIS = ReplyCode 384
pattern $bRPL_NOTOPERANYMORE :: ReplyCode
$mRPL_NOTOPERANYMORE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NOTOPERANYMORE = ReplyCode 385
pattern $bRPL_RSACHALLENGE :: ReplyCode
$mRPL_RSACHALLENGE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_RSACHALLENGE = ReplyCode 386
pattern $bRPL_TIME :: ReplyCode
$mRPL_TIME :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TIME = ReplyCode 391
pattern = ReplyCode 392
pattern $bRPL_USERS :: ReplyCode
$mRPL_USERS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_USERS = ReplyCode 393
pattern $bRPL_ENDOFUSERS :: ReplyCode
$mRPL_ENDOFUSERS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFUSERS = ReplyCode 394
pattern $bRPL_NOUSERS :: ReplyCode
$mRPL_NOUSERS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NOUSERS = ReplyCode 395
pattern $bRPL_HOSTHIDDEN :: ReplyCode
$mRPL_HOSTHIDDEN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_HOSTHIDDEN = ReplyCode 396
pattern $bERR_UNKNOWNERROR :: ReplyCode
$mERR_UNKNOWNERROR :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_UNKNOWNERROR = ReplyCode 400
pattern $bERR_NOSUCHNICK :: ReplyCode
$mERR_NOSUCHNICK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOSUCHNICK = ReplyCode 401
pattern $bERR_NOSUCHSERVER :: ReplyCode
$mERR_NOSUCHSERVER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOSUCHSERVER = ReplyCode 402
pattern $bERR_NOSUCHCHANNEL :: ReplyCode
$mERR_NOSUCHCHANNEL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOSUCHCHANNEL = ReplyCode 403
pattern $bERR_CANNOTSENDTOCHAN :: ReplyCode
$mERR_CANNOTSENDTOCHAN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_CANNOTSENDTOCHAN = ReplyCode 404
pattern $bERR_TOOMANYCHANNELS :: ReplyCode
$mERR_TOOMANYCHANNELS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TOOMANYCHANNELS = ReplyCode 405
pattern $bERR_WASNOSUCHNICK :: ReplyCode
$mERR_WASNOSUCHNICK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_WASNOSUCHNICK = ReplyCode 406
pattern $bERR_TOOMANYTARGETS :: ReplyCode
$mERR_TOOMANYTARGETS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TOOMANYTARGETS = ReplyCode 407
pattern $bERR_NOORIGIN :: ReplyCode
$mERR_NOORIGIN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOORIGIN = ReplyCode 409
pattern $bERR_INVALIDCAPCMD :: ReplyCode
$mERR_INVALIDCAPCMD :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_INVALIDCAPCMD = ReplyCode 410
pattern $bERR_NORECIPIENT :: ReplyCode
$mERR_NORECIPIENT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NORECIPIENT = ReplyCode 411
pattern $bERR_NOTEXTTOSEND :: ReplyCode
$mERR_NOTEXTTOSEND :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOTEXTTOSEND = ReplyCode 412
pattern $bERR_NOTOPLEVEL :: ReplyCode
$mERR_NOTOPLEVEL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOTOPLEVEL = ReplyCode 413
pattern $bERR_WILDTOPLEVEL :: ReplyCode
$mERR_WILDTOPLEVEL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_WILDTOPLEVEL = ReplyCode 414
pattern $bERR_MSGNEEDREGGEDNICK :: ReplyCode
$mERR_MSGNEEDREGGEDNICK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_MSGNEEDREGGEDNICK = ReplyCode 415
pattern $bERR_TOOMANYMATCHES :: ReplyCode
$mERR_TOOMANYMATCHES :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TOOMANYMATCHES = ReplyCode 416
pattern $bERR_LENGTHTRUNCATED :: ReplyCode
$mERR_LENGTHTRUNCATED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_LENGTHTRUNCATED = ReplyCode 419
pattern $bERR_UNKNOWNCOMMAND :: ReplyCode
$mERR_UNKNOWNCOMMAND :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_UNKNOWNCOMMAND = ReplyCode 421
pattern $bERR_NOMOTD :: ReplyCode
$mERR_NOMOTD :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOMOTD = ReplyCode 422
pattern $bERR_NOADMININFO :: ReplyCode
$mERR_NOADMININFO :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOADMININFO = ReplyCode 423
pattern $bERR_FILEERROR :: ReplyCode
$mERR_FILEERROR :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_FILEERROR = ReplyCode 424
pattern $bERR_NOOPERMOTD :: ReplyCode
$mERR_NOOPERMOTD :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOOPERMOTD = ReplyCode 425
pattern $bERR_TOOMANYAWAY :: ReplyCode
$mERR_TOOMANYAWAY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TOOMANYAWAY = ReplyCode 429
pattern $bERR_EVENTNICKCHANGE :: ReplyCode
$mERR_EVENTNICKCHANGE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_EVENTNICKCHANGE = ReplyCode 430
pattern $bERR_NONICKNAMEGIVEN :: ReplyCode
$mERR_NONICKNAMEGIVEN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NONICKNAMEGIVEN = ReplyCode 431
pattern $bERR_ERRONEUSNICKNAME :: ReplyCode
$mERR_ERRONEUSNICKNAME :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_ERRONEUSNICKNAME = ReplyCode 432
pattern $bERR_NICKNAMEINUSE :: ReplyCode
$mERR_NICKNAMEINUSE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NICKNAMEINUSE = ReplyCode 433
pattern $bERR_SERVICENAMEINUSE :: ReplyCode
$mERR_SERVICENAMEINUSE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_SERVICENAMEINUSE = ReplyCode 434
pattern $bERR_NORULES :: ReplyCode
$mERR_NORULES :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NORULES = ReplyCode 434
pattern $bERR_BANNICKCHANGE :: ReplyCode
$mERR_BANNICKCHANGE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BANNICKCHANGE = ReplyCode 435
pattern $bERR_NICKCOLLISION :: ReplyCode
$mERR_NICKCOLLISION :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NICKCOLLISION = ReplyCode 436
pattern $bERR_UNAVAILRESOURCE :: ReplyCode
$mERR_UNAVAILRESOURCE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_UNAVAILRESOURCE = ReplyCode 437
pattern $bERR_NICKTOOFAST :: ReplyCode
$mERR_NICKTOOFAST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NICKTOOFAST = ReplyCode 438
pattern $bERR_TARGETTOOFAST :: ReplyCode
$mERR_TARGETTOOFAST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TARGETTOOFAST = ReplyCode 439
pattern $bERR_SERVICESDOWN :: ReplyCode
$mERR_SERVICESDOWN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_SERVICESDOWN = ReplyCode 440
pattern $bERR_USERNOTINCHANNEL :: ReplyCode
$mERR_USERNOTINCHANNEL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_USERNOTINCHANNEL = ReplyCode 441
pattern $bERR_NOTONCHANNEL :: ReplyCode
$mERR_NOTONCHANNEL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOTONCHANNEL = ReplyCode 442
pattern $bERR_USERONCHANNEL :: ReplyCode
$mERR_USERONCHANNEL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_USERONCHANNEL = ReplyCode 443
pattern $bERR_NOLOGIN :: ReplyCode
$mERR_NOLOGIN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOLOGIN = ReplyCode 444
pattern $bERR_SUMMONDISABLED :: ReplyCode
$mERR_SUMMONDISABLED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_SUMMONDISABLED = ReplyCode 445
pattern $bERR_USERSDISABLED :: ReplyCode
$mERR_USERSDISABLED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_USERSDISABLED = ReplyCode 446
pattern $bERR_NONICKCHANGE :: ReplyCode
$mERR_NONICKCHANGE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NONICKCHANGE = ReplyCode 447
pattern $bERR_NOTIMPLEMENTED :: ReplyCode
$mERR_NOTIMPLEMENTED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOTIMPLEMENTED = ReplyCode 449
pattern $bERR_NOTREGISTERED :: ReplyCode
$mERR_NOTREGISTERED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOTREGISTERED = ReplyCode 451
pattern $bERR_IDCOLLISION :: ReplyCode
$mERR_IDCOLLISION :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_IDCOLLISION = ReplyCode 452
pattern $bERR_NICKLOST :: ReplyCode
$mERR_NICKLOST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NICKLOST = ReplyCode 453
pattern $bERR_HOSTILENAME :: ReplyCode
$mERR_HOSTILENAME :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_HOSTILENAME = ReplyCode 455
pattern $bERR_ACCEPTFULL :: ReplyCode
$mERR_ACCEPTFULL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_ACCEPTFULL = ReplyCode 456
pattern $bERR_ACCEPTEXIST :: ReplyCode
$mERR_ACCEPTEXIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_ACCEPTEXIST = ReplyCode 457
pattern $bERR_ACCEPTNOT :: ReplyCode
$mERR_ACCEPTNOT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_ACCEPTNOT = ReplyCode 458
pattern $bERR_NOHIDING :: ReplyCode
$mERR_NOHIDING :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOHIDING = ReplyCode 459
pattern $bERR_NOTFORHALFOPS :: ReplyCode
$mERR_NOTFORHALFOPS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOTFORHALFOPS = ReplyCode 460
pattern $bERR_NEEDMOREPARAMS :: ReplyCode
$mERR_NEEDMOREPARAMS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NEEDMOREPARAMS = ReplyCode 461
pattern $bERR_ALREADYREGISTERED :: ReplyCode
$mERR_ALREADYREGISTERED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_ALREADYREGISTERED = ReplyCode 462
pattern $bERR_NOPERMFORHOST :: ReplyCode
$mERR_NOPERMFORHOST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOPERMFORHOST = ReplyCode 463
pattern $bERR_PASSWDMISMATCH :: ReplyCode
$mERR_PASSWDMISMATCH :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_PASSWDMISMATCH = ReplyCode 464
pattern $bERR_YOUREBANNEDCREEP :: ReplyCode
$mERR_YOUREBANNEDCREEP :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_YOUREBANNEDCREEP = ReplyCode 465
pattern $bERR_YOUWILLBEBANNED :: ReplyCode
$mERR_YOUWILLBEBANNED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_YOUWILLBEBANNED = ReplyCode 466
pattern $bERR_KEYSET :: ReplyCode
$mERR_KEYSET :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_KEYSET = ReplyCode 467
pattern $bERR_INVALIDUSERNAME :: ReplyCode
$mERR_INVALIDUSERNAME :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_INVALIDUSERNAME = ReplyCode 468
pattern $bERR_ONLYSERVERSCANCHANGE :: ReplyCode
$mERR_ONLYSERVERSCANCHANGE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_ONLYSERVERSCANCHANGE = ReplyCode 468
pattern $bERR_LINKSET :: ReplyCode
$mERR_LINKSET :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_LINKSET = ReplyCode 469
pattern $bERR_LINKCHANNEL :: ReplyCode
$mERR_LINKCHANNEL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_LINKCHANNEL = ReplyCode 470
pattern $bERR_CHANNELISFULL :: ReplyCode
$mERR_CHANNELISFULL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_CHANNELISFULL = ReplyCode 471
pattern $bERR_UNKNOWNMODE :: ReplyCode
$mERR_UNKNOWNMODE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_UNKNOWNMODE = ReplyCode 472
pattern $bERR_INVITEONLYCHAN :: ReplyCode
$mERR_INVITEONLYCHAN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_INVITEONLYCHAN = ReplyCode 473
pattern $bERR_BANNEDFROMCHAN :: ReplyCode
$mERR_BANNEDFROMCHAN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BANNEDFROMCHAN = ReplyCode 474
pattern $bERR_BADCHANNELKEY :: ReplyCode
$mERR_BADCHANNELKEY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BADCHANNELKEY = ReplyCode 475
pattern $bERR_BADCHANMASK :: ReplyCode
$mERR_BADCHANMASK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BADCHANMASK = ReplyCode 476
pattern $bERR_NEEDREGGEDNICK :: ReplyCode
$mERR_NEEDREGGEDNICK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NEEDREGGEDNICK = ReplyCode 477
pattern $bERR_BANLISTFULL :: ReplyCode
$mERR_BANLISTFULL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BANLISTFULL = ReplyCode 478
pattern $bERR_BADCHANNAME :: ReplyCode
$mERR_BADCHANNAME :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BADCHANNAME = ReplyCode 479
pattern $bERR_THROTTLE :: ReplyCode
$mERR_THROTTLE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_THROTTLE = ReplyCode 480
pattern $bERR_NOPRIVILEGES :: ReplyCode
$mERR_NOPRIVILEGES :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOPRIVILEGES = ReplyCode 481
pattern $bERR_CHANOPRIVSNEEDED :: ReplyCode
$mERR_CHANOPRIVSNEEDED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_CHANOPRIVSNEEDED = ReplyCode 482
pattern $bERR_CANTKILLSERVER :: ReplyCode
$mERR_CANTKILLSERVER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_CANTKILLSERVER = ReplyCode 483
pattern $bERR_ISCHANSERVICE :: ReplyCode
$mERR_ISCHANSERVICE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_ISCHANSERVICE = ReplyCode 484
pattern $bERR_BANNEDNICK :: ReplyCode
$mERR_BANNEDNICK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BANNEDNICK = ReplyCode 485
pattern $bERR_NONONREG :: ReplyCode
$mERR_NONONREG :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NONONREG = ReplyCode 486
pattern $bERR_TSLESSCHAN :: ReplyCode
$mERR_TSLESSCHAN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TSLESSCHAN = ReplyCode 488
pattern $bERR_VOICENEEDED :: ReplyCode
$mERR_VOICENEEDED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_VOICENEEDED = ReplyCode 489
pattern $bERR_NOOPERHOST :: ReplyCode
$mERR_NOOPERHOST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOOPERHOST = ReplyCode 491
pattern $bERR_NOSERVICEHOST :: ReplyCode
$mERR_NOSERVICEHOST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOSERVICEHOST = ReplyCode 492
pattern $bERR_NOFEATURE :: ReplyCode
$mERR_NOFEATURE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOFEATURE = ReplyCode 493
pattern $bERR_OWNMODE :: ReplyCode
$mERR_OWNMODE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_OWNMODE = ReplyCode 494
pattern $bERR_BADLOGTYPE :: ReplyCode
$mERR_BADLOGTYPE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BADLOGTYPE = ReplyCode 495
pattern $bERR_BADLOGSYS :: ReplyCode
$mERR_BADLOGSYS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BADLOGSYS = ReplyCode 496
pattern $bERR_BADLOGVALUE :: ReplyCode
$mERR_BADLOGVALUE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BADLOGVALUE = ReplyCode 497
pattern $bERR_ISOPERLCHAN :: ReplyCode
$mERR_ISOPERLCHAN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_ISOPERLCHAN = ReplyCode 498
pattern $bERR_CHANOWNPRIVNEEDED :: ReplyCode
$mERR_CHANOWNPRIVNEEDED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_CHANOWNPRIVNEEDED = ReplyCode 499
pattern $bERR_UMODEUNKNOWNFLAG :: ReplyCode
$mERR_UMODEUNKNOWNFLAG :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_UMODEUNKNOWNFLAG = ReplyCode 501
pattern $bERR_USERSDONTMATCH :: ReplyCode
$mERR_USERSDONTMATCH :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_USERSDONTMATCH = ReplyCode 502
pattern $bERR_GHOSTEDCLIENT :: ReplyCode
$mERR_GHOSTEDCLIENT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_GHOSTEDCLIENT = ReplyCode 503
pattern $bERR_USERNOTONSERV :: ReplyCode
$mERR_USERNOTONSERV :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_USERNOTONSERV = ReplyCode 504
pattern $bERR_SILELISTFULL :: ReplyCode
$mERR_SILELISTFULL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_SILELISTFULL = ReplyCode 511
pattern $bERR_TOOMANYWATCH :: ReplyCode
$mERR_TOOMANYWATCH :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TOOMANYWATCH = ReplyCode 512
pattern $bERR_WRONGPONG :: ReplyCode
$mERR_WRONGPONG :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_WRONGPONG = ReplyCode 513
pattern $bERR_BADEXPIRE :: ReplyCode
$mERR_BADEXPIRE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BADEXPIRE = ReplyCode 515
pattern $bERR_DONTCHEAT :: ReplyCode
$mERR_DONTCHEAT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_DONTCHEAT = ReplyCode 516
pattern $bERR_DISABLED :: ReplyCode
$mERR_DISABLED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_DISABLED = ReplyCode 517
pattern $bERR_NOINVITE :: ReplyCode
$mERR_NOINVITE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOINVITE = ReplyCode 518
pattern $bERR_LONGMASK :: ReplyCode
$mERR_LONGMASK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_LONGMASK = ReplyCode 518
pattern $bERR_ADMONLY :: ReplyCode
$mERR_ADMONLY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_ADMONLY = ReplyCode 519
pattern $bERR_TOOMANYUSERS :: ReplyCode
$mERR_TOOMANYUSERS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TOOMANYUSERS = ReplyCode 519
pattern $bERR_OPERONLY :: ReplyCode
$mERR_OPERONLY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_OPERONLY = ReplyCode 520
pattern $bERR_MASKTOOWIDE :: ReplyCode
$mERR_MASKTOOWIDE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_MASKTOOWIDE = ReplyCode 520
pattern $bERR_WHOTRUNC :: ReplyCode
$mERR_WHOTRUNC :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_WHOTRUNC = ReplyCode 520
pattern $bERR_LISTSYNTAX :: ReplyCode
$mERR_LISTSYNTAX :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_LISTSYNTAX = ReplyCode 521
pattern $bERR_WHOSYNTAX :: ReplyCode
$mERR_WHOSYNTAX :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_WHOSYNTAX = ReplyCode 522
pattern $bERR_WHOLIMEXCEED :: ReplyCode
$mERR_WHOLIMEXCEED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_WHOLIMEXCEED = ReplyCode 523
pattern $bERR_HELPNOTFOUND :: ReplyCode
$mERR_HELPNOTFOUND :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_HELPNOTFOUND = ReplyCode 524
pattern $bERR_REMOTEPFX :: ReplyCode
$mERR_REMOTEPFX :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_REMOTEPFX = ReplyCode 525
pattern $bERR_PFXUNROUTABLE :: ReplyCode
$mERR_PFXUNROUTABLE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_PFXUNROUTABLE = ReplyCode 526
pattern $bERR_BADHOSTMASK :: ReplyCode
$mERR_BADHOSTMASK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BADHOSTMASK = ReplyCode 550
pattern $bERR_HOSTUNAVAIL :: ReplyCode
$mERR_HOSTUNAVAIL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_HOSTUNAVAIL = ReplyCode 551
pattern $bERR_USINGSLINE :: ReplyCode
$mERR_USINGSLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_USINGSLINE = ReplyCode 552
pattern $bERR_STATSSLINE :: ReplyCode
$mERR_STATSSLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_STATSSLINE = ReplyCode 553
pattern $bRPL_LOGON :: ReplyCode
$mRPL_LOGON :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LOGON = ReplyCode 600
pattern $bRPL_LOGOFF :: ReplyCode
$mRPL_LOGOFF :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LOGOFF = ReplyCode 601
pattern $bRPL_WATCHOFF :: ReplyCode
$mRPL_WATCHOFF :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WATCHOFF = ReplyCode 602
pattern $bRPL_WATCHSTAT :: ReplyCode
$mRPL_WATCHSTAT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WATCHSTAT = ReplyCode 603
pattern $bRPL_NOWON :: ReplyCode
$mRPL_NOWON :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NOWON = ReplyCode 604
pattern $bRPL_NOWOFF :: ReplyCode
$mRPL_NOWOFF :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NOWOFF = ReplyCode 605
pattern $bRPL_WATCHLIST :: ReplyCode
$mRPL_WATCHLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WATCHLIST = ReplyCode 606
pattern $bRPL_ENDOFWATCHLIST :: ReplyCode
$mRPL_ENDOFWATCHLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFWATCHLIST = ReplyCode 607
pattern $bRPL_WATCHCLEAR :: ReplyCode
$mRPL_WATCHCLEAR :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WATCHCLEAR = ReplyCode 608
pattern $bRPL_ISOPER :: ReplyCode
$mRPL_ISOPER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ISOPER = ReplyCode 610
pattern $bRPL_ISLOCOP :: ReplyCode
$mRPL_ISLOCOP :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ISLOCOP = ReplyCode 611
pattern $bRPL_ISNOTOPER :: ReplyCode
$mRPL_ISNOTOPER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ISNOTOPER = ReplyCode 612
pattern $bRPL_ENDOFISOPER :: ReplyCode
$mRPL_ENDOFISOPER :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFISOPER = ReplyCode 613
pattern $bRPL_DCCSTATUS :: ReplyCode
$mRPL_DCCSTATUS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_DCCSTATUS = ReplyCode 617
pattern $bRPL_DCCLIST :: ReplyCode
$mRPL_DCCLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_DCCLIST = ReplyCode 618
pattern $bRPL_ENDOFDCCLIST :: ReplyCode
$mRPL_ENDOFDCCLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFDCCLIST = ReplyCode 619
pattern $bRPL_WHOWASHOST :: ReplyCode
$mRPL_WHOWASHOST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOWASHOST = ReplyCode 619
pattern $bRPL_DCCINFO :: ReplyCode
$mRPL_DCCINFO :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_DCCINFO = ReplyCode 620
pattern $bRPL_RULES :: ReplyCode
$mRPL_RULES :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_RULES = ReplyCode 621
pattern $bRPL_ENDOFO :: ReplyCode
$mRPL_ENDOFO :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFO = ReplyCode 626
pattern $bRPL_SETTINGS :: ReplyCode
$mRPL_SETTINGS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SETTINGS = ReplyCode 630
pattern $bRPL_ENDOFSETTINGS :: ReplyCode
$mRPL_ENDOFSETTINGS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFSETTINGS = ReplyCode 631
pattern $bRPL_DUMPING :: ReplyCode
$mRPL_DUMPING :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_DUMPING = ReplyCode 640
pattern $bRPL_DUMPRPL :: ReplyCode
$mRPL_DUMPRPL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_DUMPRPL = ReplyCode 641
pattern $bRPL_EODUMP :: ReplyCode
$mRPL_EODUMP :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_EODUMP = ReplyCode 642
pattern $bRPL_TRACEROUTE_HOP :: ReplyCode
$mRPL_TRACEROUTE_HOP :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACEROUTE_HOP = ReplyCode 660
pattern $bRPL_TRACEROUTE_START :: ReplyCode
$mRPL_TRACEROUTE_START :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TRACEROUTE_START = ReplyCode 661
pattern $bRPL_MODECHANGEWARN :: ReplyCode
$mRPL_MODECHANGEWARN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_MODECHANGEWARN = ReplyCode 662
pattern $bRPL_CHANREDIR :: ReplyCode
$mRPL_CHANREDIR :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_CHANREDIR = ReplyCode 663
pattern $bRPL_SERVMODEIS :: ReplyCode
$mRPL_SERVMODEIS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SERVMODEIS = ReplyCode 664
pattern $bRPL_OTHERUMODEIS :: ReplyCode
$mRPL_OTHERUMODEIS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_OTHERUMODEIS = ReplyCode 665
pattern $bRPL_ENDOF_GENERIC :: ReplyCode
$mRPL_ENDOF_GENERIC :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOF_GENERIC = ReplyCode 666
pattern $bRPL_STARTTLS :: ReplyCode
$mRPL_STARTTLS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_STARTTLS = ReplyCode 670
pattern $bRPL_WHOISSECURE :: ReplyCode
$mRPL_WHOISSECURE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISSECURE = ReplyCode 671
pattern $bRPL_UNKNOWNMODES :: ReplyCode
$mRPL_UNKNOWNMODES :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_UNKNOWNMODES = ReplyCode 672
pattern $bRPL_CANNOTSETMODES :: ReplyCode
$mRPL_CANNOTSETMODES :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_CANNOTSETMODES = ReplyCode 673
pattern $bRPL_LUSERSTAFF :: ReplyCode
$mRPL_LUSERSTAFF :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LUSERSTAFF = ReplyCode 678
pattern $bRPL_TIMEONSERVERIS :: ReplyCode
$mRPL_TIMEONSERVERIS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TIMEONSERVERIS = ReplyCode 679
pattern $bRPL_NETWORKS :: ReplyCode
$mRPL_NETWORKS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NETWORKS = ReplyCode 682
pattern $bRPL_YOURLANGUAGEIS :: ReplyCode
$mRPL_YOURLANGUAGEIS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_YOURLANGUAGEIS = ReplyCode 687
pattern $bRPL_LANGUAGE :: ReplyCode
$mRPL_LANGUAGE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LANGUAGE = ReplyCode 688
pattern $bRPL_WHOISSTAFF :: ReplyCode
$mRPL_WHOISSTAFF :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISSTAFF = ReplyCode 689
pattern $bRPL_WHOISLANGUAGE :: ReplyCode
$mRPL_WHOISLANGUAGE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_WHOISLANGUAGE = ReplyCode 690
pattern $bERR_STARTTLS :: ReplyCode
$mERR_STARTTLS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_STARTTLS = ReplyCode 691
pattern $bRPL_MODLIST :: ReplyCode
$mRPL_MODLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_MODLIST = ReplyCode 702
pattern $bRPL_ENDOFMODLIST :: ReplyCode
$mRPL_ENDOFMODLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFMODLIST = ReplyCode 703
pattern $bRPL_HELPSTART :: ReplyCode
$mRPL_HELPSTART :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_HELPSTART = ReplyCode 704
pattern $bRPL_HELPTXT :: ReplyCode
$mRPL_HELPTXT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_HELPTXT = ReplyCode 705
pattern $bRPL_ENDOFHELP :: ReplyCode
$mRPL_ENDOFHELP :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFHELP = ReplyCode 706
pattern $bERR_TARGCHANGE :: ReplyCode
$mERR_TARGCHANGE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TARGCHANGE = ReplyCode 707
pattern $bRPL_ETRACEFULL :: ReplyCode
$mRPL_ETRACEFULL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ETRACEFULL = ReplyCode 708
pattern $bRPL_ETRACE :: ReplyCode
$mRPL_ETRACE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ETRACE = ReplyCode 709
pattern $bRPL_KNOCK :: ReplyCode
$mRPL_KNOCK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_KNOCK = ReplyCode 710
pattern $bRPL_KNOCKDLVR :: ReplyCode
$mRPL_KNOCKDLVR :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_KNOCKDLVR = ReplyCode 711
pattern $bERR_TOOMANYKNOCK :: ReplyCode
$mERR_TOOMANYKNOCK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TOOMANYKNOCK = ReplyCode 712
pattern $bERR_CHANOPEN :: ReplyCode
$mERR_CHANOPEN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_CHANOPEN = ReplyCode 713
pattern $bERR_KNOCKONCHAN :: ReplyCode
$mERR_KNOCKONCHAN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_KNOCKONCHAN = ReplyCode 714
pattern $bERR_KNOCKDISABLED :: ReplyCode
$mERR_KNOCKDISABLED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_KNOCKDISABLED = ReplyCode 715
pattern $bRPL_TARGUMODEG :: ReplyCode
$mRPL_TARGUMODEG :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TARGUMODEG = ReplyCode 716
pattern $bRPL_TARGNOTIFY :: ReplyCode
$mRPL_TARGNOTIFY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TARGNOTIFY = ReplyCode 717
pattern $bRPL_UMODEGMSG :: ReplyCode
$mRPL_UMODEGMSG :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_UMODEGMSG = ReplyCode 718
pattern $bRPL_OMOTDSTART :: ReplyCode
$mRPL_OMOTDSTART :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_OMOTDSTART = ReplyCode 720
pattern $bRPL_OMOTD :: ReplyCode
$mRPL_OMOTD :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_OMOTD = ReplyCode 721
pattern $bRPL_ENDOFOMOTD :: ReplyCode
$mRPL_ENDOFOMOTD :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFOMOTD = ReplyCode 722
pattern $bERR_NOPRIVS :: ReplyCode
$mERR_NOPRIVS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOPRIVS = ReplyCode 723
pattern $bRPL_TESTMASK :: ReplyCode
$mRPL_TESTMASK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TESTMASK = ReplyCode 724
pattern $bRPL_TESTLINE :: ReplyCode
$mRPL_TESTLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TESTLINE = ReplyCode 725
pattern $bRPL_NOTESTLINE :: ReplyCode
$mRPL_NOTESTLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NOTESTLINE = ReplyCode 726
pattern $bRPL_TESTMASKGECOS :: ReplyCode
$mRPL_TESTMASKGECOS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_TESTMASKGECOS = ReplyCode 727
pattern $bRPL_QUIETLIST :: ReplyCode
$mRPL_QUIETLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_QUIETLIST = ReplyCode 728
pattern $bRPL_ENDOFQUIETLIST :: ReplyCode
$mRPL_ENDOFQUIETLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFQUIETLIST = ReplyCode 729
pattern $bRPL_MONONLINE :: ReplyCode
$mRPL_MONONLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_MONONLINE = ReplyCode 730
pattern $bRPL_MONOFFLINE :: ReplyCode
$mRPL_MONOFFLINE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_MONOFFLINE = ReplyCode 731
pattern $bRPL_MONLIST :: ReplyCode
$mRPL_MONLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_MONLIST = ReplyCode 732
pattern $bRPL_ENDOFMONLIST :: ReplyCode
$mRPL_ENDOFMONLIST :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFMONLIST = ReplyCode 733
pattern $bERR_MONLISTFULL :: ReplyCode
$mERR_MONLISTFULL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_MONLISTFULL = ReplyCode 734
pattern $bRPL_RSACHALLENGE2 :: ReplyCode
$mRPL_RSACHALLENGE2 :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_RSACHALLENGE2 = ReplyCode 740
pattern $bRPL_ENDOFRSACHALLENGE2 :: ReplyCode
$mRPL_ENDOFRSACHALLENGE2 :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_ENDOFRSACHALLENGE2 = ReplyCode 741
pattern $bERR_MLOCKRESTRICTED :: ReplyCode
$mERR_MLOCKRESTRICTED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_MLOCKRESTRICTED = ReplyCode 742
pattern $bRPL_SCANMATCHED :: ReplyCode
$mRPL_SCANMATCHED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SCANMATCHED = ReplyCode 750
pattern $bRPL_SCANUMODES :: ReplyCode
$mRPL_SCANUMODES :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SCANUMODES = ReplyCode 751
pattern $bRPL_XINFO :: ReplyCode
$mRPL_XINFO :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_XINFO = ReplyCode 771
pattern $bRPL_XINFOSTART :: ReplyCode
$mRPL_XINFOSTART :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_XINFOSTART = ReplyCode 773
pattern $bRPL_XINFOEND :: ReplyCode
$mRPL_XINFOEND :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_XINFOEND = ReplyCode 774
pattern $bRPL_LOGGEDIN :: ReplyCode
$mRPL_LOGGEDIN :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LOGGEDIN = ReplyCode 900
pattern $bRPL_LOGGEDOUT :: ReplyCode
$mRPL_LOGGEDOUT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_LOGGEDOUT = ReplyCode 901
pattern $bRPL_NICKLOCKED :: ReplyCode
$mRPL_NICKLOCKED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_NICKLOCKED = ReplyCode 902
pattern $bRPL_SASLSUCCESS :: ReplyCode
$mRPL_SASLSUCCESS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SASLSUCCESS = ReplyCode 903
pattern $bERR_SASLFAIL :: ReplyCode
$mERR_SASLFAIL :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_SASLFAIL = ReplyCode 904
pattern $bERR_SASLTOOLONG :: ReplyCode
$mERR_SASLTOOLONG :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_SASLTOOLONG = ReplyCode 905
pattern $bERR_SASLABORTED :: ReplyCode
$mERR_SASLABORTED :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_SASLABORTED = ReplyCode 906
pattern $bERR_SASLALREADY :: ReplyCode
$mERR_SASLALREADY :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_SASLALREADY = ReplyCode 907
pattern $bRPL_SASLMECHS :: ReplyCode
$mRPL_SASLMECHS :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
RPL_SASLMECHS = ReplyCode 908
pattern $bERR_CANNOTDOCOMMAND :: ReplyCode
$mERR_CANNOTDOCOMMAND :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_CANNOTDOCOMMAND = ReplyCode 972
pattern $bERR_CANNOTCHANGEUMODE :: ReplyCode
$mERR_CANNOTCHANGEUMODE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_CANNOTCHANGEUMODE = ReplyCode 973
pattern $bERR_CANNOTCHANGECHANMODE :: ReplyCode
$mERR_CANNOTCHANGECHANMODE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_CANNOTCHANGECHANMODE = ReplyCode 974
pattern $bERR_CANNOTCHANGESERVERMODE :: ReplyCode
$mERR_CANNOTCHANGESERVERMODE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_CANNOTCHANGESERVERMODE = ReplyCode 975
pattern $bERR_CANNOTSENDTONICK :: ReplyCode
$mERR_CANNOTSENDTONICK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_CANNOTSENDTONICK = ReplyCode 976
pattern $bERR_UNKNOWNSERVERMODE :: ReplyCode
$mERR_UNKNOWNSERVERMODE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_UNKNOWNSERVERMODE = ReplyCode 977
pattern $bERR_SERVERMODELOCK :: ReplyCode
$mERR_SERVERMODELOCK :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_SERVERMODELOCK = ReplyCode 979
pattern $bERR_BADCHARENCODING :: ReplyCode
$mERR_BADCHARENCODING :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_BADCHARENCODING = ReplyCode 980
pattern $bERR_TOOMANYLANGUAGES :: ReplyCode
$mERR_TOOMANYLANGUAGES :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TOOMANYLANGUAGES = ReplyCode 981
pattern $bERR_NOLANGUAGE :: ReplyCode
$mERR_NOLANGUAGE :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NOLANGUAGE = ReplyCode 982
pattern $bERR_TEXTTOOSHORT :: ReplyCode
$mERR_TEXTTOOSHORT :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_TEXTTOOSHORT = ReplyCode 983
pattern $bERR_NUMERIC_ERR :: ReplyCode
$mERR_NUMERIC_ERR :: forall r. ReplyCode -> (Void# -> r) -> (Void# -> r) -> r
ERR_NUMERIC_ERR = ReplyCode 999
data ReplyCodeInfo = ReplyCodeInfo
{ ReplyCodeInfo -> ReplyType
replyCodeType :: !ReplyType
, ReplyCodeInfo -> Text
replyCodeText :: !Text
}
deriving (ReplyCodeInfo -> ReplyCodeInfo -> Bool
(ReplyCodeInfo -> ReplyCodeInfo -> Bool)
-> (ReplyCodeInfo -> ReplyCodeInfo -> Bool) -> Eq ReplyCodeInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
$c/= :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
== :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
$c== :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
Eq, Eq ReplyCodeInfo
Eq ReplyCodeInfo
-> (ReplyCodeInfo -> ReplyCodeInfo -> Ordering)
-> (ReplyCodeInfo -> ReplyCodeInfo -> Bool)
-> (ReplyCodeInfo -> ReplyCodeInfo -> Bool)
-> (ReplyCodeInfo -> ReplyCodeInfo -> Bool)
-> (ReplyCodeInfo -> ReplyCodeInfo -> Bool)
-> (ReplyCodeInfo -> ReplyCodeInfo -> ReplyCodeInfo)
-> (ReplyCodeInfo -> ReplyCodeInfo -> ReplyCodeInfo)
-> Ord ReplyCodeInfo
ReplyCodeInfo -> ReplyCodeInfo -> Bool
ReplyCodeInfo -> ReplyCodeInfo -> Ordering
ReplyCodeInfo -> ReplyCodeInfo -> ReplyCodeInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReplyCodeInfo -> ReplyCodeInfo -> ReplyCodeInfo
$cmin :: ReplyCodeInfo -> ReplyCodeInfo -> ReplyCodeInfo
max :: ReplyCodeInfo -> ReplyCodeInfo -> ReplyCodeInfo
$cmax :: ReplyCodeInfo -> ReplyCodeInfo -> ReplyCodeInfo
>= :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
$c>= :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
> :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
$c> :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
<= :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
$c<= :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
< :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
$c< :: ReplyCodeInfo -> ReplyCodeInfo -> Bool
compare :: ReplyCodeInfo -> ReplyCodeInfo -> Ordering
$ccompare :: ReplyCodeInfo -> ReplyCodeInfo -> Ordering
$cp1Ord :: Eq ReplyCodeInfo
Ord, Int -> ReplyCodeInfo -> ShowS
[ReplyCodeInfo] -> ShowS
ReplyCodeInfo -> String
(Int -> ReplyCodeInfo -> ShowS)
-> (ReplyCodeInfo -> String)
-> ([ReplyCodeInfo] -> ShowS)
-> Show ReplyCodeInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplyCodeInfo] -> ShowS
$cshowList :: [ReplyCodeInfo] -> ShowS
show :: ReplyCodeInfo -> String
$cshow :: ReplyCodeInfo -> String
showsPrec :: Int -> ReplyCodeInfo -> ShowS
$cshowsPrec :: Int -> ReplyCodeInfo -> ShowS
Show, ReadPrec [ReplyCodeInfo]
ReadPrec ReplyCodeInfo
Int -> ReadS ReplyCodeInfo
ReadS [ReplyCodeInfo]
(Int -> ReadS ReplyCodeInfo)
-> ReadS [ReplyCodeInfo]
-> ReadPrec ReplyCodeInfo
-> ReadPrec [ReplyCodeInfo]
-> Read ReplyCodeInfo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReplyCodeInfo]
$creadListPrec :: ReadPrec [ReplyCodeInfo]
readPrec :: ReadPrec ReplyCodeInfo
$creadPrec :: ReadPrec ReplyCodeInfo
readList :: ReadS [ReplyCodeInfo]
$creadList :: ReadS [ReplyCodeInfo]
readsPrec :: Int -> ReadS ReplyCodeInfo
$creadsPrec :: Int -> ReadS ReplyCodeInfo
Read)
replyCodeInfo :: ReplyCode -> ReplyCodeInfo
replyCodeInfo :: ReplyCode -> ReplyCodeInfo
replyCodeInfo (ReplyCode Word
w) =
case Vector ReplyCodeInfo
replyCodeInfoTable Vector ReplyCodeInfo -> Int -> Maybe ReplyCodeInfo
forall a. Vector a -> Int -> Maybe a
Vector.!? Int
i of
Maybe ReplyCodeInfo
Nothing -> Int -> ReplyCodeInfo
defaultReplyCodeInfo Int
i
Just ReplyCodeInfo
info -> ReplyCodeInfo
info
where
i :: Int
i = Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
w
defaultReplyCodeInfo :: Int -> ReplyCodeInfo
defaultReplyCodeInfo :: Int -> ReplyCodeInfo
defaultReplyCodeInfo = ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
UnknownReply (Text -> ReplyCodeInfo) -> (Int -> Text) -> Int -> ReplyCodeInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack (String -> Text) -> (Int -> String) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show
replyCodeInfoTable :: Vector ReplyCodeInfo
replyCodeInfoTable :: Vector ReplyCodeInfo
replyCodeInfoTable
= (ReplyCodeInfo -> ReplyCodeInfo -> ReplyCodeInfo)
-> Vector ReplyCodeInfo
-> Vector (Int, ReplyCodeInfo)
-> Vector ReplyCodeInfo
forall a b.
(a -> b -> a) -> Vector a -> Vector (Int, b) -> Vector a
Vector.accumulate
(\ReplyCodeInfo
_def ReplyCodeInfo
new -> ReplyCodeInfo
new)
(Int -> (Int -> ReplyCodeInfo) -> Vector ReplyCodeInfo
forall a. Int -> (Int -> a) -> Vector a
Vector.generate Int
1000 Int -> ReplyCodeInfo
defaultReplyCodeInfo)
(Vector (Int, ReplyCodeInfo) -> Vector ReplyCodeInfo)
-> Vector (Int, ReplyCodeInfo) -> Vector ReplyCodeInfo
forall a b. (a -> b) -> a -> b
$ ((ReplyCode, ReplyCodeInfo) -> (Int, ReplyCodeInfo))
-> Vector (ReplyCode, ReplyCodeInfo) -> Vector (Int, ReplyCodeInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(ReplyCode Word
code,ReplyCodeInfo
info) -> (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
code, ReplyCodeInfo
info))
(Vector (ReplyCode, ReplyCodeInfo) -> Vector (Int, ReplyCodeInfo))
-> Vector (ReplyCode, ReplyCodeInfo) -> Vector (Int, ReplyCodeInfo)
forall a b. (a -> b) -> a -> b
$ [(ReplyCode, ReplyCodeInfo)] -> Vector (ReplyCode, ReplyCodeInfo)
forall a. [a] -> Vector a
Vector.fromList
[ (ReplyCode
RPL_WELCOME , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"welcome")
, (ReplyCode
RPL_YOURHOST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"your-host")
, (ReplyCode
RPL_CREATED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"created")
, (ReplyCode
RPL_MYINFO , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"my-info")
, (ReplyCode
RPL_ISUPPORT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"isupport")
, (ReplyCode
RPL_SNOMASK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"sno-mask")
, (ReplyCode
RPL_STATMEMTOT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"stat-mem-tot")
, (ReplyCode
RPL_REDIR , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"redir")
, (ReplyCode
RPL_YOURCOOKIE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"your-cookie")
, (ReplyCode
RPL_MAP , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"map")
, (ReplyCode
RPL_MAPEND , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"map-end")
, (ReplyCode
RPL_YOURID , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"your-id")
, (ReplyCode
RPL_SAVENICK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"save-nick")
, (ReplyCode
RPL_ATTEMPTINGJUNC , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"attempting-junc")
, (ReplyCode
RPL_ATTEMPTINGREROUTE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"attempting-reroute")
, (ReplyCode
RPL_REMOTESUPPORT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ClientServerReply Text
"remote-support")
, (ReplyCode
RPL_TRACELINK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-link")
, (ReplyCode
RPL_TRACECONNECTING , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-connecting")
, (ReplyCode
RPL_TRACEHANDSHAKE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-handshake")
, (ReplyCode
RPL_TRACEUNKNOWN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-unknown")
, (ReplyCode
RPL_TRACEOPERATOR , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-operator")
, (ReplyCode
RPL_TRACEUSER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-user")
, (ReplyCode
RPL_TRACESERVER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-server")
, (ReplyCode
RPL_TRACESERVICE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-service")
, (ReplyCode
RPL_TRACENEWTYPE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-newtype")
, (ReplyCode
RPL_TRACECLASS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-class")
, (ReplyCode
RPL_TRACERECONNECT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-reconnect")
, (ReplyCode
RPL_STATS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats")
, (ReplyCode
RPL_STATSLINKINFO , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-linkinfo")
, (ReplyCode
RPL_STATSCOMMANDS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-commands")
, (ReplyCode
RPL_STATSCLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-cline")
, (ReplyCode
RPL_STATSNLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-nline")
, (ReplyCode
RPL_STATSILINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-iline")
, (ReplyCode
RPL_STATSKLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-kline")
, (ReplyCode
RPL_STATSQLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-qline")
, (ReplyCode
RPL_STATSYLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-yline")
, (ReplyCode
RPL_ENDOFSTATS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-stats")
, (ReplyCode
RPL_STATSPLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-pline")
, (ReplyCode
RPL_UMODEIS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"umode-is")
, (ReplyCode
RPL_SQLINE_NICK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"sqline-nick")
, (ReplyCode
RPL_STATSDLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-dline")
, (ReplyCode
RPL_STATSCOUNT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-count")
, (ReplyCode
RPL_SERVICEINFO , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"service-info")
, (ReplyCode
RPL_ENDOFSERVICES , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-services")
, (ReplyCode
RPL_SERVICE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"service")
, (ReplyCode
RPL_SERVLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"serv-list")
, (ReplyCode
RPL_SERVLISTEND , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"serv-list-end")
, (ReplyCode
RPL_STATSVERBOSE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-verbose")
, (ReplyCode
RPL_STATSIAUTH , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-iauth")
, (ReplyCode
RPL_STATSLLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-lline")
, (ReplyCode
RPL_STATSUPTIME , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-uptime")
, (ReplyCode
RPL_STATSOLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-oline")
, (ReplyCode
RPL_STATSHLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-hline")
, (ReplyCode
RPL_STATSSLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-sline")
, (ReplyCode
RPL_STATSPING , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-ping")
, (ReplyCode
RPL_STATSXLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-xline")
, (ReplyCode
RPL_STATSULINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-uline")
, (ReplyCode
RPL_STATSDEBUG , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-debug")
, (ReplyCode
RPL_STATSCONN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-conn")
, (ReplyCode
RPL_LUSERCLIENT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"luser-client")
, (ReplyCode
RPL_LUSEROP , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"luser-op")
, (ReplyCode
RPL_LUSERUNKNOWN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"luser-unknown")
, (ReplyCode
RPL_LUSERCHANNELS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"luser-channels")
, (ReplyCode
RPL_LUSERME , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"luser-me")
, (ReplyCode
RPL_ADMINME , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"admin-me")
, (ReplyCode
RPL_ADMINLOC1 , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"admin-loc1")
, (ReplyCode
RPL_ADMINLOC2 , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"admin-loc2")
, (ReplyCode
RPL_ADMINEMAIL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"admin-email")
, (ReplyCode
RPL_TRACELOG , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"trace-log")
, (ReplyCode
RPL_ENDOFTRACE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-trace")
, (ReplyCode
RPL_LOAD2HI , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"load-too-high")
, (ReplyCode
RPL_LOCALUSERS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"local-users")
, (ReplyCode
RPL_GLOBALUSERS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"global-users")
, (ReplyCode
RPL_START_NETSTAT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"start-netstat")
, (ReplyCode
RPL_NETSTAT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"netstat")
, (ReplyCode
RPL_END_NETSTAT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-netstat")
, (ReplyCode
RPL_PRIVS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"privs")
, (ReplyCode
RPL_SILELIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"sile-list")
, (ReplyCode
RPL_ENDOFSILELIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-sile-list")
, (ReplyCode
RPL_NOTIFY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"notify")
, (ReplyCode
RPL_ENDNOTIFY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-notify")
, (ReplyCode
RPL_STATSDELTA , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"stats-delta")
, (ReplyCode
RPL_WHOISCERTFP , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-certfp")
, (ReplyCode
RPL_VCHANLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"vchan-list")
, (ReplyCode
RPL_VCHANHELP , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"vchan-help")
, (ReplyCode
RPL_GLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"glist")
, (ReplyCode
RPL_ACCEPTLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"accept-list")
, (ReplyCode
RPL_ENDOFACCEPT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-accept")
, (ReplyCode
RPL_ENDOFJUPELIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-jupe-list")
, (ReplyCode
RPL_FEATURE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"feature")
, (ReplyCode
RPL_DATASTR , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"datastr")
, (ReplyCode
RPL_END_CHANINFO , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-chaninfo")
, (ReplyCode
RPL_NONE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"none")
, (ReplyCode
RPL_AWAY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"away")
, (ReplyCode
RPL_USERHOST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"userhost")
, (ReplyCode
RPL_ISON , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"ison")
, (ReplyCode
RPL_TEXT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"text")
, (ReplyCode
RPL_UNAWAY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"unaway")
, (ReplyCode
RPL_NOWAWAY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"now-away")
, (ReplyCode
RPL_WHOISREGNICK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-regnick")
, (ReplyCode
RPL_SUSERHOST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"suserhost")
, (ReplyCode
RPL_NOTIFYACTION , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"notify-action")
, (ReplyCode
RPL_WHOISADMIN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-admin")
, (ReplyCode
RPL_NICKTRACE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"nick-trace")
, (ReplyCode
RPL_WHOISSADMIN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-sadmin")
, (ReplyCode
RPL_WHOISHELPER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-helper")
, (ReplyCode
RPL_WHOISHELPOP , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-helpop")
, (ReplyCode
RPL_WHOISUSER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-user")
, (ReplyCode
RPL_WHOISSERVER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-server")
, (ReplyCode
RPL_WHOISOPERATOR , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-operator")
, (ReplyCode
RPL_WHOWASUSER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whowas-user")
, (ReplyCode
RPL_ENDOFWHO , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-who")
, (ReplyCode
RPL_WHOISCHANOP , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-chanop")
, (ReplyCode
RPL_WHOISIDLE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-idle")
, (ReplyCode
RPL_ENDOFWHOIS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-whois")
, (ReplyCode
RPL_WHOISCHANNELS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-channels")
, (ReplyCode
RPL_WHOISSPECIAL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-special")
, (ReplyCode
RPL_LISTSTART , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"list-start")
, (ReplyCode
RPL_LIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"list")
, (ReplyCode
RPL_LISTEND , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"list-end")
, (ReplyCode
RPL_CHANNELMODEIS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"channel-mode-is")
, (ReplyCode
RPL_CHANNELMLOCKIS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"channel-mlock-is")
, (ReplyCode
RPL_NOCHANPASS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"nochanpass")
, (ReplyCode
RPL_CHPASSUNKNOWN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"chpass-unknown")
, (ReplyCode
RPL_CHANNEL_URL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"channel-url")
, (ReplyCode
RPL_CREATIONTIME , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"creation-time")
, (ReplyCode
RPL_WHOISACCOUNT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-account")
, (ReplyCode
RPL_NOTOPIC , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"notopic")
, (ReplyCode
RPL_TOPIC , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"topic")
, (ReplyCode
RPL_TOPICWHOTIME , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"topic-whotime")
, (ReplyCode
RPL_LISTUSAGE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"list-usage")
, (ReplyCode
RPL_COMMANDSYNTAX , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"command-syntax")
, (ReplyCode
RPL_LISTSYNTAX , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"list-syntax")
, (ReplyCode
RPL_WHOISACTUALLY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-actually")
, (ReplyCode
RPL_BADCHANPASS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"bad-chanpass")
, (ReplyCode
RPL_INVITING , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"inviting")
, (ReplyCode
RPL_SUMMONING , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"summoning")
, (ReplyCode
RPL_INVITED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"invited")
, (ReplyCode
RPL_INVEXLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"invex-list")
, (ReplyCode
RPL_ENDOFINVEXLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-invex-list")
, (ReplyCode
RPL_EXCEPTLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"except-list")
, (ReplyCode
RPL_ENDOFEXCEPTLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-except-list")
, (ReplyCode
RPL_VERSION , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"version")
, (ReplyCode
RPL_WHOREPLY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"who-reply")
, (ReplyCode
RPL_NAMREPLY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"nam-reply")
, (ReplyCode
RPL_WHOSPCRPL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"who-special-reply")
, (ReplyCode
RPL_NAMREPLY_ , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"nam-reply_")
, (ReplyCode
RPL_WHOWASREAL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whowas-real")
, (ReplyCode
RPL_KILLDONE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"kill-done")
, (ReplyCode
RPL_CLOSING , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"closing")
, (ReplyCode
RPL_CLOSEEND , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"close-end")
, (ReplyCode
RPL_LINKS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"links")
, (ReplyCode
RPL_ENDOFLINKS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-links")
, (ReplyCode
RPL_ENDOFNAMES , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-names")
, (ReplyCode
RPL_BANLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"ban-list")
, (ReplyCode
RPL_ENDOFBANLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-ban-list")
, (ReplyCode
RPL_ENDOFWHOWAS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-whowas")
, (ReplyCode
RPL_INFO , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"info")
, (ReplyCode
RPL_MOTD , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"motd")
, (ReplyCode
RPL_INFOSTART , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"info-start")
, (ReplyCode
RPL_ENDOFINFO , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-info")
, (ReplyCode
RPL_MOTDSTART , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"motd-start")
, (ReplyCode
RPL_ENDOFMOTD , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-motd")
, (ReplyCode
RPL_WHOISHOST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-host")
, (ReplyCode
RPL_WHOISMODES , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-modes")
, (ReplyCode
RPL_YOUREOPER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"youre-oper")
, (ReplyCode
RPL_REHASHING , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"rehashing")
, (ReplyCode
RPL_YOURESERVICE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"youre-service")
, (ReplyCode
RPL_MYPORTIS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"my-port-is")
, (ReplyCode
RPL_NOTOPERANYMORE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"not-oper-anymore")
, (ReplyCode
RPL_RSACHALLENGE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"rsa-challenge")
, (ReplyCode
RPL_TIME , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"time")
, (ReplyCode
RPL_USERSSTART , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"users-start")
, (ReplyCode
RPL_USERS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"users")
, (ReplyCode
RPL_ENDOFUSERS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-users")
, (ReplyCode
RPL_NOUSERS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"nousers")
, (ReplyCode
RPL_HOSTHIDDEN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"host-hidden")
, (ReplyCode
ERR_UNKNOWNERROR , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"unknown-error")
, (ReplyCode
ERR_NOSUCHNICK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-such-nick")
, (ReplyCode
ERR_NOSUCHSERVER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-such-server")
, (ReplyCode
ERR_NOSUCHCHANNEL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-such-channel")
, (ReplyCode
ERR_CANNOTSENDTOCHAN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"cannot-send-to-chan")
, (ReplyCode
ERR_TOOMANYCHANNELS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"too-many-channels")
, (ReplyCode
ERR_WASNOSUCHNICK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"was-no-such-nick")
, (ReplyCode
ERR_TOOMANYTARGETS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"too-many-targets")
, (ReplyCode
ERR_NOORIGIN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-origin")
, (ReplyCode
ERR_INVALIDCAPCMD , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"invalid-cap-cmd")
, (ReplyCode
ERR_NORECIPIENT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-recipient")
, (ReplyCode
ERR_NOTEXTTOSEND , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-text-to-send")
, (ReplyCode
ERR_NOTOPLEVEL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-top-level")
, (ReplyCode
ERR_WILDTOPLEVEL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"wild-top-level")
, (ReplyCode
ERR_MSGNEEDREGGEDNICK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"msg-need-regged-nick")
, (ReplyCode
ERR_TOOMANYMATCHES , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"too-many-matches")
, (ReplyCode
ERR_LENGTHTRUNCATED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"length-truncated")
, (ReplyCode
ERR_UNKNOWNCOMMAND , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"unknown-command")
, (ReplyCode
ERR_NOMOTD , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-motd")
, (ReplyCode
ERR_NOADMININFO , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-admin-info")
, (ReplyCode
ERR_FILEERROR , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"file-error")
, (ReplyCode
ERR_NOOPERMOTD , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-oper-motd")
, (ReplyCode
ERR_TOOMANYAWAY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"too-many-away")
, (ReplyCode
ERR_EVENTNICKCHANGE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"event-nick-change")
, (ReplyCode
ERR_NONICKNAMEGIVEN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-nickname-given")
, (ReplyCode
ERR_ERRONEUSNICKNAME , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"err-no-use-nickname")
, (ReplyCode
ERR_NICKNAMEINUSE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"nickname-in-use")
, (ReplyCode
ERR_SERVICENAMEINUSE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"service-name-in-use")
, (ReplyCode
ERR_NORULES , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-rules")
, (ReplyCode
ERR_BANNICKCHANGE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"ban-nick-change")
, (ReplyCode
ERR_NICKCOLLISION , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"nick-collision")
, (ReplyCode
ERR_UNAVAILRESOURCE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"unavail-resource")
, (ReplyCode
ERR_NICKTOOFAST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"nick-too-fast")
, (ReplyCode
ERR_TARGETTOOFAST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"target-too-fast")
, (ReplyCode
ERR_SERVICESDOWN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"services-down")
, (ReplyCode
ERR_USERNOTINCHANNEL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"user-not-in-channel")
, (ReplyCode
ERR_NOTONCHANNEL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"not-on-channel")
, (ReplyCode
ERR_USERONCHANNEL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"user-on-channel")
, (ReplyCode
ERR_NOLOGIN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-login")
, (ReplyCode
ERR_SUMMONDISABLED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"summon-disabled")
, (ReplyCode
ERR_USERSDISABLED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"users-disabled")
, (ReplyCode
ERR_NONICKCHANGE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-nick-change")
, (ReplyCode
ERR_NOTIMPLEMENTED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"not-implemented")
, (ReplyCode
ERR_NOTREGISTERED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"not-registered")
, (ReplyCode
ERR_IDCOLLISION , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"id-collision")
, (ReplyCode
ERR_NICKLOST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"nick-lost")
, (ReplyCode
ERR_HOSTILENAME , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"hostile-name")
, (ReplyCode
ERR_ACCEPTFULL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"accept-full")
, (ReplyCode
ERR_ACCEPTEXIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"accept-exist")
, (ReplyCode
ERR_ACCEPTNOT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"accept-not")
, (ReplyCode
ERR_NOHIDING , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-hiding")
, (ReplyCode
ERR_NOTFORHALFOPS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"not-for-halfops")
, (ReplyCode
ERR_NEEDMOREPARAMS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"need-more-params")
, (ReplyCode
ERR_ALREADYREGISTERED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"already-registered")
, (ReplyCode
ERR_NOPERMFORHOST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-perm-for-host")
, (ReplyCode
ERR_PASSWDMISMATCH , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"passwd-mismatch")
, (ReplyCode
ERR_YOUREBANNEDCREEP , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"youre-banned-creep")
, (ReplyCode
ERR_YOUWILLBEBANNED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"you-will-be-banned")
, (ReplyCode
ERR_KEYSET , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"keyset")
, (ReplyCode
ERR_INVALIDUSERNAME , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"invalid-username")
, (ReplyCode
ERR_ONLYSERVERSCANCHANGE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"only-servers-can-change")
, (ReplyCode
ERR_LINKSET , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"link-set")
, (ReplyCode
ERR_LINKCHANNEL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"link-channel")
, (ReplyCode
ERR_CHANNELISFULL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"channel-is-full")
, (ReplyCode
ERR_UNKNOWNMODE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"unknown-mode")
, (ReplyCode
ERR_INVITEONLYCHAN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"invite-only-chan")
, (ReplyCode
ERR_BANNEDFROMCHAN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"banned-from-chan")
, (ReplyCode
ERR_BADCHANNELKEY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"bad-channel-key")
, (ReplyCode
ERR_BADCHANMASK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"bad-chan-mask")
, (ReplyCode
ERR_NEEDREGGEDNICK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"need-regged-nick")
, (ReplyCode
ERR_BANLISTFULL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"ban-list-full")
, (ReplyCode
ERR_BADCHANNAME , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"bad-chan-name")
, (ReplyCode
ERR_THROTTLE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"throttle")
, (ReplyCode
ERR_NOPRIVILEGES , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-privileges")
, (ReplyCode
ERR_CHANOPRIVSNEEDED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"chano-privs-needed")
, (ReplyCode
ERR_CANTKILLSERVER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"cant-kill-server")
, (ReplyCode
ERR_ISCHANSERVICE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"is-chan-service")
, (ReplyCode
ERR_BANNEDNICK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"banned-nick")
, (ReplyCode
ERR_NONONREG , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-nonreg")
, (ReplyCode
ERR_TSLESSCHAN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"tsless-chan")
, (ReplyCode
ERR_VOICENEEDED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"voice-needed")
, (ReplyCode
ERR_NOOPERHOST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-oper-host")
, (ReplyCode
ERR_NOSERVICEHOST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-service-host")
, (ReplyCode
ERR_NOFEATURE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-feature")
, (ReplyCode
ERR_OWNMODE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"own-mode")
, (ReplyCode
ERR_BADLOGTYPE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"bad-log-type")
, (ReplyCode
ERR_BADLOGSYS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"bad-log-sys")
, (ReplyCode
ERR_BADLOGVALUE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"bad-log-value")
, (ReplyCode
ERR_ISOPERLCHAN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"is-oper-lchan")
, (ReplyCode
ERR_CHANOWNPRIVNEEDED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"chan-own-priv-needed")
, (ReplyCode
ERR_UMODEUNKNOWNFLAG , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"umode-unknown-flag")
, (ReplyCode
ERR_USERSDONTMATCH , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"users-dont-match")
, (ReplyCode
ERR_GHOSTEDCLIENT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"ghosted-client")
, (ReplyCode
ERR_USERNOTONSERV , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"user-not-on-serv")
, (ReplyCode
ERR_SILELISTFULL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"sile-list-full")
, (ReplyCode
ERR_TOOMANYWATCH , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"too-many-watch")
, (ReplyCode
ERR_WRONGPONG , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"wrong-pong")
, (ReplyCode
ERR_BADEXPIRE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"bad-expire")
, (ReplyCode
ERR_DONTCHEAT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"dont-cheat")
, (ReplyCode
ERR_DISABLED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"disabled")
, (ReplyCode
ERR_NOINVITE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-invite")
, (ReplyCode
ERR_LONGMASK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"long-mask")
, (ReplyCode
ERR_ADMONLY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"adm-only")
, (ReplyCode
ERR_TOOMANYUSERS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"too-many-users")
, (ReplyCode
ERR_OPERONLY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"oper-only")
, (ReplyCode
ERR_MASKTOOWIDE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"mask-too-wide")
, (ReplyCode
ERR_WHOTRUNC , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"who-trunc")
, (ReplyCode
ERR_LISTSYNTAX , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"list-syntax")
, (ReplyCode
ERR_WHOSYNTAX , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"whosyntax")
, (ReplyCode
ERR_WHOLIMEXCEED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"wholimexceed")
, (ReplyCode
ERR_HELPNOTFOUND , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"help-not-found")
, (ReplyCode
ERR_REMOTEPFX , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"remote-pfx")
, (ReplyCode
ERR_PFXUNROUTABLE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"pfx-unroutable")
, (ReplyCode
ERR_BADHOSTMASK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"bad-hostmask")
, (ReplyCode
ERR_HOSTUNAVAIL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"host-unavail")
, (ReplyCode
ERR_USINGSLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"using-sline")
, (ReplyCode
ERR_STATSSLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"stats-sline")
, (ReplyCode
RPL_LOGON , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"logon")
, (ReplyCode
RPL_LOGOFF , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"logoff")
, (ReplyCode
RPL_WATCHOFF , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"watch-off")
, (ReplyCode
RPL_WATCHSTAT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"watch-stat")
, (ReplyCode
RPL_NOWON , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"now-on")
, (ReplyCode
RPL_NOWOFF , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"now-off")
, (ReplyCode
RPL_WATCHLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"watch-list")
, (ReplyCode
RPL_ENDOFWATCHLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-watch-list")
, (ReplyCode
RPL_WATCHCLEAR , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"watch-clear")
, (ReplyCode
RPL_ISOPER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"is-oper")
, (ReplyCode
RPL_ISLOCOP , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"is-loc-op")
, (ReplyCode
RPL_ISNOTOPER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"is-not-oper")
, (ReplyCode
RPL_ENDOFISOPER , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-is-oper")
, (ReplyCode
RPL_DCCSTATUS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"dcc-status")
, (ReplyCode
RPL_DCCLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"dcc-list")
, (ReplyCode
RPL_ENDOFDCCLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-dcc-list")
, (ReplyCode
RPL_WHOWASHOST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whowas-host")
, (ReplyCode
RPL_DCCINFO , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"dcc-info")
, (ReplyCode
RPL_RULES , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"rules")
, (ReplyCode
RPL_ENDOFO , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-o")
, (ReplyCode
RPL_SETTINGS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"settings")
, (ReplyCode
RPL_ENDOFSETTINGS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-settings")
, (ReplyCode
RPL_DUMPING , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"dumping")
, (ReplyCode
RPL_DUMPRPL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"dump-rpl")
, (ReplyCode
RPL_EODUMP , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"eodump")
, (ReplyCode
RPL_TRACEROUTE_HOP , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"traceroute-hop")
, (ReplyCode
RPL_TRACEROUTE_START , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"traceroute-start")
, (ReplyCode
RPL_MODECHANGEWARN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"mode-change-warn")
, (ReplyCode
RPL_CHANREDIR , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"chan-redir")
, (ReplyCode
RPL_SERVMODEIS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"serv-mode-is")
, (ReplyCode
RPL_OTHERUMODEIS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"other-umode-is")
, (ReplyCode
RPL_ENDOF_GENERIC , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-generic")
, (ReplyCode
RPL_STARTTLS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"start-tls")
, (ReplyCode
RPL_WHOISSECURE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-secure")
, (ReplyCode
RPL_UNKNOWNMODES , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"unknown-modes")
, (ReplyCode
RPL_CANNOTSETMODES , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"cannot-set-modes")
, (ReplyCode
RPL_LUSERSTAFF , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"luser-staff")
, (ReplyCode
RPL_TIMEONSERVERIS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"time-on-server-is")
, (ReplyCode
RPL_NETWORKS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"networks")
, (ReplyCode
RPL_YOURLANGUAGEIS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"your-language-is")
, (ReplyCode
RPL_LANGUAGE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"language")
, (ReplyCode
RPL_WHOISSTAFF , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"whois-staff")
, (ReplyCode
RPL_WHOISLANGUAGE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"who-is-language")
, (ReplyCode
ERR_STARTTLS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"err-start-tls")
, (ReplyCode
RPL_MODLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"mod-list")
, (ReplyCode
RPL_ENDOFMODLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-modlist")
, (ReplyCode
RPL_HELPSTART , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"help-start")
, (ReplyCode
RPL_HELPTXT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"help-txt")
, (ReplyCode
RPL_ENDOFHELP , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-help")
, (ReplyCode
ERR_TARGCHANGE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"targ-change")
, (ReplyCode
RPL_ETRACEFULL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"etrace-full")
, (ReplyCode
RPL_ETRACE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"etrace")
, (ReplyCode
RPL_KNOCK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"knock")
, (ReplyCode
RPL_KNOCKDLVR , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"knockd-lvr")
, (ReplyCode
ERR_TOOMANYKNOCK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"too-many-knock")
, (ReplyCode
ERR_CHANOPEN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"chan-open")
, (ReplyCode
ERR_KNOCKONCHAN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"knock-on-chan")
, (ReplyCode
ERR_KNOCKDISABLED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"knock-disabled")
, (ReplyCode
RPL_TARGUMODEG , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"targ-umodeg")
, (ReplyCode
RPL_TARGNOTIFY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"targ-notify")
, (ReplyCode
RPL_UMODEGMSG , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"umodeg-msg")
, (ReplyCode
RPL_OMOTDSTART , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"omotd-start")
, (ReplyCode
RPL_OMOTD , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"omotd")
, (ReplyCode
RPL_ENDOFOMOTD , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-omotd")
, (ReplyCode
ERR_NOPRIVS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-privs")
, (ReplyCode
RPL_TESTMASK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"test-mask")
, (ReplyCode
RPL_TESTLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"test-line")
, (ReplyCode
RPL_NOTESTLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"no-test-line")
, (ReplyCode
RPL_TESTMASKGECOS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"testmask-gecos")
, (ReplyCode
RPL_QUIETLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"quiet-list")
, (ReplyCode
RPL_ENDOFQUIETLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-quiet-list")
, (ReplyCode
RPL_MONONLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"mon-online")
, (ReplyCode
RPL_MONOFFLINE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"mon-offline")
, (ReplyCode
RPL_MONLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"mon-list")
, (ReplyCode
RPL_ENDOFMONLIST , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-mon-list")
, (ReplyCode
ERR_MONLISTFULL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"mon-list-full")
, (ReplyCode
RPL_RSACHALLENGE2 , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"rsa-challenge2")
, (ReplyCode
RPL_ENDOFRSACHALLENGE2 , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"end-of-rsa-challenge2")
, (ReplyCode
ERR_MLOCKRESTRICTED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"mlock-restricted")
, (ReplyCode
RPL_SCANMATCHED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"scan-matched")
, (ReplyCode
RPL_SCANUMODES , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"scan-umodes")
, (ReplyCode
RPL_XINFO , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"xinfo")
, (ReplyCode
RPL_XINFOSTART , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"xinfo-start")
, (ReplyCode
RPL_XINFOEND , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"xinfo-end")
, (ReplyCode
RPL_LOGGEDIN , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"logged-in")
, (ReplyCode
RPL_LOGGEDOUT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"logged-out")
, (ReplyCode
RPL_NICKLOCKED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"nick-locked")
, (ReplyCode
RPL_SASLSUCCESS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"sasl-success")
, (ReplyCode
ERR_SASLFAIL , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"sasl-fail")
, (ReplyCode
ERR_SASLTOOLONG , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"sasl-toolong")
, (ReplyCode
ERR_SASLABORTED , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"sasl-aborted")
, (ReplyCode
ERR_SASLALREADY , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"sasl-already")
, (ReplyCode
RPL_SASLMECHS , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
CommandReply Text
"sasl-mechs")
, (ReplyCode
ERR_CANNOTDOCOMMAND , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"cannot-do-command")
, (ReplyCode
ERR_CANNOTCHANGEUMODE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"cannot-change-umode")
, (ReplyCode
ERR_CANNOTCHANGECHANMODE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"cannot-change-chan-mode")
, (ReplyCode
ERR_CANNOTCHANGESERVERMODE, ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"cannot-change-server-mode")
, (ReplyCode
ERR_CANNOTSENDTONICK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"cannot-send-to-nick")
, (ReplyCode
ERR_UNKNOWNSERVERMODE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"unknown-server-mode")
, (ReplyCode
ERR_SERVERMODELOCK , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"server-mode-lock")
, (ReplyCode
ERR_BADCHARENCODING , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"bad-char-encoding")
, (ReplyCode
ERR_TOOMANYLANGUAGES , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"too-many-languages")
, (ReplyCode
ERR_NOLANGUAGE , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"no-language")
, (ReplyCode
ERR_TEXTTOOSHORT , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"text-too-short")
, (ReplyCode
ERR_NUMERIC_ERR , ReplyType -> Text -> ReplyCodeInfo
ReplyCodeInfo ReplyType
ErrorReply Text
"numeric-err")
]