Copyright | (c) Eric Mertens 2016 |
---|---|
License | ISC |
Maintainer | emertens@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
This module is responsible for tracking the state of an individual IRC connection while the client is connected to it. This state includes user information, server settings, channel membership, and more.
This module is more complicated than many of the other modules in the client because it is responsible for interpreting each IRC message from the server and updating the connection state accordingly.
Synopsis
- data NetworkState = NetworkState {
- _csChannels :: !(HashMap Identifier ChannelState)
- _csSocket :: !NetworkConnection
- _csModeTypes :: !ModeTypes
- _csUmodeTypes :: !ModeTypes
- _csChannelTypes :: ![Char]
- _csTransaction :: !Transaction
- _csModes :: ![Char]
- _csSnomask :: ![Char]
- _csStatusMsg :: ![Char]
- _csSettings :: !ServerSettings
- _csUserInfo :: !UserInfo
- _csUsers :: !(HashMap Identifier UserAndHost)
- _csModeCount :: !Int
- _csNetwork :: !Text
- _csMessageHooks :: ![MessageHook]
- _csAuthenticationState :: !AuthenticateState
- _csNextPingTime :: !(Maybe UTCTime)
- _csLatency :: !(Maybe NominalDiffTime)
- _csPingStatus :: !PingStatus
- _csLastReceived :: !(Maybe UTCTime)
- _csCertificate :: ![Text]
- data AuthenticateState
- newNetworkState :: Text -> ServerSettings -> NetworkConnection -> PingStatus -> NetworkState
- csNick :: Lens' NetworkState Identifier
- csChannels :: Lens' NetworkState (HashMap Identifier ChannelState)
- csSocket :: Lens' NetworkState NetworkConnection
- csModeTypes :: Lens' NetworkState ModeTypes
- csChannelTypes :: Lens' NetworkState [Char]
- csTransaction :: Lens' NetworkState Transaction
- csModes :: Lens' NetworkState [Char]
- csSnomask :: Lens' NetworkState [Char]
- csStatusMsg :: Lens' NetworkState [Char]
- csSettings :: Lens' NetworkState ServerSettings
- csUserInfo :: Lens' NetworkState UserInfo
- csUsers :: Lens' NetworkState (HashMap Identifier UserAndHost)
- csUser :: Functor f => Identifier -> LensLike' f NetworkState (Maybe UserAndHost)
- csModeCount :: Lens' NetworkState Int
- csNetwork :: Lens' NetworkState Text
- csNextPingTime :: Lens' NetworkState (Maybe UTCTime)
- csPingStatus :: Lens' NetworkState PingStatus
- csLatency :: Lens' NetworkState (Maybe NominalDiffTime)
- csLastReceived :: Lens' NetworkState (Maybe UTCTime)
- csCertificate :: Lens' NetworkState [Text]
- csMessageHooks :: Lens' NetworkState [MessageHook]
- csAuthenticationState :: Lens' NetworkState AuthenticateState
- data Transaction
- = NoTransaction
- | NamesTransaction [Text]
- | BanTransaction [(Text, MaskListEntry)]
- | WhoTransaction [UserInfo]
- | CapTransaction
- | CapLsTransaction [(Text, Maybe Text)]
- isChannelIdentifier :: NetworkState -> Identifier -> Bool
- iHaveOp :: Identifier -> NetworkState -> Bool
- sendMsg :: NetworkState -> RawIrcMsg -> IO ()
- initialMessages :: NetworkState -> [RawIrcMsg]
- applyMessage :: ZonedTime -> IrcMsg -> NetworkState -> ([RawIrcMsg], NetworkState)
- squelchIrcMsg :: IrcMsg -> Bool
- data PingStatus
- _PingConnecting :: Prism' PingStatus (Int, Maybe UTCTime)
- data TimedAction
- nextTimedAction :: NetworkState -> Maybe (UTCTime, TimedAction)
- applyTimedAction :: TimedAction -> NetworkState -> IO NetworkState
- useChanServ :: Identifier -> NetworkState -> Bool
- sendModeration :: Identifier -> [RawIrcMsg] -> NetworkState -> IO NetworkState
- sendTopic :: Identifier -> Text -> NetworkState -> IO ()
Connection state
data NetworkState Source #
State tracked for each IRC connection
NetworkState | |
|
data AuthenticateState Source #
State of the authentication transaction
AS_None | no active transaction |
AS_PlainStarted | PLAIN mode initiated |
AS_EcdsaStarted | ECDSA-NIST mode initiated |
AS_EcdsaWaitChallenge | ECDSA-NIST user sent waiting for challenge |
AS_ExternalStarted | EXTERNAL mode initiated |
Instances
Show AuthenticateState Source # | |
Defined in Client.State.Network showsPrec :: Int -> AuthenticateState -> ShowS # show :: AuthenticateState -> String # showList :: [AuthenticateState] -> ShowS # |
:: Text | network name |
-> ServerSettings | server settings |
-> NetworkConnection | active network connection |
-> PingStatus | initial ping status |
-> NetworkState | new network state |
Construct a new network state using the given settings and default values as specified by the IRC specification.
Lenses
csStatusMsg :: Lens' NetworkState [Char] Source #
csUser :: Functor f => Identifier -> LensLike' f NetworkState (Maybe UserAndHost) Source #
Cross-message state
data Transaction Source #
NoTransaction | |
NamesTransaction [Text] | |
BanTransaction [(Text, MaskListEntry)] | |
WhoTransaction [UserInfo] | |
CapTransaction | |
CapLsTransaction [(Text, Maybe Text)] |
Instances
Show Transaction Source # | |
Defined in Client.State.Network showsPrec :: Int -> Transaction -> ShowS # show :: Transaction -> String # showList :: [Transaction] -> ShowS # |
Connection predicates
isChannelIdentifier :: NetworkState -> Identifier -> Bool Source #
iHaveOp :: Identifier -> NetworkState -> Bool Source #
Predicate to test if the connection has op in a given channel.
Messages interactions
sendMsg :: NetworkState -> RawIrcMsg -> IO () Source #
Transmit a RawIrcMsg
on the connection associated
with the given network. For PRIVMSG
and NOTICE
overlong
commands are detected and transmitted as multiple messages.
initialMessages :: NetworkState -> [RawIrcMsg] Source #
applyMessage :: ZonedTime -> IrcMsg -> NetworkState -> ([RawIrcMsg], NetworkState) Source #
squelchIrcMsg :: IrcMsg -> Bool Source #
Return True
for messages that should be hidden outside of
full detail view. These messages are interpreted by the client
so the user shouldn't need to see them directly to get the
relevant information.
Timer information
data PingStatus Source #
Status of the ping timer
PingSent !UTCTime | ping sent at given time, waiting for pong |
PingNone | not waiting for a pong |
PingConnecting !Int !(Maybe UTCTime) | number of attempts, last known connection time |
Instances
Show PingStatus Source # | |
Defined in Client.State.Network showsPrec :: Int -> PingStatus -> ShowS # show :: PingStatus -> String # showList :: [PingStatus] -> ShowS # |
data TimedAction Source #
Timer-based events
TimedDisconnect | terminate the connection due to timeout |
TimedSendPing | transmit a ping to the server |
TimedForgetLatency | erase latency (when it is outdated) |
Instances
Eq TimedAction Source # | |
Defined in Client.State.Network (==) :: TimedAction -> TimedAction -> Bool # (/=) :: TimedAction -> TimedAction -> Bool # | |
Ord TimedAction Source # | |
Defined in Client.State.Network compare :: TimedAction -> TimedAction -> Ordering # (<) :: TimedAction -> TimedAction -> Bool # (<=) :: TimedAction -> TimedAction -> Bool # (>) :: TimedAction -> TimedAction -> Bool # (>=) :: TimedAction -> TimedAction -> Bool # max :: TimedAction -> TimedAction -> TimedAction # min :: TimedAction -> TimedAction -> TimedAction # | |
Show TimedAction Source # | |
Defined in Client.State.Network showsPrec :: Int -> TimedAction -> ShowS # show :: TimedAction -> String # showList :: [TimedAction] -> ShowS # |
nextTimedAction :: NetworkState -> Maybe (UTCTime, TimedAction) Source #
Compute the earliest timed action for a connection, if any
applyTimedAction :: TimedAction -> NetworkState -> IO NetworkState Source #
Apply the given TimedAction
to a connection state.
Moderation
:: Identifier | channel |
-> NetworkState | network state |
-> Bool | chanserv available |
:: Identifier | channel |
-> [RawIrcMsg] | commands |
-> NetworkState | network state |
-> IO NetworkState |
Used to send commands that require ops to perform. If this channel is one that the user has chanserv access and ops are needed then ops are requested and the commands are queued, otherwise send them directly.
:: Identifier | channel |
-> Text | topic |
-> NetworkState | network state |
-> IO () |